1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-12 14:28:08 +03:00
juvix/test/Typecheck/Negative.hs

171 lines
5.1 KiB
Haskell
Raw Normal View History

module Typecheck.Negative where
import Base
import Juvix.Compiler.Builtins (iniState)
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Error
import Juvix.Compiler.Pipeline
type FailMsg = String
data NegTest = NegTest
2022-04-07 19:10:53 +03:00
{ _name :: String,
2022-12-20 15:05:40 +03:00
_relDir :: Path Rel Dir,
_file :: Path Rel File,
_checkErr :: TypeCheckerError -> Maybe FailMsg
2022-04-05 20:57:21 +03:00
}
Adds many new features (w.i.p v0.1.2) (#28) * add references to the syntax and cleanup code * [make] add .PHONY to Makefile targets * [parser] add parser / pretty for axiom backends * Pairing progress * [scoper] Add support for Axiom backends * [parser] Fix foreign block parsing * [ app ] adds --no-colors flag for the scope command * [ghc] upgrade to ghc 9.2.2 * use GHC2021 * [doc] Remove out-of-date comment * [test] Add ambiguity tests * [scoper] Improve resolution of local symbols * [error] WIP improving ambiguity error messages * [ clean-up ] new lab folder for experimentation * [ app ] ixes the lint warning * [ Termination ] removes Alga dependency * [error] Add message for ambiguous symbol error * [error] Add ambiguous module message * [scoper] Remove ErrGeneric * [test] Add test to suite * [test] show diff when ast's are different * [ lab ] folder organization * [ Makefile ] add targets with --watch option (stack cmds) and remove unused things * [ app ] add --version flag and fixed warnings and formatting * [test] remove fromRightIO to fix ambiguity error * [test] Add test of shadowing public open * [scoper] Add visibility annotation for Name * prepare buildIntoTable * [ Concrete ] add instance of hashable for refs. * add InfoTableBuilder effect * [ scoper ] add InfoTableBuilder effect * [ CHANGELOG ] updated v0.1.1 * [ README ] org version now * fix package.yaml * fix readme * [microjuvix] implement basic typechecker * add simple test for MicroJuvix type checker * fix checking for constructors apps in patterns * [scope] Move InfoTable to a new module * [abstract] Make Iden use references instead of Name * [abstract] Add InfoTable for abstract syntax * [scoper] Add function clauses to scoped InfoTable * [abstract] Add InfoTableBuilder for scoped to abstract * [main] Fix callsites of translateModule * [doc] Remove empty docs * [scoper] Update emptyInfoTable with missing field * rename some functions * [minihaskell] add compilation to MiniHaskell * [microjuvix] improve wrong type message * Add a validity predicate example written in MiniJuvix * [typecheck] Add error infrastructure for type errors Add a pretty error for mismatched constructor type in a pattern match * [test] Adds negative typecheck test for constructor * [app] Adds microjuvix subcommands for printing / typechecking * [typecheck] Add error message for ctor match args mistmatch * [typecheck] Add descriptive messages for remainng errors * [typecheck] Updates to error message copy * [typecheck] fix merge conflicts: * [highlight] add basic support for highlighting symbols * [minijuvix-mode] add minijuvix-mode and basic description in the readme * [readme] improve formatting * automatically detect the root of the project and add --show-root flag Co-authored-by: Jan Mas Rovira <janmasrovira@gmail.com> Co-authored-by: Paul Cadman <git@paulcadman.dev> Co-authored-by: Paul Cadman <pcadman@gmail.com>
2022-04-01 14:00:15 +03:00
testDescr :: NegTest -> TestDescr
2022-04-05 20:57:21 +03:00
testDescr NegTest {..} =
2022-12-20 15:05:40 +03:00
let tRoot = root <//> _relDir
file' = tRoot <//> _file
2022-04-07 19:10:53 +03:00
in TestDescr
{ _testName = _name,
_testRoot = tRoot,
_testAssertion = Single $ do
2022-12-20 15:05:40 +03:00
let entryPoint = defaultEntryPoint tRoot file'
result <- runIOEither iniState entryPoint upToInternalTyped
case mapLeft fromJuvixError result of
Left (Just tyError) -> whenJust (_checkErr tyError) assertFailure
2023-01-17 11:41:07 +03:00
Left Nothing -> assertFailure "An error ocurred but it was not in the type checker."
Right _ -> assertFailure "The type checker did not find an error."
2022-04-07 19:10:53 +03:00
}
allTests :: TestTree
2022-04-05 20:57:21 +03:00
allTests =
testGroup
"Typecheck negative tests"
[ testGroup
"General typechecking errors"
(map (mkTest . testDescr) tests),
testGroup
"Non-strictly positive data types"
(map (mkTest . testDescr) negPositivityTests)
]
2022-12-20 15:05:40 +03:00
root :: Path Abs Dir
root = relToProject $(mkRelDir "tests/negative")
wrongError :: Maybe FailMsg
wrongError = Just "Incorrect error"
tests :: [NegTest]
2022-04-05 20:57:21 +03:00
tests =
[ NegTest
"Constructor in pattern type error"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "PatternConstructor.juvix")
2022-04-05 20:57:21 +03:00
$ \case
ErrWrongConstructorType {} -> Nothing
2022-04-05 20:57:21 +03:00
_ -> wrongError,
NegTest
"Check pattern with hole type"
2022-12-20 15:05:40 +03:00
$(mkRelDir "265")
$(mkRelFile "M.juvix")
$ \case
ErrWrongConstructorType {} -> Nothing
_ -> wrongError,
2022-04-05 20:57:21 +03:00
NegTest
"Type vs inferred type mismatch"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "WrongType.juvix")
2022-04-05 20:57:21 +03:00
$ \case
ErrWrongType {} -> Nothing
2022-04-05 20:57:21 +03:00
_ -> wrongError,
NegTest
"Function application with non-function type"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "ExpectedFunctionType.juvix")
2022-04-05 20:57:21 +03:00
$ \case
ErrExpectedFunctionType {} -> Nothing
2022-04-05 20:57:21 +03:00
_ -> wrongError,
NegTest
"Unsolved hole"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "UnsolvedMeta.juvix")
$ \case
ErrUnsolvedMeta {} -> Nothing
_ -> wrongError,
2022-04-05 20:57:21 +03:00
NegTest
"Multiple type errors are captured"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "MultiWrongType.juvix")
2022-04-05 20:57:21 +03:00
$ \case
ErrWrongType {} -> Nothing
_ -> wrongError,
NegTest
"Unexpected braces in pattern"
2022-12-20 15:05:40 +03:00
$(mkRelDir "issue1337")
$(mkRelFile "Braces.juvix")
$ \case
ErrArity (ErrWrongPatternIsImplicit {}) -> Nothing
_ -> wrongError,
NegTest
"Wrong return type name for a constructor of a simple data type"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "WrongReturnType.juvix")
$ \case
ErrWrongReturnType {} -> Nothing
_ -> wrongError,
NegTest
"Too few arguments for the return type of a constructor"
2022-12-20 15:05:40 +03:00
$(mkRelDir "Internal")
$(mkRelFile "WrongReturnTypeTooFewArguments.juvix")
$ \case
ErrWrongType {} -> Nothing
_ -> wrongError,
2023-01-09 20:56:28 +03:00
NegTest
"Ambiguous hole"
$(mkRelDir "Internal")
$(mkRelFile "IdenFunctionArgsNoExplicit.juvix")
2023-01-17 15:28:38 +03:00
$ \case
ErrUnsolvedMeta {} -> Nothing
_ -> wrongError,
NegTest
"Cycle in hole"
$(mkRelDir "issue1700")
$(mkRelFile "SelfApplication.juvix")
2023-01-09 20:56:28 +03:00
$ \case
ErrUnsolvedMeta {} -> Nothing
2022-04-05 20:57:21 +03:00
_ -> wrongError
]
negPositivityTests :: [NegTest]
negPositivityTests =
2022-12-20 15:05:40 +03:00
[ NegTest "E1" $(mkRelDir "Internal/Positivity") $(mkRelFile "E1.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E2" $(mkRelDir "Internal/Positivity") $(mkRelFile "E2.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E3" $(mkRelDir "Internal/Positivity") $(mkRelFile "E3.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E4" $(mkRelDir "Internal/Positivity") $(mkRelFile "E4.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E5" $(mkRelDir "Internal/Positivity") $(mkRelFile "E5.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E6" $(mkRelDir "Internal/Positivity") $(mkRelFile "E6.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E7" $(mkRelDir "Internal/Positivity") $(mkRelFile "E7.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E8" $(mkRelDir "Internal/Positivity") $(mkRelFile "E8.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError,
2022-12-20 15:05:40 +03:00
NegTest "E9" $(mkRelDir "Internal/Positivity") $(mkRelFile "E9.juvix") $
\case
ErrNoPositivity {} -> Nothing
_ -> wrongError
]