Require trailing semicolon for type declarations

This commit is contained in:
Eugen Wissner 2024-08-02 00:09:57 +03:00
parent d4471ca2fa
commit 5f8d9abe76
4 changed files with 13 additions and 9 deletions

View File

@ -51,7 +51,6 @@ declaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable
declaration globalTable (AST.TypeDefinition identifier typeExpression) declaration globalTable (AST.TypeDefinition identifier typeExpression)
= flip (SymbolTable.enter identifier) globalTable . TypeInfo = flip (SymbolTable.enter identifier) globalTable . TypeInfo
<$> withSymbolTable globalTable (dataType typeExpression) <$> withSymbolTable globalTable (dataType typeExpression)
declaration globalTable (AST.ProcedureDefinition identifier _parameters _variables _body) = declaration globalTable (AST.ProcedureDefinition identifier _parameters _variables _body) =
let localTable = SymbolTable.empty let localTable = SymbolTable.empty
in pure $ SymbolTable.enter identifier (ProcedureInfo localTable mempty) globalTable in pure $ SymbolTable.enter identifier (ProcedureInfo localTable mempty) globalTable

View File

@ -88,6 +88,7 @@ typeDefinitionP :: Parser Declaration
typeDefinitionP = TypeDefinition typeDefinitionP = TypeDefinition
<$> (symbol "type" *> identifierP) <$> (symbol "type" *> identifierP)
<*> (symbol "=" *> typeExpressionP) <*> (symbol "=" *> typeExpressionP)
<* semicolonP
<?> "type definition" <?> "type definition"
variableDeclarationP :: Parser VariableDeclaration variableDeclarationP :: Parser VariableDeclaration

View File

@ -4,7 +4,7 @@ module Language.Elna.NameAnalysisSpec
import Data.Text (Text) import Data.Text (Text)
import Text.Megaparsec (runParser) import Text.Megaparsec (runParser)
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy, pendingWith) import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
import Language.Elna.NameAnalysis (Error(..), nameAnalysis) import Language.Elna.NameAnalysis (Error(..), nameAnalysis)
import Language.Elna.SymbolTable (Info(..), SymbolTable) import Language.Elna.SymbolTable (Info(..), SymbolTable)
import qualified Language.Elna.SymbolTable as SymbolTable import qualified Language.Elna.SymbolTable as SymbolTable
@ -19,21 +19,21 @@ nameAnalysisOnText sourceText = nameAnalysis
spec :: Spec spec :: Spec
spec = describe "nameAnalysis" $ do spec = describe "nameAnalysis" $ do
it "adds type to the symbol table" $ do it "adds type to the symbol table" $ do
let given = "type A = int" let given = "type A = int;"
expected = Right $ Just $ TypeInfo intType expected = Right $ Just $ TypeInfo intType
actual <- nameAnalysisOnText given actual <- nameAnalysisOnText given
actual `shouldSatisfy` (expected ==) . fmap (SymbolTable.lookup "A") actual `shouldSatisfy` (expected ==) . fmap (SymbolTable.lookup "A")
it "errors when the aliased type is not defined" $ do it "errors when the aliased type is not defined" $ do
let given = "type A = B" let given = "type A = B;"
expected = Left $ UndefinedTypeError "B" expected = Left $ UndefinedTypeError "B"
actual <- nameAnalysisOnText given actual <- nameAnalysisOnText given
actual `shouldBe` expected actual `shouldBe` expected
it "errors if the aliased identifier is not a type" $ do it "errors if the aliased identifier is not a type" $ do
let given = "proc main() {} type A = main" let given = "proc main() {} type A = main;"
expected = Left expected = Left
$ UnexpectedTypeInfoError $ UnexpectedTypeInfoError
$ ProcedureInfo mempty mempty $ ProcedureInfo mempty mempty
@ -41,5 +41,9 @@ spec = describe "nameAnalysis" $ do
actual `shouldBe` expected actual `shouldBe` expected
it "replaces the alias with an equivalent base type" $ it "replaces the alias with an equivalent base type" $ do
pendingWith "Not implemented" let given = "type A = int; type B = A; type C = B;"
expected = Right $ Just $ TypeInfo intType
actual <- nameAnalysisOnText given
actual `shouldSatisfy` (expected ==) . fmap (SymbolTable.lookup "C")

View File

@ -25,12 +25,12 @@ spec =
it "parses type definition for a type starting like array" $ it "parses type definition for a type starting like array" $
let expected = Program [TypeDefinition "t" $ NamedType "arr"] let expected = Program [TypeDefinition "t" $ NamedType "arr"]
actual = parse programP "" "type t = arr" actual = parse programP "" "type t = arr;"
in actual `shouldParse` expected in actual `shouldParse` expected
it "parses array type definition" $ it "parses array type definition" $
let expected = Program [TypeDefinition "t" $ ArrayType 10 (NamedType "int")] let expected = Program [TypeDefinition "t" $ ArrayType 10 (NamedType "int")]
actual = parse programP "" "type t = array[10] of int" actual = parse programP "" "type t = array[10] of int;"
in actual `shouldParse` expected in actual `shouldParse` expected
it "parses parameters" $ it "parses parameters" $