Parse type declarations

This commit is contained in:
Eugen Wissner 2024-10-17 00:37:42 +02:00
parent 582040e5d3
commit bf5ec1f3e2
Signed by: belka
GPG Key ID: A27FDC1E8EE902C0
4 changed files with 21 additions and 13 deletions

View File

@ -28,13 +28,13 @@ instance Show Program
data Declaration data Declaration
= ProcedureDeclaration Identifier [Parameter] [VariableDeclaration] [Statement] = ProcedureDeclaration Identifier [Parameter] [VariableDeclaration] [Statement]
-- | TypeDefinition Identifier TypeExpression | TypeDefinition Identifier TypeExpression
deriving Eq deriving Eq
instance Show Declaration instance Show Declaration
where where
{- show (TypeDefinition identifier typeExpression) = show (TypeDefinition identifier typeExpression) =
concat ["type ", show identifier, " = ", show typeExpression, ";"] -} concat ["type ", show identifier, " = ", show typeExpression, ";"]
show (ProcedureDeclaration procedureName parameters variables body) show (ProcedureDeclaration procedureName parameters variables body)
= "proc " <> show procedureName <> showParameters parameters <> " {\n" = "proc " <> show procedureName <> showParameters parameters <> " {\n"
<> unlines ((" " <>) . show <$> variables) <> unlines ((" " <>) . show <$> variables)

View File

@ -71,12 +71,19 @@ program symbolTable (AST.Program declarations) = do
foldM declaration globalTable declarations foldM declaration globalTable declarations
procedureDeclaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable procedureDeclaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable
procedureDeclaration globalTable (AST.ProcedureDeclaration identifier parameters _ _) = do procedureDeclaration globalTable = \case
parametersInfo <- mapM (parameter globalTable) parameters (AST.ProcedureDeclaration identifier parameters _ _)
let procedureInfo = ProcedureInfo SymbolTable.empty -> mapM (parameter globalTable) parameters
$ Vector.fromList parametersInfo >>= enterOrFail identifier
. ProcedureInfo SymbolTable.empty
. Vector.fromList
(AST.TypeDefinition identifier typeExpression)
-> dataType globalTable typeExpression
>>= enterOrFail identifier . SymbolTable.TypeInfo
where
enterOrFail identifier declarationInfo =
maybe (NameAnalysis $ throwE $ IdentifierAlreadyDefinedError identifier) pure maybe (NameAnalysis $ throwE $ IdentifierAlreadyDefinedError identifier) pure
$ SymbolTable.enter identifier procedureInfo globalTable $ SymbolTable.enter identifier declarationInfo globalTable
declaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable declaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable
declaration globalTable (AST.ProcedureDeclaration identifier parameters variables body) = do declaration globalTable (AST.ProcedureDeclaration identifier parameters variables body) = do
@ -92,6 +99,7 @@ declaration globalTable (AST.ProcedureDeclaration identifier parameters variable
updater procedureTable (ProcedureInfo _ parameters') = Just updater procedureTable (ProcedureInfo _ parameters') = Just
$ ProcedureInfo procedureTable parameters' $ ProcedureInfo procedureTable parameters'
updater _ _ = Nothing updater _ _ = Nothing
declaration globalTable (AST.TypeDefinition _ _) = pure globalTable
parameterToVariableInfo :: SymbolTable -> AST.Parameter -> NameAnalysis (Identifier, Info) parameterToVariableInfo :: SymbolTable -> AST.Parameter -> NameAnalysis (Identifier, Info)
parameterToVariableInfo symbolTable (AST.Parameter identifier typeExpression isReferenceParameter') parameterToVariableInfo symbolTable (AST.Parameter identifier typeExpression isReferenceParameter')

View File

@ -52,14 +52,14 @@ literalP
where where
charP = fromIntegral . fromEnum charP = fromIntegral . fromEnum
<$> between (char '\'') (char '\'') Lexer.charLiteral <$> between (char '\'') (char '\'') Lexer.charLiteral
{-
typeDefinitionP :: Parser Declaration typeDefinitionP :: Parser Declaration
typeDefinitionP = TypeDefinition typeDefinitionP = TypeDefinition
<$> (symbol "type" *> identifierP) <$> (symbol "type" *> identifierP)
<*> (symbol "=" *> typeExpressionP) <*> (symbol "=" *> typeExpressionP)
<* semicolonP <* semicolonP
<?> "type definition" <?> "type definition"
-}
termP :: Parser Expression termP :: Parser Expression
termP = choice termP = choice
[ parensP expressionP [ parensP expressionP
@ -214,7 +214,7 @@ variableDeclarationP = VariableDeclaration
<?> "variable declaration" <?> "variable declaration"
declarationP :: Parser Declaration declarationP :: Parser Declaration
declarationP = procedureDeclarationP -- <|> typeDefinitionP declarationP = procedureDeclarationP <|> typeDefinitionP
programP :: Parser Program programP :: Parser Program
programP = Program <$> many declarationP <* eof programP = Program <$> many declarationP <* eof

View File

@ -70,7 +70,7 @@ declaration globalTable (AST.ProcedureDeclaration procedureName _ _ statements)
. flip Vector.snoc StopQuadruple . flip Vector.snoc StopQuadruple
. fold . fold
<$> traverse (statement globalTable) statements <$> traverse (statement globalTable) statements
-- declaration (AST.TypeDefinition _ _) accumulator = pure accumulator declaration _ (AST.TypeDefinition _ _) = pure Nothing
statement :: SymbolTable -> AST.Statement -> Glue (Vector (Quadruple Variable)) statement :: SymbolTable -> AST.Statement -> Glue (Vector (Quadruple Variable))
statement _ AST.EmptyStatement = pure mempty statement _ AST.EmptyStatement = pure mempty