Collect types into the global symbol table
This commit is contained in:
45
tests/Language/Elna/NameAnalysisSpec.hs
Normal file
45
tests/Language/Elna/NameAnalysisSpec.hs
Normal file
@ -0,0 +1,45 @@
|
||||
module Language.Elna.NameAnalysisSpec
|
||||
( spec
|
||||
) where
|
||||
|
||||
import Data.Text (Text)
|
||||
import Text.Megaparsec (runParser)
|
||||
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy, pendingWith)
|
||||
import Language.Elna.NameAnalysis (Error(..), nameAnalysis)
|
||||
import Language.Elna.SymbolTable (Info(..), SymbolTable)
|
||||
import qualified Language.Elna.SymbolTable as SymbolTable
|
||||
import qualified Language.Elna.Parser as AST
|
||||
import Language.Elna.Types (intType)
|
||||
import Control.Exception (throwIO)
|
||||
|
||||
nameAnalysisOnText :: Text -> IO (Either Error SymbolTable)
|
||||
nameAnalysisOnText sourceText = nameAnalysis
|
||||
<$> either throwIO pure (runParser AST.programP "" sourceText)
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "nameAnalysis" $ do
|
||||
it "adds type to the symbol table" $ do
|
||||
let given = "type A = int"
|
||||
expected = Right $ Just $ TypeInfo intType
|
||||
actual <- nameAnalysisOnText given
|
||||
|
||||
actual `shouldSatisfy` (expected ==) . fmap (SymbolTable.lookup "A")
|
||||
|
||||
it "errors when the aliased type is not defined" $ do
|
||||
let given = "type A = B"
|
||||
expected = Left $ UndefinedTypeError "B"
|
||||
actual <- nameAnalysisOnText given
|
||||
|
||||
actual `shouldBe` expected
|
||||
|
||||
it "errors if the aliased identifier is not a type" $ do
|
||||
let given = "proc main() {} type A = main"
|
||||
expected = Left
|
||||
$ UnexpectedTypeInfoError
|
||||
$ ProcedureInfo mempty mempty
|
||||
actual <- nameAnalysisOnText given
|
||||
|
||||
actual `shouldBe` expected
|
||||
|
||||
it "replaces the alias with an equivalent base type" $
|
||||
pendingWith "Not implemented"
|
Reference in New Issue
Block a user