1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-27 09:32:18 +03:00
juvix/test/Typecheck/Negative.hs

289 lines
8.4 KiB
Haskell
Raw Normal View History

module Typecheck.Negative where
import Base
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Error
Run test suite in parallel (#2507) ## Overview This PR makes the compiler pipeline thread-safe so that the test suite can be run in parallel. This is achieved by: * Removing use of `{get, set, with}CurrentDir` functions. * Adding locking around shared file resources like the the global-project and internal build directory. NB: **Locking is disabled for the main compiler target**, as it is single threaded they are not required. ## Run test suite in parallel To run the test suite in parallel you must add `--ta '+RTS -N -RTS'` to your stack test arguments. For example: ``` stack test --fast --ta '+RTS -N -RTS' ``` The `-N` instructs the Haskell runtime to choose the number of threads to use based on how many processors there are on your machine. You can use `-Nn` to see the number of threads to `n`. These flags are already [set in the Makefile](https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/Makefile#L26) when you or CI uses `stack test`. ## Locking The Haskell package [filelock](https://hackage.haskell.org/package/filelock) is used for locking. File locks are used instead of MVars because Juvix code does not control when new threads are created, they are created by the test suite. This means that MVars created by Juvix code will have no effect, because they are created independently on each test-suite thread. Additionally the resources we're locking live on the filesystem and so can be conveniently tagged by path. ### FileLock The filelock library is wrapped in a FileLock effect: https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/FileLock/Base.hs#L6-L8 There is an [IO interpreter](https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/FileLock/IO.hs#L8) that uses filelock and an [no-op interpreter](https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/FileLock/Permissive.hs#L7) that just runs actions unconditionally. ### TaggedLock To make the file locks simpler to use a TaggedLock effect is introduced: https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/TaggedLock/Base.hs#L5-L11 And convenience function: https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/TaggedLock.hs#L28 This allows an action to be locked, tagged by a directory that may or may not exist. For example in the following code, an action is performed on a directory `root` that may delete the directory before repopulating the files. So the lockfile cannot be stored in the `root` itself. https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Extra/Files.hs#L55-L60 ## Pipeline As noted above, we only use locking in the test suite. The main app target pipeline is single threaded and so locking is unnecessary. So the interpretation of locks is parameterised so that locking can be disabled https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Compiler/Pipeline/Run.hs#L64
2023-11-16 18:19:52 +03:00
import Juvix.Data.Effect.TaggedLock
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
Run test suite in parallel (#2507) ## Overview This PR makes the compiler pipeline thread-safe so that the test suite can be run in parallel. This is achieved by: * Removing use of `{get, set, with}CurrentDir` functions. * Adding locking around shared file resources like the the global-project and internal build directory. NB: **Locking is disabled for the main compiler target**, as it is single threaded they are not required. ## Run test suite in parallel To run the test suite in parallel you must add `--ta '+RTS -N -RTS'` to your stack test arguments. For example: ``` stack test --fast --ta '+RTS -N -RTS' ``` The `-N` instructs the Haskell runtime to choose the number of threads to use based on how many processors there are on your machine. You can use `-Nn` to see the number of threads to `n`. These flags are already [set in the Makefile](https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/Makefile#L26) when you or CI uses `stack test`. ## Locking The Haskell package [filelock](https://hackage.haskell.org/package/filelock) is used for locking. File locks are used instead of MVars because Juvix code does not control when new threads are created, they are created by the test suite. This means that MVars created by Juvix code will have no effect, because they are created independently on each test-suite thread. Additionally the resources we're locking live on the filesystem and so can be conveniently tagged by path. ### FileLock The filelock library is wrapped in a FileLock effect: https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/FileLock/Base.hs#L6-L8 There is an [IO interpreter](https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/FileLock/IO.hs#L8) that uses filelock and an [no-op interpreter](https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/FileLock/Permissive.hs#L7) that just runs actions unconditionally. ### TaggedLock To make the file locks simpler to use a TaggedLock effect is introduced: https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/TaggedLock/Base.hs#L5-L11 And convenience function: https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Data/Effect/TaggedLock.hs#L28 This allows an action to be locked, tagged by a directory that may or may not exist. For example in the following code, an action is performed on a directory `root` that may delete the directory before repopulating the files. So the lockfile cannot be stored in the `root` itself. https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Extra/Files.hs#L55-L60 ## Pipeline As noted above, we only use locking in the test suite. The main app target pipeline is single threaded and so locking is unnecessary. So the interpretation of locks is parameterised so that locking can be disabled https://github.com/anoma/juvix/blob/e6dca22cfdcff936add5e7134f9c6f20416504a5/src/Juvix/Compiler/Pipeline/Run.hs#L64
2023-11-16 18:19:52 +03:00
entryPoint <- defaultEntryPointIO' LockModeExclusive tRoot file'
result <- runIOEither' LockModeExclusive 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
"Unexpected double braces in pattern"
$(mkRelDir "issue1337")
$(mkRelFile "DoubleBraces.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
Add builtin integer type to the surface language (#1948) This PR adds a builtin integer type to the surface language that is compiled to the backend integer type. ## Inductive definition The `Int` type is defined in the standard library as: ``` builtin int type Int := | --- ofNat n represents the integer n ofNat : Nat -> Int | --- negSuc n represents the integer -(n + 1) negSuc : Nat -> Int; ``` ## New builtin functions defined in the standard library ``` intToString : Int -> String; + : Int -> Int -> Int; neg : Int -> Int; * : Int -> Int -> Int; - : Int -> Int -> Int; div : Int -> Int -> Int; mod : Int -> Int -> Int; == : Int -> Int -> Bool; <= : Int -> Int -> Bool; < : Int -> Int -> Bool; ``` Additional builtins required in the definition of the other builtins: ``` negNat : Nat -> Int; intSubNat : Nat -> Nat -> Int; nonNeg : Int -> Bool; ``` ## REPL types of literals In the REPL, non-negative integer literals have the inferred type `Nat`, negative integer literals have the inferred type `Int`. ``` Stdlib.Prelude> :t 1 Nat Stdlib.Prelude> :t -1 Int :t let x : Int := 1 in x Int ``` ## The standard library Prelude The definitions of `*`, `+`, `div` and `mod` are not exported from the standard library prelude as these would conflict with the definitions from `Stdlib.Data.Nat`. Stdlib.Prelude ``` open import Stdlib.Data.Int hiding {+;*;div;mod} public; ``` * Closes https://github.com/anoma/juvix/issues/1679 * Closes https://github.com/anoma/juvix/issues/1984 --------- Co-authored-by: Lukasz Czajka <lukasz@heliax.dev>
2023-04-13 10:16:49 +03:00
_ -> wrongError,
NegTest
"Negative integer literal cannot be used as a Nat"
$(mkRelDir "Internal")
$(mkRelFile "LiteralInteger.juvix")
$ \case
ErrNoInstance {} -> Nothing
Add builtin integer type to the surface language (#1948) This PR adds a builtin integer type to the surface language that is compiled to the backend integer type. ## Inductive definition The `Int` type is defined in the standard library as: ``` builtin int type Int := | --- ofNat n represents the integer n ofNat : Nat -> Int | --- negSuc n represents the integer -(n + 1) negSuc : Nat -> Int; ``` ## New builtin functions defined in the standard library ``` intToString : Int -> String; + : Int -> Int -> Int; neg : Int -> Int; * : Int -> Int -> Int; - : Int -> Int -> Int; div : Int -> Int -> Int; mod : Int -> Int -> Int; == : Int -> Int -> Bool; <= : Int -> Int -> Bool; < : Int -> Int -> Bool; ``` Additional builtins required in the definition of the other builtins: ``` negNat : Nat -> Int; intSubNat : Nat -> Nat -> Int; nonNeg : Int -> Bool; ``` ## REPL types of literals In the REPL, non-negative integer literals have the inferred type `Nat`, negative integer literals have the inferred type `Int`. ``` Stdlib.Prelude> :t 1 Nat Stdlib.Prelude> :t -1 Int :t let x : Int := 1 in x Int ``` ## The standard library Prelude The definitions of `*`, `+`, `div` and `mod` are not exported from the standard library prelude as these would conflict with the definitions from `Stdlib.Data.Nat`. Stdlib.Prelude ``` open import Stdlib.Data.Int hiding {+;*;div;mod} public; ``` * Closes https://github.com/anoma/juvix/issues/1679 * Closes https://github.com/anoma/juvix/issues/1984 --------- Co-authored-by: Lukasz Czajka <lukasz@heliax.dev>
2023-04-13 10:16:49 +03:00
_ -> wrongError,
NegTest
"Integer literal cannot be used as a String"
$(mkRelDir "Internal")
$(mkRelFile "LiteralIntegerString.juvix")
$ \case
ErrNoInstance {} -> Nothing
_ -> wrongError,
NegTest
"Unsupported type function"
$(mkRelDir "Internal")
$(mkRelFile "UnsupportedTypeFunction.juvix")
$ \case
ErrUnsupportedTypeFunction {} -> Nothing
Traits (#2320) * Closes #1646 Implements a basic trait framework. A simple instance search mechanism is included which fails if there is more than one matching instance at any step. Example usage: ``` import Stdlib.Prelude open hiding {Show; mkShow; show}; trait type Show A := mkShow { show : A → String }; instance showStringI : Show String := mkShow (show := id); instance showBoolI : Show Bool := mkShow (show := λ{x := if x "true" "false"}); instance showNatI : Show Nat := mkShow (show := natToString); showList {A} : {{Show A}} → List A → String | nil := "nil" | (h :: t) := Show.show h ++str " :: " ++str showList t; instance showListI {A} {{Show A}} : Show (List A) := mkShow (show := showList); showMaybe {A} {{Show A}} : Maybe A → String | (just x) := "just (" ++str Show.show x ++str ")" | nothing := "nothing"; instance showMaybeI {A} {{Show A}} : Show (Maybe A) := mkShow (show := showMaybe); main : IO := printStringLn (Show.show true) >> printStringLn (Show.show false) >> printStringLn (Show.show 3) >> printStringLn (Show.show [true; false]) >> printStringLn (Show.show [1; 2; 3]) >> printStringLn (Show.show [1; 2]) >> printStringLn (Show.show [true; false]) >> printStringLn (Show.show [just true; nothing; just false]) >> printStringLn (Show.show [just [1]; nothing; just [2; 3]]) >> printStringLn (Show.show "abba") >> printStringLn (Show.show ["a"; "b"; "c"; "d"]); ``` It is possible to manually provide an instance and to match on implicit instances: ``` f {A} : {{Show A}} -> A -> String | {{mkShow s}} x -> s x; f' {A} : {{Show A}} → A → String | {{M}} x := Show.show {{M}} x; ``` The trait parameters in instance types are checked to be structurally decreasing to avoid looping in the instance search. So the following is rejected: ``` type Box A := box A; trait type T A := mkT { pp : A → A }; instance boxT {A} : {{T (Box A)}} → T (Box A) := mkT (λ{x := x}); ``` We check whether each parameter is a strict subterm of some trait parameter in the target. This ordering is included in the finite multiset extension of the subterm ordering, hence terminating.
2023-09-08 13:16:43 +03:00
_ -> wrongError,
NegTest
"Instance target not a trait"
$(mkRelDir "Internal")
$(mkRelFile "TargetNotATrait.juvix")
$ \case
ErrTargetNotATrait {} -> Nothing
_ -> wrongError,
NegTest
"Not a trait"
$(mkRelDir "Internal")
$(mkRelFile "NotATrait.juvix")
$ \case
ErrNotATrait {} -> Nothing
_ -> wrongError,
NegTest
"No instance"
$(mkRelDir "Internal")
$(mkRelFile "NoInstance.juvix")
$ \case
ErrNoInstance {} -> Nothing
_ -> wrongError,
NegTest
"Ambiguous instances"
$(mkRelDir "Internal")
$(mkRelFile "AmbiguousInstances.juvix")
$ \case
ErrAmbiguousInstances {} -> Nothing
_ -> wrongError,
NegTest
"Subsumed instance"
$(mkRelDir "Internal")
$(mkRelFile "SubsumedInstance.juvix")
$ \case
ErrSubsumedInstance {} -> Nothing
_ -> wrongError,
Traits (#2320) * Closes #1646 Implements a basic trait framework. A simple instance search mechanism is included which fails if there is more than one matching instance at any step. Example usage: ``` import Stdlib.Prelude open hiding {Show; mkShow; show}; trait type Show A := mkShow { show : A → String }; instance showStringI : Show String := mkShow (show := id); instance showBoolI : Show Bool := mkShow (show := λ{x := if x "true" "false"}); instance showNatI : Show Nat := mkShow (show := natToString); showList {A} : {{Show A}} → List A → String | nil := "nil" | (h :: t) := Show.show h ++str " :: " ++str showList t; instance showListI {A} {{Show A}} : Show (List A) := mkShow (show := showList); showMaybe {A} {{Show A}} : Maybe A → String | (just x) := "just (" ++str Show.show x ++str ")" | nothing := "nothing"; instance showMaybeI {A} {{Show A}} : Show (Maybe A) := mkShow (show := showMaybe); main : IO := printStringLn (Show.show true) >> printStringLn (Show.show false) >> printStringLn (Show.show 3) >> printStringLn (Show.show [true; false]) >> printStringLn (Show.show [1; 2; 3]) >> printStringLn (Show.show [1; 2]) >> printStringLn (Show.show [true; false]) >> printStringLn (Show.show [just true; nothing; just false]) >> printStringLn (Show.show [just [1]; nothing; just [2; 3]]) >> printStringLn (Show.show "abba") >> printStringLn (Show.show ["a"; "b"; "c"; "d"]); ``` It is possible to manually provide an instance and to match on implicit instances: ``` f {A} : {{Show A}} -> A -> String | {{mkShow s}} x -> s x; f' {A} : {{Show A}} → A → String | {{M}} x := Show.show {{M}} x; ``` The trait parameters in instance types are checked to be structurally decreasing to avoid looping in the instance search. So the following is rejected: ``` type Box A := box A; trait type T A := mkT { pp : A → A }; instance boxT {A} : {{T (Box A)}} → T (Box A) := mkT (λ{x := x}); ``` We check whether each parameter is a strict subterm of some trait parameter in the target. This ordering is included in the finite multiset extension of the subterm ordering, hence terminating.
2023-09-08 13:16:43 +03:00
NegTest
"Explicit instance argument"
$(mkRelDir "Internal")
$(mkRelFile "ExplicitInstanceArgument.juvix")
$ \case
ErrExplicitInstanceArgument {} -> Nothing
_ -> wrongError,
NegTest
"Instance termination"
$(mkRelDir "Internal")
$(mkRelFile "InstanceTermination.juvix")
$ \case
ErrTraitNotTerminating {} -> Nothing
2023-10-11 00:28:06 +03:00
_ -> wrongError,
NegTest
"Default value wrong type"
$(mkRelDir "Internal")
$(mkRelFile "DefaultTypeError.juvix")
$ \case
ErrWrongType {} -> Nothing
Instance coercions (#2444) * Closes #2426 A coercion from trait `T` to `T'` can be declared with the syntax ``` coercion instance coeName {A} {{T A}} : T' A := ... ``` Coercions can be seen as instances with special resolution rules. Coercion resolution rules ------------------------- * If a non-coercion instance can be applied in a single instance resolution step, no coercions are considered. No ambiguity results if there exists some coercion which could be applied, but a non-coercion instance exists - the non-coercion instances have priority. * If no non-coercion instance can be applied in a single resolution step, all minimal coercion paths which lead to an applicable non-coercion instance are considered. If there is more than one, ambiguity is reported. Examples ---------- The following type-checks because: 1. There is no non-coercion instance found for `U String`. 2. There are two minimal coercion paths `U` <- `U1` and `U` <- `U2`, but only one of them (`U` <- `U2`) ends in an applicable non-coercion instance (`instU2` for `U2 String`). ``` trait type U A := mkU {pp : A -> A}; trait type U1 A := mkU1 {pp : A -> A}; trait type U2 A := mkU2 {pp : A -> A}; coercion instance fromU1toU {A} {{U1 A}} : U A := mkU@{ pp := U1.pp }; coercion instance fromU2toU {A} {{U2 A}} : U A := mkU@{ pp := U2.pp }; instance instU2 : U2 String := mkU2 id; main : IO := printStringLn (U.pp "X") ``` The following results in an ambiguity error because: 1. There is no non-coercion instance found for `T Unit`. 2. There are two minimal coercion paths `T` <- `T1` and `T` <- `T2`, both of which end in applicable non-coercion instances. ``` trait type T A := mkT { pp : A → A }; trait type T1 A := mkT1 { pp : A → A }; trait type T2 A := mkT2 { pp : A → A }; instance unitT1 : T1 Unit := mkT1 (pp := λ{_ := unit}); instance unitT2 : T2 Unit := mkT2 (pp := λ{_ := unit}); coercion instance fromT1toT {A} {{T1 A}} : T A := mkT@{ pp := T1.pp }; coercion instance fromT2toT {A} {{T2 A}} : T A := mkT@{ pp := T2.pp }; main : Unit := T.pp unit; ``` The following type-checks, because there exists a non-coercion instance for `T2 String`, so the coercion `fromT1toT2` is ignored during instance resolution. ``` trait type T1 A := mkT1 {pp : A -> A}; trait type T2 A := mkT2 {pp : A -> A}; instance instT1 {A} : T1 A := mkT1@{ pp := id }; coercion instance fromT1toT2 {A} {{M : T1 A}} : T2 A := mkT2@{ pp := T1.pp {{M}} }; instance instT2 : T2 String := mkT2@{ pp (s : String) : String := s ++str "!" }; main : String := T2.pp "a"; ```
2023-10-19 17:00:31 +03:00
_ -> wrongError,
NegTest
"Coercion target not a trait"
$(mkRelDir "Internal")
$(mkRelFile "CoercionTargetNotATrait.juvix")
$ \case
ErrTargetNotATrait {} -> Nothing
_ -> wrongError,
NegTest
"Invalid coercion type"
$(mkRelDir "Internal")
$(mkRelFile "InvalidCoercionType.juvix")
$ \case
ErrInvalidCoercionType {} -> Nothing
_ -> wrongError,
NegTest
"Wrong coercion argument"
$(mkRelDir "Internal")
$(mkRelFile "WrongCoercionArgument.juvix")
$ \case
ErrWrongCoercionArgument {} -> Nothing
_ -> wrongError,
NegTest
"Ambiguous coercions"
$(mkRelDir "Internal")
$(mkRelFile "AmbiguousCoercions.juvix")
$ \case
ErrAmbiguousInstances {} -> Nothing
_ -> wrongError,
NegTest
"Coercion cycles"
$(mkRelDir "Internal")
$(mkRelFile "LoopingCoercion.juvix")
$ \case
ErrCoercionCycles {} -> 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
]