diff options
author | Marvin Borner | 2022-03-03 21:40:07 +0100 |
---|---|---|
committer | Marvin Borner | 2022-03-03 21:40:26 +0100 |
commit | 6af1f804f0def7f48ae2d726951b13c895b85931 (patch) | |
tree | 617bcd70c9c2ec65fa2ffb525a88576113571a1a /src/Fun | |
parent | 8a3405146b918ef18a42aca1bcdac55a8c484c47 (diff) |
Syntax and typing start
Diffstat (limited to 'src/Fun')
-rw-r--r-- | src/Fun/Grammar.hs | 16 | ||||
-rw-r--r-- | src/Fun/Syntax.hs | 20 | ||||
-rw-r--r-- | src/Fun/Tree.hs | 8 | ||||
-rw-r--r-- | src/Fun/Typer.hs | 20 |
4 files changed, 49 insertions, 15 deletions
diff --git a/src/Fun/Grammar.hs b/src/Fun/Grammar.hs index 8014a20..7f6625d 100644 --- a/src/Fun/Grammar.hs +++ b/src/Fun/Grammar.hs @@ -2,6 +2,7 @@ module Fun.Grammar where import Fun.Parser import Fun.Tree +import Fun.Typer -- TODO: Multiple programs (= files) in tree tree :: Parser Tree @@ -11,14 +12,7 @@ program :: Parser Program program = iterFull block >>> Program <?> "program" block :: Parser Block -block = - functionBlock - <+-> newline - >>> Block - <|> functionBlock - <+-> endOfFile - >>> Block - <?> "block" +block = functionBlock <+-> newline <|> functionBlock <+-> endOfFile <?> "block" visibility :: Parser Visibility visibility = @@ -26,7 +20,7 @@ visibility = <|> (literal '-' >>> const PrivateVisibility) <?> "visibility" -functionBlock :: Parser FunctionBlock +functionBlock :: Parser Block functionBlock = functionDeclaration <+> iter functionDefinition >>> build where build (decl, defn) = FunctionBlock decl defn @@ -77,13 +71,13 @@ functionName = <?> "function name" where build (first, rest) = first : rest -functionTypes :: Parser [String] +functionTypes :: Parser [Type] functionTypes = iter (functionType <+-> space <+-> functionTypeDelimiter <+-> space) <+> functionType >>> build <?> "function types" - where build (a, b) = a ++ [b] + where build (a, b) = (map resolveType a) ++ [resolveType b] functionType :: Parser String functionType = diff --git a/src/Fun/Syntax.hs b/src/Fun/Syntax.hs new file mode 100644 index 0000000..ab17215 --- /dev/null +++ b/src/Fun/Syntax.hs @@ -0,0 +1,20 @@ +module Fun.Syntax where + +import Data.Either +import Fun.Tree + +data SyntaxError = SyntaxError String + +syntaxBlock :: Block -> Either [SyntaxError] Block +syntaxBlock (FunctionBlock decl defns) = Right $ FunctionBlock decl defns + +mergeSyntax :: [Either [SyntaxError] a] -> ([a] -> b) -> Either [SyntaxError] b +mergeSyntax d c = case any isLeft d of + True -> Left $ concat $ lefts d + False -> Right $ c $ rights d + +syntaxProgram :: Program -> Either [SyntaxError] Program +syntaxProgram (Program blocks) = mergeSyntax (map syntaxBlock blocks) Program + +syntaxTree :: Tree -> Either [SyntaxError] Tree +syntaxTree (Tree programs) = mergeSyntax (map syntaxProgram programs) Tree diff --git a/src/Fun/Tree.hs b/src/Fun/Tree.hs index 354677d..63ca0b5 100644 --- a/src/Fun/Tree.hs +++ b/src/Fun/Tree.hs @@ -1,14 +1,14 @@ module Fun.Tree where +import Fun.Typer + data Tree = Tree [Program] deriving Show data Program = Program [Block] deriving Show -data Block = Block FunctionBlock -- | Block DataBlock ... - deriving Show -data FunctionBlock = FunctionBlock FunctionDeclaration [FunctionDefinition] +data Block = FunctionBlock FunctionDeclaration [FunctionDefinition] -- | DataBlock .. TODO deriving Show data Visibility = PublicVisibility | PrivateVisibility @@ -16,7 +16,7 @@ data Visibility = PublicVisibility | PrivateVisibility data FunctionDeclaration = FunctionDeclaration String Visibility - [String] + [Type] [FunctionFlag] deriving Show data FunctionFlag = FunctionInline | FunctionDeprecated | FunctionUnknown diff --git a/src/Fun/Typer.hs b/src/Fun/Typer.hs new file mode 100644 index 0000000..def34a1 --- /dev/null +++ b/src/Fun/Typer.hs @@ -0,0 +1,20 @@ +module Fun.Typer where + +data Type = UnknownType | NormalType String + deriving Show +-- TODO: Struct (like 'data' with mutiple), Union (like 'data' with '|') + +-- TODO: Handle primary types as normal non-primary types? +sizeOfNormalType :: String -> Integer +sizeOfNormalType "Signed64" = 64 +sizeOfNormalType "Signed32" = 32 +sizeOfNormalType "Signed16" = 16 +sizeOfNormalType "Signed8" = 8 +sizeOfNormalType "Unsigned64" = 64 +sizeOfNormalType "Unsigned32" = 32 +sizeOfNormalType "Unsigned16" = 16 +sizeOfNormalType "Unsigned8" = 8 +sizeOfNormalType _ = 0 + +resolveType :: String -> Type +resolveType t = NormalType t |