summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorCamil Staps2018-02-07 15:27:17 +0100
committerCamil Staps2018-02-07 15:27:17 +0100
commite40d000153eabb3e957ecb485ad7a12dacf6115c (patch)
tree1138834456812d06dee665d0d391b2ff044e24f8
parentMerge branch 'master' of gitlab.science.ru.nl:cstaps/compiler-construction (diff)
Statement parsing
-rw-r--r--src/SPL/Lex.hs2
-rw-r--r--src/SPL/Parse.hs38
-rw-r--r--src/SPL/Syntax.hs1
3 files changed, 32 insertions, 9 deletions
diff --git a/src/SPL/Lex.hs b/src/SPL/Lex.hs
index 21b8a82..b8f09e3 100644
--- a/src/SPL/Lex.hs
+++ b/src/SPL/Lex.hs
@@ -30,6 +30,7 @@ data Token
| TArrow
| TIf
+ | TElse
| TWhile
| TReturn
| TVar
@@ -107,6 +108,7 @@ lex s = (comment s <|> item s <|> int s <|> char s <|> bool s <|> ident s) >>=
item :: (Alternative m) => String -> m (Token, String)
item ('i':'f':s) = noIdentifier TIf s
+ item ('e':'l':'s':'e':s) = noIdentifier TElse s
item ('w':'h':'i':'l':'e':s) = noIdentifier TWhile s
item ('r':'e':'t':'u':'r':'n':s) = noIdentifier TReturn s
item ('v':'a':'r':s) = noIdentifier TVar s
diff --git a/src/SPL/Parse.hs b/src/SPL/Parse.hs
index c05b755..4331ccb 100644
--- a/src/SPL/Parse.hs
+++ b/src/SPL/Parse.hs
@@ -3,12 +3,13 @@
module SPL.Parse (parse)
where
-import Text.Parsec (sepBy)
-import qualified Text.Parsec as P
-
import Control.Applicative
+import Control.Monad
import Data.Functor
+import Text.Parsec (sepBy, (<?>))
+import qualified Text.Parsec as P
+
import SPL.Syntax hiding (TInt,TBool,TChar,TArrow)
import qualified SPL.Syntax
import SPL.Lex
@@ -22,7 +23,7 @@ satisfy p = P.tokenPrim
(\t -> if p t then Just t else Nothing)
token :: Token -> Parser Token
-token = satisfy . (==)
+token t = satisfy (== t) <?> show t
check :: (Token -> Maybe a) -> Parser a
check f = P.tokenPrim
@@ -48,6 +49,12 @@ comment = toString <$> satisfy isCommentToken
toString (TSingleComment s) = s
toString (TBlockComment s) = s
+parenthesised :: Parser a -> Parser a
+parenthesised p = token TParenOpen *> p <* token TParenClose
+
+braced :: Parser a -> Parser a
+braced p = token TBraceOpen *> p <* token TBraceClose
+
var :: Parser Variable
var = do
t <- Just <$> plainType <|> (token TVar $> Nothing)
@@ -60,13 +67,11 @@ var = do
fun :: Parser Function
fun = do
id <- ident
- token TParenOpen
- args <- ident `sepBy` token TComma
- token TParenClose
+ args <- parenthesised $ ident `sepBy` token TComma
ftype <- optional (token TColonColon *> funType)
token TBraceOpen
vars <- many var
- stmt <- statement
+ stmt <- statements
token TBraceClose
return $ Function id ftype args vars stmt
@@ -95,5 +100,20 @@ expr = literal -- TODO
TBool b -> Just (LBool b)
_ -> Nothing
+statements :: Parser Statement
+statements = foldr1 Seq <$> some statement <|> pure Nop
+
statement :: Parser Statement
-statement = fail "" -- TODO
+statement =
+ liftM3 If
+ (token TIf *> parenthesised expr)
+ (braced statements)
+ (optional (token TElse *> braced statements)) <|>
+ liftM2 While
+ (token TWhile *> parenthesised expr)
+ (braced statements) <|>
+ liftM2 Assign
+ ident
+ (token TEquals *> expr <* token TSemicolon) <|>
+ Eval <$> (expr <* token TSemicolon) <|>
+ Return <$> (token TReturn *> optional expr <* token TSemicolon)
diff --git a/src/SPL/Syntax.hs b/src/SPL/Syntax.hs
index d274803..e40d47c 100644
--- a/src/SPL/Syntax.hs
+++ b/src/SPL/Syntax.hs
@@ -42,6 +42,7 @@ data Statement
| Eval Expression
| Return (Maybe Expression)
| Seq Statement Statement
+ | Nop
deriving (Show)
data Expression