1
1
-- Retina - Proyecto de Traductores
2
- -- OurMonad , Monad para realizar el analisis de contexto y sus funciones respectivas.
2
+ -- OurContextMonad , Monad para realizar el analisis de contexto y sus funciones respectivas.
3
3
-- Augusto Hidalgo 13-10665
4
4
-- Genesis Kufatty 13-10708
5
5
6
- module OurMonad where
6
+ module OurContextMonad where
7
7
8
8
import Control.Monad.Error
9
9
import Control.Monad.State
@@ -29,11 +29,11 @@ data Scope = Scope {getList::[(String, OurType)]}
29
29
30
30
data FuncSign = FuncSign { getId :: String , getType :: OurType , getParamList :: [(String ,OurType )]}
31
31
32
- data SymTable = SymTable { getScopes :: [Scope ], getFuncSigns :: [FuncSign ]}
32
+ data ContextSymTable = ContextSymTable { getScopes :: [Scope ], getFuncSigns :: [FuncSign ]}
33
33
34
- data OurState = OurState { getSymTable :: SymTable , getReturnT :: (Maybe OurType )}
34
+ data OurContextState = OurContextState { getSymTable :: ContextSymTable , getReturnT :: (Maybe OurType )}
35
35
36
- emptyState = OurState ( SymTable [] [] ) Nothing
36
+ emptyContextState = OurContextState ( ContextSymTable [] [] ) Nothing
37
37
38
38
data OurLog = OurLog { getScopesLog :: String , getWarningsLog :: String }
39
39
@@ -49,43 +49,43 @@ scopeToOurLog s = OurLog s ""
49
49
warningToOurLog s = OurLog " " s
50
50
51
51
52
- type OurMonad a = StateT OurState (WriterT OurLog (Either OurError )) a
52
+ type OurContextMonad a = StateT OurContextState (WriterT OurLog (Either OurError )) a
53
53
54
- runOurMonad :: OurMonad a -> OurState -> Either OurError ((a , OurState ), OurLog )
55
- runOurMonad f a = runWriterT (runStateT f a)
54
+ runOurContextMonad :: OurContextMonad a -> OurContextState -> Either OurError ((a , OurContextState ), OurLog )
55
+ runOurContextMonad f a = runWriterT (runStateT f a)
56
56
57
- getLog f a = show $ snd $ getRight $ runOurMonad f a `catchError` (\ (OurError pos s) -> error $ " \n Error en linea " ++ show pos++ " :\n " ++ s)
57
+ getLog f a = show $ snd $ getRight $ runOurContextMonad f a `catchError` (\ (OurError pos s) -> error $ " \n Error en linea " ++ show pos++ " :\n " ++ s)
58
58
where
59
59
getRight (Right x) = x
60
60
61
61
62
62
lookInList :: String -> [(String , OurType )] -> Maybe OurType
63
63
lookInList s l = snd <$> find ((== s). fst ) l
64
64
65
- lookInLastScope :: String -> OurMonad (Maybe OurType )
65
+ lookInLastScope :: String -> OurContextMonad (Maybe OurType )
66
66
lookInLastScope s = lookInList s. getList. head'. getScopes. getSymTable <$> get
67
67
where head' [] = Scope []
68
68
head' (a: as) = a
69
69
70
- lookInSymTable :: String -> OurMonad (Maybe OurType )
70
+ lookInSymTable :: String -> OurContextMonad (Maybe OurType )
71
71
lookInSymTable s = msum . map (lookInList s) . (map getList). getScopes. getSymTable <$> get
72
72
73
- newScope :: OurMonad ()
73
+ newScope :: OurContextMonad ()
74
74
newScope = do
75
75
oldState <- get
76
76
let oldSymTable = getSymTable oldState
77
77
oldScopes = getScopes oldSymTable
78
78
newSymTable = oldSymTable {getScopes = (Scope [] ): oldScopes}
79
79
put $ oldState {getSymTable = newSymTable}
80
80
81
- removeLastScope :: OurMonad ()
81
+ removeLastScope :: OurContextMonad ()
82
82
removeLastScope = do
83
83
oldState <- get
84
84
let oldSymTable = getSymTable oldState
85
85
newSymTable = oldSymTable {getScopes = tail . getScopes $ oldSymTable }
86
86
put $ oldState { getSymTable = newSymTable}
87
87
88
- addToSymTable :: (String , OurType ) -> OurMonad ()
88
+ addToSymTable :: (String , OurType ) -> OurContextMonad ()
89
89
addToSymTable pair = do
90
90
oldState <- get
91
91
let oldSymTable = getSymTable oldState
@@ -95,15 +95,15 @@ addToSymTable pair = do
95
95
newSymTable = oldSymTable { getScopes = newScopeList }
96
96
put $ oldState { getSymTable = newSymTable }
97
97
98
- addFunctionSign :: String -> [(String , OurType )] -> OurType -> OurMonad () -- No crea el scope
98
+ addFunctionSign :: String -> [(String , OurType )] -> OurType -> OurContextMonad () -- No crea el scope
99
99
addFunctionSign s params typ = do
100
100
oldState <- get
101
101
let newFunc = FuncSign s typ params
102
102
oldSymTable = getSymTable oldState
103
103
newSymTable = oldSymTable { getFuncSigns = newFunc: (getFuncSigns oldSymTable) }
104
104
put $ oldState { getSymTable = newSymTable }
105
105
106
- lookFunction :: String -> OurMonad Bool
106
+ lookFunction :: String -> OurContextMonad Bool
107
107
lookFunction s = do
108
108
oldState <- get
109
109
let funcsList = map (getId) (getFuncSigns. getSymTable $ oldState)
@@ -113,29 +113,29 @@ lookFunction s = do
113
113
_ -> True
114
114
return ans
115
115
116
- getFunctionReturnType :: String -> OurMonad OurType
116
+ getFunctionReturnType :: String -> OurContextMonad OurType
117
117
getFunctionReturnType s = do
118
118
oldState <- get
119
119
let listFunc = getFuncSigns. getSymTable $ oldState
120
120
func = filter ((== s). getId) listFunc
121
121
return $ getType. head $ func
122
122
123
- checkFunction :: String -> [OurType ] -> OurMonad (Bool ,Int )
123
+ checkFunction :: String -> [OurType ] -> OurContextMonad (Bool ,Int )
124
124
checkFunction s list = do
125
125
oldState <- get
126
126
let listF = getParamList $ head $ filter ((== s). getId) (getFuncSigns. getSymTable $ oldState)
127
127
listType = map snd listF
128
128
return (listType== list,length listType)
129
129
130
- setReturnType :: Maybe OurType -> OurMonad ()
130
+ setReturnType :: Maybe OurType -> OurContextMonad ()
131
131
setReturnType typeR = do
132
132
oldState <- get
133
133
put $ oldState { getReturnT = typeR }
134
134
135
- getReturnType :: OurMonad (Maybe OurType )
135
+ getReturnType :: OurContextMonad (Maybe OurType )
136
136
getReturnType = get >>= (return . getReturnT)
137
137
138
- lastScopeToLog :: String -> OurMonad ()
138
+ lastScopeToLog :: String -> OurContextMonad ()
139
139
lastScopeToLog scopeName = do
140
140
scopes <- getScopes. getSymTable <$> get
141
141
let nested = length scopes
@@ -145,6 +145,6 @@ lastScopeToLog scopeName = do
145
145
tell. scopeToOurLog $ concatMap (\ s -> ident++ " |> " ++ s++ " \n " ) $ map showVarAndType $ reverse . getList $ lastScope
146
146
where
147
147
showVarAndType (s, t) = s ++ " : " ++ show t
148
- warningToLog :: String -> OurMonad ()
148
+ warningToLog :: String -> OurContextMonad ()
149
149
warningToLog warning = do
150
150
tell. warningToOurLog $ warning++ " \n "
0 commit comments