Skip to content

Commit 56520f5

Browse files
committed
Nombres cambiados
1 parent ba9500e commit 56520f5

File tree

5 files changed

+43
-42
lines changed

5 files changed

+43
-42
lines changed

.gitignore

+2
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
*.hi
22
*.o
3+
*.pbm
34
Lexer.hs
45
Parser.hs
56
retina
7+
^intento$

SemanticChecker.hs ContextChecker.hs

+11-11
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@
33
-- Augusto Hidalgo 13-10665
44
-- Genesis Kufatty 13-10708
55

6-
module SemanticChecker where
6+
module ContextChecker where
77
import AST
8-
import OurMonad
8+
import OurContextMonad
99
import Control.Monad.Error
1010
import Control.Monad.State
1111
import Control.Monad.Writer
@@ -39,7 +39,7 @@ typeNConvert NumberN = Number
3939
----------------------------------------------------------
4040
-- checkConstrN ------------------------------------------
4141
----------------------------------------------------------
42-
checkConstrN :: ConstrN -> OurMonad ()
42+
checkConstrN :: ConstrN -> OurContextMonad ()
4343
checkConstrN (PN ldfN instrListN) = do
4444
addFunctionSign "home" [] Void
4545
addFunctionSign "openeye" [] Void
@@ -62,11 +62,11 @@ checkConstrN (LDFN l) = do
6262
checkConstrN (LDN l) = do
6363
mapM_ proccessTypeAndList l
6464
where
65-
proccessTypeAndList :: (TypeN, [VarN]) -> OurMonad ()
65+
proccessTypeAndList :: (TypeN, [VarN]) -> OurContextMonad ()
6666
proccessTypeAndList (tN, varNList) = do
6767
let t = typeNConvert tN
6868
mapM_ (adder t) varNList -- lanza error sin pos y en el with catcharlo y lanzarlo bien
69-
adder :: OurType -> VarN -> OurMonad ()
69+
adder :: OurType -> VarN -> OurContextMonad ()
7070
adder t varN = do
7171
let (s,me) = case varN of
7272
(VarN st) -> (st, Nothing)
@@ -85,7 +85,7 @@ checkConstrN (LDN l) = do
8585
----------------------------------------------------------
8686
-- checkFuncDefN -----------------------------------------
8787
----------------------------------------------------------
88-
checkFuncDefN :: FuncDefN -> OurMonad ()
88+
checkFuncDefN :: FuncDefN -> OurContextMonad ()
8989
checkFuncDefN funcDefN = do
9090
let (funId, paramList, instrListN, lineNum, retType) = case funcDefN of
9191
DFN s p i (ln,_) -> (s,(map (\(x,y) -> (y, typeNConvert x))).listLPN $ p,i,ln, Void)
@@ -118,14 +118,14 @@ checkFuncDefN funcDefN = do
118118
----------------------------------------------------------
119119
-- checkInstrListN ---------------------------------------
120120
----------------------------------------------------------
121-
checkInstrListN :: InstrListN -> OurMonad Returned
121+
checkInstrListN :: InstrListN -> OurContextMonad Returned
122122
checkInstrListN (LIN instrList) = do
123123
(foldl (|+|) No) <$> (mapM checkInstrN instrList)
124124

125125
----------------------------------------------------------
126126
-- checkInstrN -------------------------------------------
127127
----------------------------------------------------------
128-
checkInstrN :: InstrN -> OurMonad Returned
128+
checkInstrN :: InstrN -> OurContextMonad Returned
129129
checkInstrN (WithDoN ldn lin (lineNum,_)) = do
130130
newScope
131131
checkConstrN ldn `catchError` (reThrow lineNum)
@@ -134,7 +134,7 @@ checkInstrN (WithDoN ldn lin (lineNum,_)) = do
134134
removeLastScope
135135
return res
136136
where
137-
reThrow :: Int -> OurError -> OurMonad ()
137+
reThrow :: Int -> OurError -> OurContextMonad ()
138138
reThrow lineNum (OurErrorNoPos s) = throwError $ OurError lineNum s
139139
reThrow lineNum e = throwError e
140140

@@ -228,7 +228,7 @@ checkInstrN (ExprN expN) = do
228228
----------------------------------------------------------
229229
-- checkExpN ---------------------------------------------
230230
----------------------------------------------------------
231-
checkExpN :: ExpN -> OurMonad OurType
231+
checkExpN :: ExpN -> OurContextMonad OurType
232232
checkExpN (IdN s (lineNum,_)) = do
233233
bo <- lookInSymTable s
234234
when (bo==Nothing) $ throwError $ OurError lineNum $ "'"++s++"' no esta declarada en este alcance."
@@ -297,7 +297,7 @@ checkExpN (NumberLiteralN s _) = do
297297
----------------------------------------------------------
298298
-- checkWordListN ----------------------------------------
299299
----------------------------------------------------------
300-
checkWordListN :: [WordN] -> OurMonad ()
300+
checkWordListN :: [WordN] -> OurContextMonad ()
301301
checkWordListN (wordList) = do
302302
mapM_ checkWord wordList
303303
where checkWord (PWEN exp) = do

Makefile

+5-5
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
retina: Lexer Parser OurMonad SemanticChecker
1+
retina: Lexer Parser OurContextMonad ContextChecker
22
ghc --make -w retina.hs
33

44
Lexer: Lexer.x
@@ -7,11 +7,11 @@ Lexer: Lexer.x
77
Parser: Parser.y
88
happy Parser.y
99

10-
OurMonad: OurMonad.hs
11-
ghc --make -w OurMonad.hs
10+
OurContextMonad: OurContextMonad.hs
11+
ghc --make -w OurContextMonad.hs
1212

13-
SemanticChecker: SemanticChecker.hs
14-
ghc --make -w SemanticChecker.hs
13+
ContextChecker: ContextChecker.hs
14+
ghc --make -w ContextChecker.hs
1515

1616
AST: AST.hs
1717
ghc --make -w AST.hs

OurMonad.hs OurContextMonad.hs

+22-22
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
-- 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.
33
-- Augusto Hidalgo 13-10665
44
-- Genesis Kufatty 13-10708
55

6-
module OurMonad where
6+
module OurContextMonad where
77

88
import Control.Monad.Error
99
import Control.Monad.State
@@ -29,11 +29,11 @@ data Scope = Scope {getList::[(String, OurType)]}
2929

3030
data FuncSign = FuncSign {getId::String, getType:: OurType, getParamList::[(String,OurType)]}
3131

32-
data SymTable = SymTable {getScopes::[Scope], getFuncSigns::[FuncSign]}
32+
data ContextSymTable = ContextSymTable {getScopes::[Scope], getFuncSigns::[FuncSign]}
3333

34-
data OurState = OurState {getSymTable::SymTable, getReturnT::(Maybe OurType)}
34+
data OurContextState = OurContextState {getSymTable::ContextSymTable, getReturnT::(Maybe OurType)}
3535

36-
emptyState = OurState (SymTable [] []) Nothing
36+
emptyContextState = OurContextState (ContextSymTable [] []) Nothing
3737

3838
data OurLog = OurLog {getScopesLog::String, getWarningsLog::String}
3939

@@ -49,43 +49,43 @@ scopeToOurLog s = OurLog s ""
4949
warningToOurLog s = OurLog "" s
5050

5151

52-
type OurMonad a = StateT OurState (WriterT OurLog (Either OurError)) a
52+
type OurContextMonad a = StateT OurContextState (WriterT OurLog (Either OurError)) a
5353

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)
5656

57-
getLog f a = show $ snd $ getRight $ runOurMonad f a `catchError` (\(OurError pos s) -> error $ "\nError en linea "++show pos++":\n"++s)
57+
getLog f a = show $ snd $ getRight $ runOurContextMonad f a `catchError` (\(OurError pos s) -> error $ "\nError en linea "++show pos++":\n"++s)
5858
where
5959
getRight (Right x) = x
6060

6161

6262
lookInList :: String -> [(String, OurType)] -> Maybe OurType
6363
lookInList s l = snd <$> find ((==s).fst) l
6464

65-
lookInLastScope :: String -> OurMonad (Maybe OurType)
65+
lookInLastScope :: String -> OurContextMonad (Maybe OurType)
6666
lookInLastScope s = lookInList s.getList.head'.getScopes.getSymTable <$> get
6767
where head' [] = Scope []
6868
head' (a:as) = a
6969

70-
lookInSymTable :: String -> OurMonad (Maybe OurType)
70+
lookInSymTable :: String -> OurContextMonad (Maybe OurType)
7171
lookInSymTable s = msum . map (lookInList s) . (map getList).getScopes.getSymTable <$> get
7272

73-
newScope :: OurMonad ()
73+
newScope :: OurContextMonad ()
7474
newScope = do
7575
oldState <- get
7676
let oldSymTable = getSymTable oldState
7777
oldScopes = getScopes oldSymTable
7878
newSymTable = oldSymTable {getScopes = (Scope []):oldScopes}
7979
put $ oldState {getSymTable = newSymTable}
8080

81-
removeLastScope :: OurMonad ()
81+
removeLastScope :: OurContextMonad ()
8282
removeLastScope = do
8383
oldState <- get
8484
let oldSymTable = getSymTable oldState
8585
newSymTable = oldSymTable {getScopes = tail.getScopes $ oldSymTable }
8686
put $ oldState { getSymTable = newSymTable}
8787

88-
addToSymTable :: (String, OurType) -> OurMonad ()
88+
addToSymTable :: (String, OurType) -> OurContextMonad ()
8989
addToSymTable pair = do
9090
oldState <- get
9191
let oldSymTable = getSymTable oldState
@@ -95,15 +95,15 @@ addToSymTable pair = do
9595
newSymTable = oldSymTable { getScopes = newScopeList }
9696
put $ oldState { getSymTable = newSymTable }
9797

98-
addFunctionSign :: String -> [(String, OurType)] -> OurType -> OurMonad () -- No crea el scope
98+
addFunctionSign :: String -> [(String, OurType)] -> OurType -> OurContextMonad () -- No crea el scope
9999
addFunctionSign s params typ = do
100100
oldState <- get
101101
let newFunc = FuncSign s typ params
102102
oldSymTable = getSymTable oldState
103103
newSymTable = oldSymTable { getFuncSigns = newFunc:(getFuncSigns oldSymTable) }
104104
put $ oldState { getSymTable = newSymTable }
105105

106-
lookFunction :: String -> OurMonad Bool
106+
lookFunction :: String -> OurContextMonad Bool
107107
lookFunction s = do
108108
oldState <- get
109109
let funcsList = map (getId) (getFuncSigns.getSymTable $ oldState)
@@ -113,29 +113,29 @@ lookFunction s = do
113113
_ -> True
114114
return ans
115115

116-
getFunctionReturnType :: String -> OurMonad OurType
116+
getFunctionReturnType :: String -> OurContextMonad OurType
117117
getFunctionReturnType s = do
118118
oldState <- get
119119
let listFunc = getFuncSigns.getSymTable $ oldState
120120
func = filter ((==s).getId) listFunc
121121
return $ getType.head $ func
122122

123-
checkFunction :: String -> [OurType] -> OurMonad (Bool,Int)
123+
checkFunction :: String -> [OurType] -> OurContextMonad (Bool,Int)
124124
checkFunction s list = do
125125
oldState <- get
126126
let listF = getParamList $ head $ filter ((==s).getId) (getFuncSigns.getSymTable $ oldState)
127127
listType = map snd listF
128128
return (listType==list,length listType)
129129

130-
setReturnType :: Maybe OurType -> OurMonad ()
130+
setReturnType :: Maybe OurType -> OurContextMonad ()
131131
setReturnType typeR = do
132132
oldState <- get
133133
put $ oldState { getReturnT = typeR }
134134

135-
getReturnType :: OurMonad (Maybe OurType)
135+
getReturnType :: OurContextMonad (Maybe OurType)
136136
getReturnType = get >>= (return.getReturnT)
137137

138-
lastScopeToLog :: String -> OurMonad ()
138+
lastScopeToLog :: String -> OurContextMonad ()
139139
lastScopeToLog scopeName = do
140140
scopes <- getScopes.getSymTable <$> get
141141
let nested = length scopes
@@ -145,6 +145,6 @@ lastScopeToLog scopeName = do
145145
tell.scopeToOurLog $ concatMap (\s -> ident++"|> "++s++"\n" ) $ map showVarAndType $ reverse.getList $ lastScope
146146
where
147147
showVarAndType (s, t) = s ++" : "++ show t
148-
warningToLog :: String -> OurMonad ()
148+
warningToLog :: String -> OurContextMonad ()
149149
warningToLog warning = do
150150
tell.warningToOurLog $ warning++"\n"

retina.hs

+3-4
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,8 @@
66
import Lexer
77
import AST
88
import qualified Parser as P
9-
import SemanticChecker
10-
import OurMonad
9+
import ContextChecker
10+
import OurContextMonad
1111
import System.Environment
1212

1313
main = do
@@ -18,8 +18,7 @@ main = do
1818
putStrLn "Error lexicografico (alex isn't happy)"
1919
mapM_ printToken $ reverse $ tokenList ls
2020
else do
21-
--Imprimir AST
2221
--printConstrN 0 . (P.parse) . reverse . tokenList $ ls
23-
putStrLn $ getLog (checkConstrN $ (P.parse) . reverse . tokenList $ ls) emptyState
22+
putStrLn $ getLog (checkConstrN $ (P.parse) . reverse . tokenList $ ls) emptyContextState
2423

2524
Left e -> putStrLn e

0 commit comments

Comments
 (0)