type-spec-0.3.0.1: Type Level Specification by Example

Safe HaskellNone
LanguageHaskell2010

Test.TypeSpec.Core

Contents

Description

Core of the TypeSpec abstractions. Import to add custom instances.

Synopsis

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.

Instances

PrettyTypeSpec k t => Show (TypeSpec k t) Source # 

Methods

showsPrec :: Int -> TypeSpec k t -> ShowS #

show :: TypeSpec k t -> String #

showList :: [TypeSpec k t] -> ShowS #

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 Type (ShouldBeFalse t t1) Source # 
type EvalExpectation Type (ShouldBeTrue t t1) Source # 
type EvalExpectation Type (It expectation message expectation1) Source # 
type EvalExpectation Type (It expectation message expectation1) = (>>) Type (Either ErrorMessage) expectation (PrependToError expectation ((:$$:) (Text message) (Text " ")) (EvalExpectation expectation expectation1)) (OK ErrorMessage Type (It expectation message expectation1))
type EvalExpectation Type (ShouldNotBe expected actual actual1 expected1) Source # 
type EvalExpectation Type (ShouldNotBe expected actual actual1 expected1) = If (Either ErrorMessage Type) (EqExtra 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 actual1 expected1))
type EvalExpectation Type (ShouldBe t t1 actual expected) Source # 
type EvalExpectation Type (ShouldBe t t1 actual expected) = If (Either ErrorMessage Type) (EqExtra t t1 actual expected) (OK ErrorMessage Type (ShouldBe t t1 actual expected)) (FAILED ErrorMessage Type ((:$$:) ((:<>:) (Text "Expected type: ") (ShowType t expected)) ((:<>:) (Text "Actual type: ") (ShowType t1 actual))))
type EvalExpectation Type (ButNot shouldntBe Type (ShouldBe t t1 actual expected) other) Source # 
type EvalExpectation Type (ButNot shouldntBe Type (ShouldBe t t1 actual expected) other) = If (Either ErrorMessage Type) (EqExtra t t1 actual expected) (If (Either ErrorMessage Type) (EqExtra t shouldntBe other expected) (FAILED ErrorMessage Type ((:$$:) ((:$$:) ((:$$:) (Text "Expected type: ") ((:<>:) (Text " ") (ShowType t expected))) (Text "to be different from: ")) ((:<>:) (Text " ") (ShowType shouldntBe other)))) (OK ErrorMessage Type (ButNot shouldntBe Type (ShouldBe t t1 actual expected) other))) (FAILED ErrorMessage Type ((:$$:) ((:<>:) (Text "Expected type: ") (ShowType t expected)) ((:<>:) (Text "Actual type: ") (ShowType t1 actual))))
type EvalExpectation [k] ([] k) Source # 
type EvalExpectation [k] ([] k) = OK ErrorMessage [k] ([] k)
type EvalExpectation [a] ((:) a expectation rest) Source # 
type EvalExpectation [a] ((:) a expectation rest) = (<*>) (Either ErrorMessage) [a] [a] ((<$>) (Either ErrorMessage) a ((~>) [a] [a]) (Cons'' a) (EvalExpectation a expectation)) (EvalExpectation [a] rest)
type EvalExpectation * ((-/-) a a1 expectation expectations) Source # 
type EvalExpectation * ((-/-) a a1 expectation expectations) = (<*>) (Either ErrorMessage) a * ((<$>) (Either ErrorMessage) a1 ((~>) a *) (TyCon2 * a a1 ((-/-) a a1)) (EvalExpectation a1 expectation)) (EvalExpectation a expectations)
type EvalExpectation (a, a1) ((,) a a1 a2 b) Source # 
type EvalExpectation (a, a1) ((,) a a1 a2 b) = (<*>) (Either ErrorMessage) a1 (a, a1) ((<$>) (Either ErrorMessage) a ((~>) a1 (a, a1)) (Pair'' a a1) (EvalExpectation a a2)) (EvalExpectation a1 b)

Pretty Printing Support

class PrettyTypeSpec t where Source #

A class for pretty printing via the Show instance of TypeSpec.

Minimal complete definition

prettyTypeSpec

Methods

prettyTypeSpec :: proxy t -> Doc Source #

Instances

PrettyTypeSpec Type (ShouldBeFalse expectation a) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

PrettyTypeSpec Type (ShouldBeTrue expectation a) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

(KnownSymbol msg, PrettyTypeSpec expectation x) => PrettyTypeSpec Type (It expectation msg x) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

PrettyTypeSpec Type (ShouldNotBe expected actual a b) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

PrettyTypeSpec Type (ShouldBe expected actual a b) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

(~) Type a (ShouldBe expected actual a0 a1) => PrettyTypeSpec Type (ButNot shouldntBe Type a b) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

PrettyTypeSpec [k] ([] k) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

(PrettyTypeSpec a expectation, PrettyTypeSpec [a] rest) => PrettyTypeSpec [a] ((:) a expectation rest) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

(PrettyTypeSpec k1 expectation1, PrettyTypeSpec k expectation2) => PrettyTypeSpec * ((-/-) k k1 expectation1 expectation2) Source #

Pretty Printing Instance.

Methods

prettyTypeSpec :: proxy t -> Doc Source #

(PrettyTypeSpec k1 expectation1, PrettyTypeSpec k expectation2) => PrettyTypeSpec (k1, k) ((,) k1 k expectation1 expectation2) Source # 

Methods

prettyTypeSpec :: proxy t -> Doc Source #

prettyIndentation :: Int Source #

The default indention to use when nesting Documents.