module Compiler.AST.FunctionDef where import Common import Control.Applicative import Data.List as L import Data.List.NonEmpty as NE import Data.Maybe import Data.Text as T import Compiler.AST.Common import Compiler.AST.FunctionStatement import Compiler.AST.Parser.Common import Compiler.Lexer import Parser.Lib import Test.Common data FunctionDef = FunctionDef Identifier [Identifier] (NonEmpty FunctionStatementWithLoc) deriving (Show, Eq) instance HasAstParser FunctionDef where astParser = nameParser "Function Definition" $ do surroundWs_ (parseKeyword KwProc) fnName <- surroundWs parseIdentifier args <- parseItemListInParen parseIdentifier stms <- mandatory (some (surroundWs (astParser @FunctionStatementWithLoc))) mandatory $ surroundWs_ $ parseKeyword KwEndProc pure $ FunctionDef fnName (fromMaybe [] (NE.toList <$> args)) (NE.fromList stms) instance ToSource FunctionDef where toSourcePretty i (FunctionDef name args stms) = T.concat $ [nlt, indent i, toSource KwProc, wst, toSource name, toSource DlParenOpen] <> (L.intersperse (toSource DlComma <> " ") (toSource <$> args)) <> [toSource DlParenClose] <> [nlt] <> [toSourcePretty (i+1) (NE.toList stms)] <> [nlt, indent i, toSource KwEndProc] instance HasGen FunctionDef where getGen = FunctionDef <$> getGen <*> getGen <*> (nonEmptyGen getGen)