Add printc and exit builtin functions

This commit is contained in:
2024-10-04 18:26:10 +02:00
parent fdf56ce9d0
commit 35742aa525
20 changed files with 139 additions and 53 deletions

View File

@ -12,10 +12,12 @@ module Language.Elna.Frontend.AST
, Literal(..)
) where
import Data.Char (chr)
import Data.Int (Int32)
import Data.List (intercalate)
import Data.Word ({-Word16, -}Word32)
import Data.Word (Word8, Word32)
import Language.Elna.Location (Identifier(..), showArrayType)
import Numeric (showHex)
newtype Program = Program [Declaration]
deriving Eq
@ -67,8 +69,8 @@ data Statement
= EmptyStatement
{-| AssignmentStatement VariableAccess Expression
| IfStatement Condition Statement (Maybe Statement)
| WhileStatement Condition Statement
| CompoundStatement [Statement]-}
| WhileStatement Condition Statement -}
| CompoundStatement [Statement]
| CallStatement Identifier [Expression]
deriving Eq
@ -83,9 +85,9 @@ instance Show Statement
, maybe "" ((<> " else ") . show) else'
]
show (WhileStatement expression statement) =
concat ["while (", show expression, ") ", show statement, ";"]
concat ["while (", show expression, ") ", show statement, ";"]-}
show (CompoundStatement statements) =
concat ["{\n", unlines (show <$> statements), " }"]-}
concat ["{\n", unlines (show <$> statements), " }"]
show (CallStatement name parameters) = show name <> "("
<> intercalate ", " (show <$> parameters) <> ")"
@ -93,22 +95,18 @@ data VariableDeclaration =
VariableDeclaration Identifier TypeExpression
deriving Eq
newtype Literal
data Literal
= IntegerLiteral Int32
{- | HexadecimalLiteral Int32
| CharacterLiteral Word16
| BooleanLiteral Bool -}
| HexadecimalLiteral Int32
| CharacterLiteral Word8
deriving Eq
instance Show Literal
where
show (IntegerLiteral integer) = show integer
{- show (HexadecimalLiteral integer) = '0' : 'x' : showHex integer ""
show (HexadecimalLiteral integer) = '0' : 'x' : showHex integer ""
show (CharacterLiteral character) =
'\'' : chr (fromEnum character) : ['\'']
show (BooleanLiteral boolean)
| boolean = "true"
| otherwise = "false" -}
instance Show VariableDeclaration
where
@ -120,8 +118,8 @@ data Expression
| SumExpression Expression Expression
| SubtractionExpression Expression Expression
| NegationExpression Expression
{- | VariableExpression VariableAccess
| ProductExpression Expression Expression
{- | VariableExpression VariableAccess
| DivisionExpression Expression Expression -}
deriving Eq
@ -131,13 +129,10 @@ instance Show Expression
show (SumExpression lhs rhs) = concat [show lhs, " + ", show rhs]
show (SubtractionExpression lhs rhs) = concat [show lhs, " - ", show rhs]
show (NegationExpression negation) = '-' : show negation
{- show (VariableExpression variable) = show variable
show (ProductExpression lhs rhs) = concat [show lhs, " * ", show rhs]
{- show (VariableExpression variable) = show variable
show (DivisionExpression lhs rhs) = concat [show lhs, " / ", show rhs] -}
{-
import Data.Char (chr)
import Numeric (showHex)
data VariableAccess
= VariableAccess Identifier
| ArrayAccess VariableAccess Expression

View File

@ -144,11 +144,11 @@ expression globalTable (AST.SubtractionExpression lhs rhs)
>> expression globalTable rhs
expression globalTable (AST.NegationExpression negation) =
expression globalTable negation
{- expression globalTable (AST.VariableExpression variableExpression) =
variableAccess globalTable variableExpression
expression globalTable (AST.ProductExpression lhs rhs)
= expression globalTable lhs
>> expression globalTable rhs
{- expression globalTable (AST.VariableExpression variableExpression) =
variableAccess globalTable variableExpression
expression globalTable (AST.DivisionExpression lhs rhs)
= expression globalTable lhs
>> expression globalTable rhs
@ -158,6 +158,8 @@ statement _ AST.EmptyStatement = pure ()
statement globalTable (AST.CallStatement name arguments)
= checkSymbol globalTable name
>> traverse_ (expression globalTable) arguments
statement globalTable (AST.CompoundStatement statements) =
traverse_ (statement globalTable) statements
{- statement globalTable (AST.AssignmentStatement lvalue rvalue)
= variableAccess globalTable lvalue
>> expression globalTable rvalue
@ -168,8 +170,6 @@ statement globalTable (AST.IfStatement ifCondition ifStatement elseStatement)
statement globalTable (AST.WhileStatement whileCondition loop)
= condition globalTable whileCondition
>> statement globalTable loop
statement globalTable (AST.CompoundStatement statements) =
traverse_ (statement globalTable) statements
variableAccess :: SymbolTable -> AST.VariableAccess -> NameAnalysis ()
variableAccess globalTable (AST.ArrayAccess arrayExpression indexExpression)

View File

@ -34,27 +34,24 @@ import Text.Megaparsec
import qualified Text.Megaparsec.Char.Lexer as Lexer
import Text.Megaparsec.Char
( alphaNumChar
-- , char
, char
, letterChar
, space1
-- , string
, string
)
import Control.Applicative (Alternative(..))
import Data.Maybe (isJust)
-- import Data.Functor (($>))
type Parser = Parsec Void Text
literalP :: Parser Literal
literalP
= {- HexadecimalLiteral <$> (string "0x" *> lexeme Lexer.hexadecimal)
<|> -} IntegerLiteral <$> Lexer.signed space integerP
{- <|> CharacterLiteral <$> lexeme charP
<|> BooleanLiteral <$> (symbol "true" $> True)
<|> BooleanLiteral <$> (symbol "false" $> False)
= HexadecimalLiteral <$> (string "0x" *> lexeme Lexer.hexadecimal)
<|> IntegerLiteral <$> Lexer.signed space integerP
<|> CharacterLiteral <$> lexeme charP
where
charP = fromIntegral . fromEnum
<$> between (char '\'') (char '\'') Lexer.charLiteral -}
<$> between (char '\'') (char '\'') Lexer.charLiteral
{-
typeDefinitionP :: Parser Declaration
typeDefinitionP = TypeDefinition
@ -73,7 +70,7 @@ termP = choice
operatorTable :: [[Operator Parser Expression]]
operatorTable =
[ unaryOperator
-- , factorOperator
, factorOperator
, termOperator
]
where
@ -81,10 +78,10 @@ operatorTable =
[ prefix "-" NegationExpression
, prefix "+" id
]
{- factorOperator =
factorOperator =
[ binary "*" ProductExpression
, binary "/" DivisionExpression
] -}
-- , binary "/" DivisionExpression
]
termOperator =
[ binary "+" SumExpression
, binary "-" SubtractionExpression

View File

@ -40,9 +40,22 @@ scope parent (SymbolTable _ mappings) = SymbolTable (Just parent) mappings
builtInSymbolTable :: SymbolTable
builtInSymbolTable = SymbolTable Nothing $ HashMap.fromList
[ ("printi", ProcedureInfo empty Vector.empty)
[ ("printi", ProcedureInfo empty (Vector.singleton printiX))
, ("printc", ProcedureInfo empty (Vector.singleton printcI))
, ("exit", ProcedureInfo empty Vector.empty)
, ("int", TypeInfo intType)
]
where
printiX = ParameterInfo
{ name = "x"
, type' = intType
, isReferenceParameter = False
}
printcI = ParameterInfo
{ name = "i"
, type' = intType
, isReferenceParameter = False
}
toMap :: SymbolTable -> HashMap Identifier Info
toMap (SymbolTable _ map') = map'