type-spec-0.4.0.0: 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 t => Show (TypeSpec t) Source # 
Instance details

Defined in Test.TypeSpec.Core

Methods

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

show :: TypeSpec t -> String #

showList :: [TypeSpec 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 (ShouldBeFalse t2 :: Type) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Test.TypeSpec.ShouldBe

type EvalExpectation (ShouldNotBe actual2 expected2 :: Type) = If (EqExtra expected2 actual2) (FAILED (((Text "Expected type: " :$$: (Text " " :<>: ShowType expected2)) :$$: Text "to be different from: ") :$$: (Text " " :<>: ShowType actual2))) (OK (ShouldNotBe actual2 expected2))
type EvalExpectation (ShouldBe actual expected :: Type) Source # 
Instance details

Defined in Test.TypeSpec.ShouldBe

type EvalExpectation (ShouldBe actual expected :: Type) = If (EqExtra actual expected) (OK (ShouldBe actual expected)) (FAILED ((Text "Expected type: " :<>: ShowType expected) :$$: (Text "Actual type: " :<>: ShowType actual)))
type EvalExpectation (ButNot (ShouldBe actual expected) other :: Type) Source # 
Instance details

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 (expectation : rest) try to evaluate the expectation then, if no error was returned, the rest.

Instance details

Defined in Test.TypeSpec.Core

type EvalExpectation ([] :: [k]) = OK ([] :: [k])
type EvalExpectation (expectation ': rest :: [a]) Source # 
Instance details

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 # 
Instance details

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 (expectation1, expectation2) try to evaluate the first then, if no error was returned, the second.

Instance details

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 #

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

Methods

prettyTypeSpec :: proxy t -> Doc Source #

Instances
PrettyTypeSpec (ShouldBeFalse a :: Type) Source # 
Instance details

Defined in Test.TypeSpec.ShouldBe

Methods

prettyTypeSpec :: proxy (ShouldBeFalse a) -> Doc Source #

PrettyTypeSpec (ShouldBeTrue a :: Type) Source # 
Instance details

Defined in Test.TypeSpec.ShouldBe

Methods

prettyTypeSpec :: proxy (ShouldBeTrue a) -> Doc Source #

(KnownSymbol msg, PrettyTypeSpec x) => PrettyTypeSpec (It msg x :: Type) Source # 
Instance details

Defined in Test.TypeSpec.Label

Methods

prettyTypeSpec :: proxy (It msg x) -> Doc Source #

PrettyTypeSpec (ShouldNotBe a b :: Type) Source # 
Instance details

Defined in Test.TypeSpec.ShouldBe

Methods

prettyTypeSpec :: proxy (ShouldNotBe a b) -> Doc Source #

PrettyTypeSpec (ShouldBe a b :: Type) Source # 
Instance details

Defined in Test.TypeSpec.ShouldBe

Methods

prettyTypeSpec :: proxy (ShouldBe a b) -> Doc Source #

a ~ ShouldBe a0 a1 => PrettyTypeSpec (ButNot a b :: Type) Source # 
Instance details

Defined in Test.TypeSpec.ShouldBe

Methods

prettyTypeSpec :: proxy (ButNot a b) -> Doc Source #

PrettyTypeSpec ([] :: [k]) Source # 
Instance details

Defined in Test.TypeSpec.Core

Methods

prettyTypeSpec :: proxy [] -> Doc Source #

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

Defined in Test.TypeSpec.Core

Methods

prettyTypeSpec :: proxy (expectation ': rest) -> Doc Source #

(PrettyTypeSpec expectation1, PrettyTypeSpec expectation2) => PrettyTypeSpec (expectation1 -/- expectation2 :: Type) Source #

Pretty Printing Instance.

Instance details

Defined in Test.TypeSpec.Group

Methods

prettyTypeSpec :: proxy (expectation1 -/- expectation2) -> Doc Source #

(PrettyTypeSpec expectation1, PrettyTypeSpec expectation2) => PrettyTypeSpec ((,) expectation1 expectation2 :: (k2, k1)) Source # 
Instance details

Defined in Test.TypeSpec.Core

Methods

prettyTypeSpec :: proxy (expectation1, expectation2) -> Doc Source #

prettyIndentation :: Int Source #

The default indention to use when nesting Documents.