type-spec-0.1.0.0: Type Level Specification by Example

Safe HaskellNone
LanguageHaskell2010

Test.TypeSpec.ShouldBe

Description

Type level assertions on type equality.

Synopsis

Documentation

data ShouldBe :: expected -> actual -> Type Source #

State that two types or type constructs are boiled down to the same type.

Instances

PrettyTypeSpec Type (ShouldBe expected actual a b) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

type EvalExpectation Type (ShouldBe t t1 expected actual) Source # 
type EvalExpectation Type (ShouldBe t t1 expected actual) = If (Either ErrorMessage Type) (PolyKindEq t1 t expected actual) (OK ErrorMessage Type (ShouldBe t t1 expected actual)) (FAILED ErrorMessage Type ((:$$:) ((:<>:) (Text "Expected type: ") (ShowType t expected)) ((:<>:) (Text "Actual type: ") (ShowType t1 actual))))
type EvalExpectation Type (ButNot Type t (ShouldBe t t expected actual) other) Source # 
type EvalExpectation Type (ButNot Type t (ShouldBe t t expected actual) other) = If (Either ErrorMessage Type) ((==) t expected actual) (If (Either ErrorMessage Type) ((==) t expected other) (FAILED ErrorMessage Type ((:$$:) ((:$$:) ((:$$:) (Text "Expected type: ") ((:<>:) (Text " ") (ShowType t expected))) (Text "to be different from: ")) ((:<>:) (Text " ") (ShowType t other)))) (OK ErrorMessage Type (ButNot Type t (ShouldBe t t expected actual) other))) (FAILED ErrorMessage Type ((:$$:) ((:<>:) (Text "Expected type: ") (ShowType t expected)) ((:<>:) (Text "Actual type: ") (ShowType t actual))))

data ShouldNotBe :: expected -> actual -> Type Source #

State that two types or type constructs are NOT the same type.

Instances

(Showtype expected a, Showtype actual b) => PrettyTypeSpec Type (ShouldNotBe expected actual a b) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

type EvalExpectation Type (ShouldNotBe expected actual expected1 actual1) Source # 
type EvalExpectation Type (ShouldNotBe expected actual expected1 actual1) = If (Either ErrorMessage Type) (PolyKindEq actual expected expected1 actual1) (FAILED ErrorMessage Type ((:$$:) ((:$$:) ((:$$:) (Text "Expected type: ") ((:<>:) (Text " ") (ShowType expected expected1))) (Text "to be different from: ")) ((:<>:) (Text " ") (ShowType actual actual1)))) (OK ErrorMessage Type (ShouldNotBe expected actual expected1 actual1))

data ShouldBeTrue :: expectation -> Type Source #

State that a type is equal to the type level True.

Instances

data ShouldBeFalse :: expectation -> Type Source #

State that a type is equal to the type level False.

Instances

data ButNot :: shouldBe -> actual -> 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

((~) Type a (ShouldBe k k1 a0 a1), Showtype k a0, Showtype k1 a1, Showtype actual b) => PrettyTypeSpec Type (ButNot Type actual a b) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

type EvalExpectation Type (ButNot Type t (ShouldBe t t expected actual) other) Source # 
type EvalExpectation Type (ButNot Type t (ShouldBe t t expected actual) other) = If (Either ErrorMessage Type) ((==) t expected actual) (If (Either ErrorMessage Type) ((==) t expected other) (FAILED ErrorMessage Type ((:$$:) ((:$$:) ((:$$:) (Text "Expected type: ") ((:<>:) (Text " ") (ShowType t expected))) (Text "to be different from: ")) ((:<>:) (Text " ") (ShowType t other)))) (OK ErrorMessage Type (ButNot Type t (ShouldBe t t expected actual) other))) (FAILED ErrorMessage Type ((:$$:) ((:<>:) (Text "Expected type: ") (ShowType t expected)) ((:<>:) (Text "Actual type: ") (ShowType t actual))))