{-# LANGUAGE PatternSynonyms #-}
module Graphics.Implicit.ExtOpenScad.Parser.Statement (parseProgram) where
import Prelude(Char, Either, String, ($), (*>), Bool(False, True), (<$>), (<*>), (.), (<$), flip, fmap, filter, not, pure)
import Data.Maybe(Maybe(Just, Nothing))
import Graphics.Implicit.ExtOpenScad.Definitions (Statement(DoNothing, NewModule, Include, If, ModuleCall, (:=)), Expr(LamE), StatementI(StatementI), Symbol(Symbol), SourcePosition)
import qualified Graphics.Implicit.ExtOpenScad.Definitions as GIED (Pattern(Name))
import Graphics.Implicit.ExtOpenScad.Parser.Util ((*<|>), patternMatcher, sourcePosition)
import Graphics.Implicit.ExtOpenScad.Parser.Expr (expr0)
import Graphics.Implicit.ExtOpenScad.Parser.Lexer (whiteSpace, matchFunction, matchInclude, matchUse, matchIf, matchElse, matchModule, matchTok, matchComma, matchSemi, surroundedBy, matchIdentifier)
import Text.Parsec (SourceName, (<?>), sepBy, oneOf, getPosition, parse, eof, ParseError, many, noneOf, option, between, char, optionMaybe)
import Text.Parsec.String (GenParser)
import Control.Applicative ((<*), (<|>))
import Data.Functor (($>))
pattern Name :: String -> GIED.Pattern
pattern Name n = GIED.Name (Symbol n)
data CompIdx = A1 | A2
parseProgram :: SourceName -> String -> Either ParseError [StatementI]
parseProgram = parse program where
program :: GenParser Char st [StatementI]
program = removeNoOps <$> (whiteSpace *> many (computation A1) <* eof)
computation :: CompIdx -> GenParser Char st StatementI
computation A1 =
computation A2
<|>
throwAway
computation A2 =
userModule
<|>
ifStatementI
<|>
userModuleDeclaration
<|>
( include
<|>
function
) <* matchSemi
*<|>
assignment <* matchSemi
suite :: GenParser Char st [StatementI]
suite = (
removeNoOps . (:[]) <$> computation A1
*<|>
removeNoOps <$> surroundedBy '{' (many (computation A1)) '}'
) <?> "suite"
statementI :: GenParser Char st (Statement StatementI) -> GenParser Char st StatementI
statementI p = StatementI <$> sourcePos <*> p
throwAway :: GenParser Char st StatementI
throwAway = statementI $ DoNothing <$ oneOf "%*" <* whiteSpace <* computation A2
include :: GenParser Char st StatementI
include = statementI p <?> "include/use"
where
p :: GenParser Char st (Statement StatementI)
p = flip Include
<$> (matchInclude $> True <|> matchUse $> False)
<*> between (char '<') (matchTok '>') (many $ noneOf "<> ")
assignment :: GenParser Char st StatementI
assignment = statementI p <?> "assignment"
where
p :: GenParser Char st (Statement StatementI)
p = (:=) <$> patternMatcher <* matchTok '=' <*> expr0
function :: GenParser Char st StatementI
function = statementI p <?> "function"
where
p :: GenParser Char st (Statement StatementI)
p = (:=) <$> lval <*> rval
lval :: GenParser Char st GIED.Pattern
lval = Name <$> (matchFunction *> matchIdentifier)
rval :: GenParser Char st Expr
rval = LamE <$> surroundedBy '(' (sepBy patternMatcher matchComma) ')' <*> (matchTok '=' *> expr0)
ifStatementI :: GenParser Char st StatementI
ifStatementI = statementI p <?> "if"
where
p :: GenParser Char st (Statement StatementI)
p = If <$> (matchIf *> surroundedBy '(' expr0 ')') <*> suite <*> option [] (matchElse *> suite)
userModule :: GenParser Char st StatementI
userModule = statementI p <?> "module call"
where
p :: GenParser Char st (Statement StatementI)
p = ModuleCall <$> fmap Symbol matchIdentifier <*> moduleArgsUnit <*> (suite *<|> (matchSemi $> []))
userModuleDeclaration :: GenParser Char st StatementI
userModuleDeclaration = statementI p <?> "module declaration"
where
p :: GenParser Char st (Statement StatementI)
p = NewModule <$> fmap Symbol (matchModule *> matchIdentifier) <*> moduleArgsUnitDecl <*> suite
moduleArgsUnit :: GenParser Char st [(Maybe Symbol, Expr)]
moduleArgsUnit =
surroundedBy '('
(sepBy (
do
symb <- matchIdentifier
expr <- matchTok '=' *> expr0
pure (Just (Symbol symb), expr)
*<|> do
symb <- matchIdentifier
argVars <- surroundedBy '(' (sepBy matchIdentifier matchComma) ')'
expr <- matchTok '=' *> expr0
pure (Just (Symbol symb), LamE (fmap Name argVars) expr)
*<|> do
expr <- expr0
pure (Nothing, expr)
) matchComma)
')'
moduleArgsUnitDecl :: GenParser Char st [(Symbol, Maybe Expr)]
moduleArgsUnitDecl =
surroundedBy '('
(sepBy (
do
symb <- matchIdentifier
expr <- optionMaybe (matchTok '=' *> expr0)
pure (Symbol symb, expr)
) matchComma)
')'
sourcePos :: GenParser Char st SourcePosition
sourcePos = sourcePosition <$> getPosition
isNoOp :: StatementI -> Bool
isNoOp (StatementI _ DoNothing) = True
isNoOp _ = False
removeNoOps :: [StatementI] -> [StatementI]
removeNoOps = filter $ not . isNoOp