elna/lib/Language/Elna/Frontend/AST.hs

207 lines
6.8 KiB
Haskell
Raw Normal View History

2024-10-02 22:56:15 +02:00
module Language.Elna.Frontend.AST
2024-09-15 23:03:25 +02:00
( Declaration(..)
2024-07-23 22:44:42 +02:00
, Identifier(..)
, Parameter(..)
2024-09-15 23:03:25 +02:00
, Program(..)
2024-07-23 22:44:42 +02:00
, Statement(..)
2024-09-15 23:03:25 +02:00
, TypeExpression(..)
2024-07-23 22:44:42 +02:00
, VariableDeclaration(..)
2024-11-06 22:23:49 +01:00
, VariableAccess(..)
2024-10-11 16:14:01 +02:00
, Condition(..)
2024-09-15 23:03:25 +02:00
, Expression(..)
2024-09-24 22:20:57 +02:00
, Literal(..)
2024-07-23 22:44:42 +02:00
) where
2024-10-04 18:26:10 +02:00
import Data.Char (chr)
2024-09-24 22:20:57 +02:00
import Data.Int (Int32)
2024-07-23 22:44:42 +02:00
import Data.List (intercalate)
import Data.Word (Word8)
2024-07-26 12:22:07 +02:00
import Language.Elna.Location (Identifier(..), showArrayType)
2024-10-04 18:26:10 +02:00
import Numeric (showHex)
import Data.Bifunctor (Bifunctor(bimap))
2024-09-15 23:03:25 +02:00
newtype Program = Program [Declaration]
deriving Eq
instance Show Program
where
show (Program declarations) = unlines (show <$> declarations)
data Declaration
= ProcedureDeclaration Identifier [Parameter] [VariableDeclaration] [Statement]
2024-10-17 00:37:42 +02:00
| TypeDefinition Identifier TypeExpression
2024-09-15 23:03:25 +02:00
deriving Eq
instance Show Declaration
where
2024-10-17 00:37:42 +02:00
show (TypeDefinition identifier typeExpression) =
concat ["type ", show identifier, " = ", show typeExpression, ";"]
2024-09-15 23:03:25 +02:00
show (ProcedureDeclaration procedureName parameters variables body)
= "proc " <> show procedureName <> showParameters parameters <> " {\n"
<> unlines ((" " <>) . show <$> variables)
<> unlines ((" " <>) . show <$> body)
<> "}"
data Parameter = Parameter Identifier TypeExpression Bool
deriving Eq
instance Show Parameter
where
show (Parameter identifier typeName ref) = concat
[ if ref then "ref " else ""
, show identifier, ": ", show typeName
]
showParameters :: [Parameter] -> String
showParameters parameters =
"(" <> intercalate ", " (show <$> parameters) <> ")"
2024-07-23 22:44:42 +02:00
data TypeExpression
= NamedType Identifier
| ArrayType Literal TypeExpression
2024-07-23 22:44:42 +02:00
deriving Eq
instance Show TypeExpression
where
show (NamedType typeName) = show typeName
show (ArrayType elementCount typeName) =
showArrayType elementCount typeName
2024-07-23 22:44:42 +02:00
2024-09-15 23:03:25 +02:00
data Statement
= EmptyStatement
| IfStatement Condition Statement (Maybe Statement)
2024-11-06 22:23:49 +01:00
| AssignmentStatement VariableAccess Expression
-- | WhileStatement Condition Statement
2024-10-04 18:26:10 +02:00
| CompoundStatement [Statement]
2024-09-24 22:20:57 +02:00
| CallStatement Identifier [Expression]
2024-09-15 23:03:25 +02:00
deriving Eq
instance Show Statement
where
show EmptyStatement = ";"
show (IfStatement condition if' else') = concat
[ "if (", show condition, ") "
, show if'
, maybe "" ((<> " else ") . show) else'
]
2024-11-06 22:23:49 +01:00
show (AssignmentStatement lhs rhs) =
2024-10-11 16:14:01 +02:00
concat [show lhs, " := ", show rhs, ";"]
2024-11-06 22:23:49 +01:00
{-show (WhileStatement expression statement) =
2024-10-04 18:26:10 +02:00
concat ["while (", show expression, ") ", show statement, ";"]-}
2024-09-15 23:03:25 +02:00
show (CompoundStatement statements) =
2024-10-04 18:26:10 +02:00
concat ["{\n", unlines (show <$> statements), " }"]
2024-09-15 23:03:25 +02:00
show (CallStatement name parameters) = show name <> "("
2024-09-24 22:20:57 +02:00
<> intercalate ", " (show <$> parameters) <> ")"
2024-09-15 23:03:25 +02:00
data VariableDeclaration =
VariableDeclaration Identifier TypeExpression
deriving Eq
2024-10-04 18:26:10 +02:00
data Literal
= DecimalLiteral Int32
2024-10-04 18:26:10 +02:00
| HexadecimalLiteral Int32
| CharacterLiteral Word8
2024-07-23 22:44:42 +02:00
deriving Eq
instance Show Literal
where
show (DecimalLiteral integer) = show integer
2024-10-04 18:26:10 +02:00
show (HexadecimalLiteral integer) = '0' : 'x' : showHex integer ""
2024-07-23 22:44:42 +02:00
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
2024-09-24 22:20:57 +02:00
instance Show VariableDeclaration
2024-08-15 20:13:56 +02:00
where
2024-09-24 22:20:57 +02:00
show (VariableDeclaration identifier typeExpression) =
concat ["var ", show identifier, ": " <> show typeExpression, ";"]
2024-08-15 20:13:56 +02:00
2024-09-29 19:50:55 +02:00
data Expression
2024-09-24 22:20:57 +02:00
= LiteralExpression Literal
2024-07-23 22:44:42 +02:00
| SumExpression Expression Expression
| SubtractionExpression Expression Expression
2024-09-29 19:50:55 +02:00
| NegationExpression Expression
2024-07-23 22:44:42 +02:00
| ProductExpression Expression Expression
2024-10-06 18:07:57 +02:00
| DivisionExpression Expression Expression
2024-11-06 22:23:49 +01:00
| VariableExpression VariableAccess
2024-07-23 22:44:42 +02:00
deriving Eq
instance Show Expression
where
show (LiteralExpression literal) = show literal
show (SumExpression lhs rhs) = concat [show lhs, " + ", show rhs]
show (SubtractionExpression lhs rhs) = concat [show lhs, " - ", show rhs]
2024-09-29 19:50:55 +02:00
show (NegationExpression negation) = '-' : show negation
2024-07-23 22:44:42 +02:00
show (ProductExpression lhs rhs) = concat [show lhs, " * ", show rhs]
2024-10-06 18:07:57 +02:00
show (DivisionExpression lhs rhs) = concat [show lhs, " / ", show rhs]
2024-11-06 22:23:49 +01:00
show (VariableExpression variable) = show variable
newtype VariableAccess
2024-09-24 22:20:57 +02:00
= VariableAccess Identifier
2024-11-06 22:23:49 +01:00
-- | ArrayAccess VariableAccess Expression
2024-09-24 22:20:57 +02:00
deriving Eq
instance Show VariableAccess
where
show (VariableAccess variableName) = show variableName
2024-11-06 22:23:49 +01:00
{- show (ArrayAccess arrayAccess elementIndex) =
concat [show arrayAccess, "[", show elementIndex, "]"] -}
2024-08-15 20:13:56 +02:00
data Condition
= EqualCondition Expression Expression
2024-10-13 12:59:47 +02:00
| NonEqualCondition Expression Expression
| LessCondition Expression Expression
| GreaterCondition Expression Expression
| LessOrEqualCondition Expression Expression
| GreaterOrEqualCondition Expression Expression
2024-08-15 20:13:56 +02:00
deriving Eq
instance Show Condition
where
show (EqualCondition lhs rhs) = concat [show lhs, " = ", show rhs]
2024-10-13 12:59:47 +02:00
show (NonEqualCondition lhs rhs) = concat [show lhs, " # ", show rhs]
show (LessCondition lhs rhs) = concat [show lhs, " < ", show rhs]
show (GreaterCondition lhs rhs) = concat [show lhs, " > ", show rhs]
show (LessOrEqualCondition lhs rhs) = concat [show lhs, " <= ", show rhs]
show (GreaterOrEqualCondition lhs rhs) = concat [show lhs, " >= ", show rhs]