Add enum AST types
This commit is contained in:
parent
f673ca48a9
commit
01398f48bf
6
.gitignore
vendored
Normal file
6
.gitignore
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
/build/
|
||||
.cache/
|
||||
CMakeFiles/
|
||||
CMakeCache.txt
|
||||
node_modules/
|
||||
/dist-newstyle/
|
@ -1,5 +1,6 @@
|
||||
module Language.Elna.AST
|
||||
( ConstantDefinition(..)
|
||||
, Declaration(..)
|
||||
, Expression(..)
|
||||
, Identifier(..)
|
||||
, Literal(..)
|
||||
@ -7,6 +8,7 @@ module Language.Elna.AST
|
||||
, Program(..)
|
||||
, Statement(..)
|
||||
, VariableDeclaration(..)
|
||||
, TypeDefinition(..)
|
||||
, TypeName(..)
|
||||
) where
|
||||
|
||||
@ -44,8 +46,12 @@ instance Show TypeName
|
||||
data Literal
|
||||
= StringLiteral Text
|
||||
| IntegerLiteral Int32
|
||||
| ByteLiteral Word8
|
||||
| CharacterLiteral Word8
|
||||
| BooleanLiteral Bool
|
||||
| RecordLiteral (NonEmpty Argument)
|
||||
| VariantLiteral (NonEmpty Argument)
|
||||
| EnumLiteral Identifier
|
||||
deriving Eq
|
||||
|
||||
instance Show Literal
|
||||
@ -53,11 +59,15 @@ instance Show Literal
|
||||
show (StringLiteral string) = Text.unpack
|
||||
$ "\"" <> string <> "\""
|
||||
show (IntegerLiteral integer) = show integer
|
||||
show (ByteLiteral word) = show word
|
||||
show (CharacterLiteral character) =
|
||||
'\'' : chr (fromEnum character) : ['\'']
|
||||
show (BooleanLiteral boolean)
|
||||
| boolean = "true"
|
||||
| otherwise = "false"
|
||||
show (RecordLiteral arguments) = showArguments arguments
|
||||
show (VariantLiteral arguments) = showArguments arguments
|
||||
show (EnumLiteral identifier) = show identifier
|
||||
|
||||
data Expression
|
||||
= VariableExpression Identifier
|
||||
@ -77,7 +87,7 @@ data Expression
|
||||
| LessOrEqualExpression Expression Expression
|
||||
| GreaterOrEqualExpression Expression Expression
|
||||
| IfExpression Expression Statement Statement
|
||||
| LoopExpression Expression Statement
|
||||
| LoopExpression Identifier Expression Statement
|
||||
| FieldExpression Expression Identifier
|
||||
deriving Eq
|
||||
|
||||
@ -101,11 +111,14 @@ instance Show Expression
|
||||
show (GreaterOrEqualExpression lhs rhs) = concat [show lhs, " >= ", show rhs]
|
||||
show (IfExpression condition if' else') = concat
|
||||
[ "if ", show condition
|
||||
, " then " <> show if'
|
||||
, " else " <> show else'
|
||||
, " then ", show if'
|
||||
, " else ", show else'
|
||||
]
|
||||
show (LoopExpression identifier accumulator iteration) = concat
|
||||
[ "loop ", show identifier
|
||||
, " := ", show accumulator
|
||||
, " do ", show iteration
|
||||
]
|
||||
show (LoopExpression accumulator iteration) = concat
|
||||
["loop ", show accumulator, " do ", show iteration]
|
||||
show (FieldExpression fieldExpression identifier) =
|
||||
show fieldExpression <> "." <> show identifier
|
||||
|
||||
@ -147,14 +160,22 @@ instance Show Parameter
|
||||
show (Parameter identifier typeName) =
|
||||
show identifier <> ": " <> show typeName
|
||||
|
||||
data Argument = Argument Identifier Literal
|
||||
deriving Eq
|
||||
|
||||
instance Show Argument
|
||||
where
|
||||
show (Argument identifier value) =
|
||||
concat [show identifier, ": ", show value]
|
||||
|
||||
data ProcedureDeclaration
|
||||
= ProcedureDeclaration Identifier [Parameter]
|
||||
= ExternProcedureDeclaration Identifier [Parameter]
|
||||
| ProcedureDefinition Identifier [Parameter] Bool [ConstantDefinition] Statement
|
||||
deriving Eq
|
||||
|
||||
instance Show ProcedureDeclaration
|
||||
where
|
||||
show (ProcedureDeclaration procedureName parameters) =
|
||||
show (ExternProcedureDeclaration procedureName parameters) =
|
||||
"proc " <> show procedureName <> showParameters parameters <> "; extern;"
|
||||
show (ProcedureDefinition procedureName parameters exports constants body)
|
||||
= "proc " <> show procedureName <> showParameters parameters <> ";"
|
||||
@ -163,13 +184,13 @@ instance Show ProcedureDeclaration
|
||||
<> show body <> ";"
|
||||
|
||||
data VariableDeclaration
|
||||
= VariableDeclaration Identifier TypeName
|
||||
= ExternVariableDeclaration Identifier TypeName
|
||||
| VariableDefinition Identifier TypeName (Maybe Literal) Bool
|
||||
deriving Eq
|
||||
|
||||
instance Show VariableDeclaration
|
||||
where
|
||||
show (VariableDeclaration identifier typeName)
|
||||
show (ExternVariableDeclaration identifier typeName)
|
||||
= show identifier <> ": " <> show typeName <> "; extern;"
|
||||
show (VariableDefinition identifier typeName initialValue exports)
|
||||
= show identifier <> ": " <> show typeName
|
||||
@ -179,6 +200,7 @@ instance Show VariableDeclaration
|
||||
data TypeDefinition
|
||||
= RecordDefinition Identifier (NonEmpty Parameter)
|
||||
| VariantDefinition Identifier (NonEmpty Parameter)
|
||||
| EnumerationDefinition Identifier (NonEmpty Identifier)
|
||||
deriving Eq
|
||||
|
||||
instance Show TypeDefinition
|
||||
@ -189,17 +211,44 @@ instance Show TypeDefinition
|
||||
show (VariantDefinition identifier fields) = show identifier
|
||||
<> " = variant " <> intercalate "; " (NonEmpty.toList $ show <$> fields)
|
||||
<> " end;"
|
||||
show (EnumerationDefinition identifier members) = show identifier <> " = ("
|
||||
<> intercalate ", " (NonEmpty.toList $ show <$> members) <> ");"
|
||||
|
||||
data Program =
|
||||
Program [TypeDefinition] [ConstantDefinition] [VariableDeclaration] [ProcedureDeclaration] Statement
|
||||
data Declaration
|
||||
= TypeDeclaration TypeDefinition
|
||||
| ConstantDeclaration ConstantDefinition
|
||||
| VariableDeclaration VariableDeclaration
|
||||
| ProcedureDeclaration ProcedureDeclaration
|
||||
deriving Eq
|
||||
|
||||
instance Show Declaration
|
||||
where
|
||||
show (TypeDeclaration typeDefinition) = show typeDefinition
|
||||
show (ConstantDeclaration constantDefinition) = show constantDefinition
|
||||
show (VariableDeclaration variableDeclaration) = show variableDeclaration
|
||||
show (ProcedureDeclaration procedureDeclaration) = show procedureDeclaration
|
||||
|
||||
data Program = Program [Declaration] Statement
|
||||
deriving Eq
|
||||
|
||||
instance Show Program
|
||||
where
|
||||
show (Program types constants globals procedures body)
|
||||
= unlines (show <$> types)
|
||||
<> showConstants constants <> showVariables globals
|
||||
<> unlines (show <$> procedures) <> show body <> "."
|
||||
show (Program declarations body) =
|
||||
let declarations' = foldr showDeclaration ("", []) declarations
|
||||
in unlines (snd declarations') <> show body <> "."
|
||||
where
|
||||
showDeclaration :: Declaration -> (String, [String]) -> (String, [String])
|
||||
showDeclaration (TypeDeclaration typeDeclaration) (previous, accumulator)
|
||||
| previous == "type" = ("type", show typeDeclaration : accumulator)
|
||||
| otherwise = ("type", "type " <> show typeDeclaration : accumulator)
|
||||
showDeclaration (ConstantDeclaration constantDeclaration) (previous, accumulator)
|
||||
| previous == "const" = ("const", show constantDeclaration : accumulator)
|
||||
| otherwise = ("const", "const " <> show constantDeclaration : accumulator)
|
||||
showDeclaration (VariableDeclaration variableDeclaration) (previous, accumulator)
|
||||
| previous == "var" = ("var", show variableDeclaration : accumulator)
|
||||
| otherwise = ("var", "var " <> show variableDeclaration : accumulator)
|
||||
showDeclaration (ProcedureDeclaration procedureDeclaration) (_previous, accumulator) =
|
||||
("proc", show procedureDeclaration : accumulator)
|
||||
|
||||
showAttributes :: Bool -> String
|
||||
showAttributes True = " export;"
|
||||
@ -209,12 +258,11 @@ showParameters :: [Parameter] -> String
|
||||
showParameters parameters =
|
||||
"(" <> intercalate ", " (show <$> parameters) <> ")"
|
||||
|
||||
showArguments :: NonEmpty Argument -> String
|
||||
showArguments arguments =
|
||||
"(" <> intercalate "; " (NonEmpty.toList $ show <$> arguments) <> ")"
|
||||
|
||||
showConstants :: [ConstantDefinition] -> String
|
||||
showConstants constants
|
||||
| null constants = ""
|
||||
| otherwise = " const " <> unwords (show <$> constants) <> "\n"
|
||||
|
||||
showVariables :: [VariableDeclaration] -> String
|
||||
showVariables variables
|
||||
| null variables = ""
|
||||
| otherwise = " var " <> unwords (show <$> variables) <> "\n"
|
||||
|
@ -34,4 +34,4 @@ endP = void $ symbol "end"
|
||||
|
||||
programP :: Parser Program
|
||||
programP = beginP >> endP >> symbol "."
|
||||
>> pure (Program mempty mempty mempty $ CompoundStatement mempty)
|
||||
>> pure (Program mempty $ CompoundStatement mempty)
|
||||
|
Loading…
Reference in New Issue
Block a user