module Fun.Tree where import Fun.Typer data Visibility = PublicVisibility | PrivateVisibility deriving Show -- TODO: Actually enforce danger-* in syntax-check data FunctionFlag = FunctionInline | FunctionDeprecated | FunctionDangerVoid | FunctionDangerAsm | FunctionUnknown deriving Show instance Read FunctionFlag where readsPrec _ "inline" = [(FunctionInline, "")] readsPrec _ "deprecated" = [(FunctionDeprecated, "")] readsPrec _ "danger-void" = [(FunctionDangerVoid, "")] readsPrec _ "danger-asm" = [(FunctionDangerAsm, "")] readsPrec _ _ = [(FunctionUnknown, "")] data Tree = Tree [Program] deriving Show data Program = Program [Block] deriving Show data Block = FunctionBlock { bDecl :: FunctionDeclaration , bDefns :: [FunctionDefinition] } -- | DataBlock .. TODO deriving Show type FunctionSignature = [Type] data FunctionDeclaration = FunctionDeclaration { dName :: String , dVisibility :: Visibility , dTypes :: FunctionSignature , dFlags :: [FunctionFlag] } deriving Show data FunctionDefinition = FunctionDefinition { dPattern :: FunctionPattern , dBody :: FunctionBody } deriving Show data FunctionPattern = FunctionPattern { pElements :: [FunctionPatternElement] } deriving Show data FunctionPatternElement = FunctionPatternParameter String | FunctionPatternString String | FunctionPatternNumber Integer | FunctionPatternWildcard | FunctionPatternSuperWildcard deriving (Show, Eq, Ord) data FunctionBody = FunctionBody { bElements :: [FunctionBodyElement] } deriving Show data FunctionBodyElement = Statement String | FunctionBodyIdentifier String | FunctionBodyParameter String | FunctionBodyString String | FunctionBodyNumber Integer deriving Show ---- -- TODO: This can be optimized getFunction :: Tree -> String -> FunctionSignature -> Maybe Block getFunction (Tree ps) f sig = let fromProgram (Program bs) = filter (\b -> (dName . bDecl) b == f && (dTypes . bDecl) b == sig) bs fromTree = filter (\b -> length b == 1) (map fromProgram ps) in case fromTree of [[f]] -> Just f _ -> Nothing