Safe Haskell | None |
---|---|
Language | Haskell2010 |
Type level assertions on type equality.
Synopsis
- data ShouldBe :: actual -> expected -> Type
- data ShouldNotBe :: actual -> expected -> Type
- data ShouldBeTrue :: expectation -> Type
- data ShouldBeFalse :: expectation -> Type
- data ButNot :: shouldBe -> shouldntBe -> Type
Documentation
data ShouldBe :: actual -> expected -> Type Source #
State that two types or type constructs are boiled down to the same type.
Instances
PrettyTypeSpec (ShouldBe a b :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe prettyTypeSpec :: proxy (ShouldBe a b) -> Doc Source # | |
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))) |
data ShouldNotBe :: actual -> expected -> Type Source #
State that two types or type constructs are NOT the same type.
Instances
PrettyTypeSpec (ShouldNotBe a b :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe prettyTypeSpec :: proxy (ShouldNotBe a b) -> Doc Source # | |
type EvalExpectation (ShouldNotBe actual2 expected2 :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe |
data ShouldBeTrue :: expectation -> Type Source #
State that a type is equal to the type level True
.
Instances
PrettyTypeSpec (ShouldBeTrue a :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe prettyTypeSpec :: proxy (ShouldBeTrue a) -> Doc Source # | |
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)) |
data ShouldBeFalse :: expectation -> Type Source #
State that a type is equal to the type level False
.
Instances
PrettyTypeSpec (ShouldBeFalse a :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe prettyTypeSpec :: proxy (ShouldBeFalse a) -> Doc Source # | |
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)) |
data ButNot :: shouldBe -> shouldntBe -> Type Source #
State that one type is different to two other types. This must always be
used right next to a ShouldBe
pair, otherwise this will not work.
Instances
a ~ ShouldBe a0 a1 => PrettyTypeSpec (ButNot a b :: Type) Source # | |
Defined in Test.TypeSpec.ShouldBe prettyTypeSpec :: proxy (ButNot a b) -> Doc 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))) |