module Language.While.Parser (loadFile, loadStdin) where
import Control.Applicative ((<$>), (<*))
import Control.Monad (liftM)
import Language.While.Types
import Text.Parsec
import Text.Parsec.Expr
import Text.Parsec.Indent
import Text.Parsec.Language (GenLanguageDef)
import Text.Parsec.String
import qualified Text.Parsec.Token as P
loadFile :: FilePath -> IO (Either String Stm)
loadFile path = parseString "Failed to parse file; " <$> readFile path
loadStdin :: IO (Either String Stm)
loadStdin = parseString "Failed to parse stdin; " <$> getContents
parseString errMsg input =
case parseResult of
Left err -> Left $ errMsg ++ show err
Right res -> Right res
where
parseResult = runIndent "" $ runParserT program () "" input
binaryOp name fun = Infix body
where
body = reservedOp name >> return fun
prefixOp name fun = Prefix $ reservedOp name >> return fun
program = do
whiteSpace
st <- semiSep consecutive
return $ foldr1 Scomp . concat $ st
consecutive = do
s1 <- statement
(s1:) <$> option [] (liftM return statement)
statement
= try stmAssignment
<|> try stmTryCatch
<|> try stmSkip
<|> try stmIf
<|> try stmWhile <* whiteSpace
<|> parens stmWhile <* whiteSpace
arithmeticAtom
= Numeral <$> integer
<|> Variable <$> identifier
<|> parens arithmeticExpr
arithmeticOperation =
[ [binaryOp "*" Amul AssocLeft]
, [binaryOp "+" Aadd AssocLeft, binaryOp "-" Asub AssocLeft , binaryOp "/" Adiv AssocLeft ]
]
arithmeticExpr = buildExpressionParser arithmeticOperation arithmeticAtom
data WrapAtom
= BexpW Bexp
| AexpW Aexp
booleanAtom
= (try (symbol "true") >> truthVal Btrue)
<|> (try (symbol "false") >> truthVal Bfalse)
<|> (try $ AexpW <$> arithmeticExpr)
<|> parens booleanExpr'
where truthVal = return . BexpW
booleanOperation =
[ [prefixOp "!" bneg]
, [binaryOp "=" beq AssocLeft
, binaryOp "<=" bleq AssocLeft
, binaryOp "^" band AssocLeft ]
]
where
bneg (BexpW b) = BexpW $ Bneg b
beq (AexpW a1) (AexpW a2) = BexpW $ Beq a1 a2
bleq (AexpW a1) (AexpW a2) = BexpW $ Bleq a1 a2
band (BexpW b1) (BexpW b2) = BexpW $ Band b1 b2
booleanExpr = do
result <- booleanExpr'
case result of
(BexpW val) -> return val
_ -> error "Parse error: failed to extract boolean"
booleanExpr' = buildExpressionParser booleanOperation booleanAtom
stmAssignment = do
var <- identifier
symbol ":="
expr <- arithmeticExpr
return $ Sass var expr
stmSkip = symbol "skip" >> return Sskip
stmIf = do
symbol "if"
check <- booleanExpr
symbol "then"
s1 <- program
symbol "else"
s2 <- program
return $ Sif check s1 s2
stmWhile = do
symbol "while"
check <- booleanExpr
symbol "do"
prog <- liftM (foldr1 Scomp) . block $ do
s <- statement
optional semi
return s
return $ Swhile check prog
stmTryCatch = do
symbol "try"
s1 <- program
symbol "catch"
s2 <- program
return $ Stry s1 s2
identifier = P.identifier whileLexer
integer = P.integer whileLexer
parens = P.parens whileLexer
reservedOp = P.reservedOp whileLexer
semi = P.semi whileLexer
symbol = P.symbol whileLexer
semiSep = P.semiSep whileLexer
whiteSpace = P.whiteSpace whileLexer
whileLexer = P.makeTokenParser whileStyle
whileStyle :: Monad m => GenLanguageDef String u m
whileStyle = P.LanguageDef
{ P.commentStart = ""
, P.commentEnd = ""
, P.commentLine = "#"
, P.nestedComments = True
, P.identStart = letter <|> char '_'
, P.identLetter = alphaNum <|> oneOf "_'"
, P.opStart = P.opLetter whileStyle
, P.opLetter = oneOf ":!#$%&*+./<=>?@\\^|-~"
, P.reservedOpNames= []
, P.reservedNames = []
, P.caseSensitive = True
}