Generate a call to _divide_by_zero_error on RiscV

This commit is contained in:
2024-10-30 14:12:51 +01:00
parent 6b92e5059c
commit 43882a3a06
11 changed files with 89 additions and 29 deletions

View File

@ -15,9 +15,10 @@ module Language.Elna.Frontend.AST
import Data.Char (chr)
import Data.Int (Int32)
import Data.List (intercalate)
import Data.Word (Word8, Word32)
import Data.Word (Word8)
import Language.Elna.Location (Identifier(..), showArrayType)
import Numeric (showHex)
import Data.Bifunctor (Bifunctor(bimap))
newtype Program = Program [Declaration]
deriving Eq
@ -57,13 +58,14 @@ showParameters parameters =
data TypeExpression
= NamedType Identifier
| ArrayType Word32 TypeExpression
| ArrayType Literal TypeExpression
deriving Eq
instance Show TypeExpression
where
show (NamedType typeName) = show typeName
show (ArrayType elementCount typeName) = showArrayType elementCount typeName
show (ArrayType elementCount typeName) =
showArrayType elementCount typeName
data Statement
= EmptyStatement
@ -96,18 +98,59 @@ data VariableDeclaration =
deriving Eq
data Literal
= IntegerLiteral Int32
= DecimalLiteral Int32
| HexadecimalLiteral Int32
| CharacterLiteral Word8
deriving Eq
instance Show Literal
where
show (IntegerLiteral integer) = show integer
show (DecimalLiteral integer) = show integer
show (HexadecimalLiteral integer) = '0' : 'x' : showHex integer ""
show (CharacterLiteral character) =
'\'' : chr (fromEnum character) : ['\'']
instance Ord Literal
where
compare x y = compare (int32Literal x) (int32Literal y)
instance Num Literal
where
x + y = DecimalLiteral $ int32Literal x + int32Literal y
x * y = DecimalLiteral $ int32Literal x * int32Literal y
abs (DecimalLiteral x) = DecimalLiteral $ abs x
abs (HexadecimalLiteral x) = HexadecimalLiteral $ abs x
abs (CharacterLiteral x) = CharacterLiteral $ abs x
negate (DecimalLiteral x) = DecimalLiteral $ negate x
negate (HexadecimalLiteral x) = HexadecimalLiteral $ negate x
negate (CharacterLiteral x) = CharacterLiteral $ negate x
signum (DecimalLiteral x) = DecimalLiteral $ signum x
signum (HexadecimalLiteral x) = HexadecimalLiteral $ signum x
signum (CharacterLiteral x) = CharacterLiteral $ signum x
fromInteger = DecimalLiteral . fromInteger
instance Real Literal
where
toRational (DecimalLiteral integer) = toRational integer
toRational (HexadecimalLiteral integer) = toRational integer
toRational (CharacterLiteral integer) = toRational integer
instance Enum Literal
where
toEnum = DecimalLiteral . fromIntegral
fromEnum = fromEnum . int32Literal
instance Integral Literal
where
toInteger = toInteger . int32Literal
quotRem x y = bimap DecimalLiteral DecimalLiteral
$ quotRem (int32Literal x) (int32Literal y)
int32Literal :: Literal -> Int32
int32Literal (DecimalLiteral integer) = integer
int32Literal (HexadecimalLiteral integer) = integer
int32Literal (CharacterLiteral integer) = fromIntegral integer
instance Show VariableDeclaration
where
show (VariableDeclaration identifier typeExpression) =

View File

@ -134,7 +134,7 @@ dataType environmentSymbolTable (AST.NamedType baseType) = do
| otherwise -> NameAnalysis $ throwE $ UnexpectedTypeInfoError baseInfo
_ -> NameAnalysis $ throwE $ UndefinedTypeError baseType
dataType environmentSymbolTable (AST.ArrayType arraySize baseType) =
dataType environmentSymbolTable baseType <&> ArrayType arraySize
dataType environmentSymbolTable baseType <&> ArrayType (fromIntegral arraySize)
checkSymbol :: SymbolTable -> Identifier -> NameAnalysis ()
checkSymbol globalTable identifier

View File

@ -46,8 +46,8 @@ type Parser = Parsec Void Text
literalP :: Parser Literal
literalP
= HexadecimalLiteral <$> (string "0x" *> lexeme Lexer.hexadecimal)
<|> IntegerLiteral <$> Lexer.signed space integerP
= HexadecimalLiteral <$> Lexer.signed space hexadecimalP
<|> DecimalLiteral <$> Lexer.signed space decimalP
<|> CharacterLiteral <$> lexeme charP
where
charP = fromIntegral . fromEnum
@ -141,8 +141,11 @@ commaP = void $ symbol ","
semicolonP :: Parser ()
semicolonP = void $ symbol ";"
integerP :: Integral a => Parser a
integerP = lexeme Lexer.decimal
decimalP :: Integral a => Parser a
decimalP = lexeme Lexer.decimal
hexadecimalP :: Integral a => Parser a
hexadecimalP = string "0x" *> lexeme Lexer.hexadecimal
identifierP :: Parser Identifier
identifierP =
@ -166,7 +169,7 @@ typeExpressionP = arrayTypeExpression
<?> "type expression"
where
arrayTypeExpression = ArrayType
<$> (symbol "array" *> bracketsP integerP)
<$> (symbol "array" *> bracketsP literalP)
<*> (symbol "of" *> typeExpressionP)
procedureDeclarationP :: Parser Declaration