| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.TypeSpec.Core
Description
Core of the TypeSpec abstractions. Import to add custom instances.
Synopsis
- data TypeSpec expectation where
- Valid :: Try (EvalExpectation expectation) ~ expectation => TypeSpec expectation
- Invalid :: DontTry (EvalExpectation expectation) => TypeSpec expectation
- type family EvalExpectation (expectation :: k) :: Result k
- class PrettyTypeSpec (t :: k) where
- prettyTypeSpec :: proxy t -> Doc
- prettyIndentation :: Int
- module Test.TypeSpec.Internal.Result
Core Data Type
data TypeSpec expectation where Source #
A type specification.
Constructors
| Valid :: Try (EvalExpectation expectation) ~ expectation => TypeSpec expectation | Expect the given expectations to hold. If the compiler does not reject it - the expectation seem plausible. |
| Invalid :: DontTry (EvalExpectation expectation) => TypeSpec expectation | Expect the given expectations to **NOT** hold. If the compiler does not reject it - the expectation seem indeed implausible. |
Expectations
type family EvalExpectation (expectation :: k) :: Result k Source #
An open family of type level expectation evaluators, that return either ()
or an ErrorMessage.
Instances
| type EvalExpectation (ShouldBeFalse t2 :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe type EvalExpectation (ShouldBeFalse t2 :: Type) = If (EqExtra t2 False) (OK (ShouldBeFalse t2)) (FAILED (Text "Should have been 'False: " :<>: ShowType t2)) | |
| type EvalExpectation (ShouldBeTrue t2 :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe type EvalExpectation (ShouldBeTrue t2 :: Type) = If (EqExtra t2 True) (OK (ShouldBeTrue t2)) (FAILED (Text "Should have been 'True: " :<>: ShowType t2)) | |
| type EvalExpectation (It message expectation2 :: Type) Source # | |
Defined in Test.TypeSpec.Label type EvalExpectation (It message expectation2 :: Type) = PrependToError (Text message :$$: Text " ") (EvalExpectation expectation2) >> OK (It message expectation2) | |
| type EvalExpectation (ShouldNotBe actual2 expected2 :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe | |
| type EvalExpectation (ShouldBe actual expected :: Type) Source # | |
| type EvalExpectation (ButNot (ShouldBe actual expected) other :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe type EvalExpectation (ButNot (ShouldBe actual expected) other :: Type) = If (EqExtra actual expected) (If (EqExtra other expected) (FAILED (((Text "Expected type: " :$$: (Text " " :<>: ShowType expected)) :$$: Text "to be different from: ") :$$: (Text " " :<>: ShowType other))) (OK (ButNot (ShouldBe actual expected) other))) (FAILED ((Text "Expected type: " :<>: ShowType expected) :$$: (Text "Actual type: " :<>: ShowType actual))) | |
| type EvalExpectation ([] :: [k]) Source # | Given a list |
Defined in Test.TypeSpec.Core | |
| type EvalExpectation (expectation ': rest :: [a]) Source # | |
Defined in Test.TypeSpec.Core type EvalExpectation (expectation ': rest :: [a]) = ((Cons'' :: TyFun a ([a] ~> [a]) -> Type) <$> EvalExpectation expectation) <*> EvalExpectation rest | |
| type EvalExpectation (expectation -/- expectations :: Type) Source # | |
Defined in Test.TypeSpec.Group type EvalExpectation (expectation -/- expectations :: Type) = (TyCon2 ((-/-) :: a2 -> a1 -> Type) <$> EvalExpectation expectation) <*> EvalExpectation expectations | |
| type EvalExpectation ((,) a3 b :: (a2, a1)) Source # | Given a pair |
Defined in Test.TypeSpec.Core type EvalExpectation ((,) a3 b :: (a2, a1)) = ((Pair'' :: TyFun a2 (a1 ~> (a2, a1)) -> Type) <$> EvalExpectation a3) <*> EvalExpectation b | |
Pretty Printing Support
class PrettyTypeSpec (t :: k) where Source #
Methods
prettyTypeSpec :: proxy t -> Doc Source #