@@ -2,5 +2,154 @@ module Parser where
22
33import Lexer
44import Text.Parsec.String (Parser )
5+ import Text.Parsec.Combinator
6+ import Text.Parsec.Char
7+ import Text.Parsec
8+ import AST
59
6- import AST
10+ -- literalParser :: Type -> Parser Literal
11+ -- literalParser IntC = do
12+ -- val <- integer
13+ -- return (IntLiteral val)
14+ -- literalParser StringC = do
15+ -- val <- stringLiteral
16+ -- return (StrLiteral val)
17+
18+ -- strP = literalParser StringC
19+
20+ -- topParser :: Parser Module
21+ -- topParser = commandParser <|> funcParser
22+
23+ -- commandParser :: Parser Module
24+ -- commandParser = do
25+ -- spaces
26+ -- exp <- exprParser
27+ -- char ';'
28+ -- spaces
29+ -- return $ Command exp
30+
31+ exprParser :: Parser Expr
32+ exprParser = literalStmtParser
33+ -- <|> funcCallParser
34+ -- <|> literalParser
35+ -- <|> parens exprParser
36+
37+ -- declStmtParser :: Parser Expr
38+ -- declStmtParser = do
39+ -- decl <- declParser
40+ -- return $ DeclarationStmt decl
41+
42+ -- declParser :: Parser Declaration
43+ -- declParser = externDeclParser <|> varDeclParser
44+
45+ -- externDeclParser :: Parser Declaration
46+ -- externDeclParser = do
47+ -- spaces
48+ -- string "extern"
49+ -- name <- nameParser
50+ -- argList <- argListParser
51+ -- ret <- typeParser
52+ -- spaces
53+ -- return $ ExternDecl name argList ret
54+
55+ -- varDeclParser :: Parser Declaration
56+ -- varDeclParser = do
57+ -- spaces
58+ -- type <- typeParser
59+ -- nameList <- vListParser
60+ -- spaces
61+ -- return $ VarDecl type nameList
62+
63+
64+ -- | Parsing type related stuffs. ----
65+ -- NSS
66+ typeParser :: Parser Type
67+ typeParser = intTParser <|> stringTParser
68+
69+ -- NSS
70+ intTParser = do
71+ reserved " int"
72+ spaces
73+ return IntC
74+
75+ -- NSS
76+ stringTParser = do
77+ reserved " string"
78+ spaces
79+ return StringC
80+ -------------------------------------
81+
82+ -- | Variable Names and identifier -----
83+ -- NSS
84+ nameParser :: Parser Name
85+ nameParser = ident
86+ ----------------------------------------
87+
88+ -- | VList: Name[, VList] -----------------
89+ -- NSS
90+ vListParser :: Parser VList
91+ vListParser = nameParser `sepBy1` (spaces >> (char ' ,' ) >> spaces)
92+ -------------------------------------------
93+
94+ -- ArgList : Type Name[, ArgList] ----------
95+ -- NSS
96+ argListParer :: Parser ArgList
97+ argListParer = unit `sepBy1` (spaces >> (char ' ,' ) >> spaces)
98+ where unit = do
99+ tp <- typeParser
100+ name <- nameParser
101+ return (tp, name)
102+ ---------------------------------------------
103+
104+ -- | Args : Expr[, Args]
105+ -- NSS
106+ argsParser :: Parser Args
107+ argsParser = exprParser `sepBy1` (spaces >> (char ' ,' ) >> spaces)
108+ -----------------------------------------------
109+
110+ -- delim :: Parser ()
111+ -- delim p = (spaces >> (char p) >> spaces)
112+
113+ ---------------------------------------------------
114+ -- | LiteralStmt : StrLiteral | IntLiteral
115+ -- NSS
116+ literalStmtParser :: Parser Expr
117+ literalStmtParser = do
118+ res <- literalParser
119+ return $ LiteralStmt res
120+ -- NSS
121+ literalParser :: Parser Literal
122+ literalParser = strLiteralP <|> intLiteralP
123+ -- NSS
124+ strLiteralP :: Parser Literal
125+ strLiteralP = do
126+ res <- stringLiteral
127+ return (StrLiteral res)
128+ -- NSS
129+ intLiteralP :: Parser Literal
130+ intLiteralP = do
131+ res <- integer
132+ return (IntLiteral res)
133+ -----------------------------------------------------
134+
135+ -- funcCallParser :: Parser
136+
137+ mainTest = do
138+ str <- getLine
139+ if str == " quit"
140+ then
141+ return ()
142+ else do
143+ print (parse argListParer " sdf" str)
144+ mainTest
145+
146+
147+
148+ -- --------------Done
149+ -- Type
150+ -- Literal
151+ -- Name
152+ -- VList
153+ -- ArgList
154+ -- Args
155+ -- LiteralStmt
0 commit comments