Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lorentz.Test.DupableScan
Description
Test utilities to ensure the proper layout of non-dupable elements within datatypes.
Synopsis
- type family CheckDupablesDistribution a where ...
- type VerifyDupablesDistribution a = ResToConstraint (CheckDupablesDistribution a)
- checkDupablesDistribution :: forall a. DemoteRes (CheckDupablesDistribution a) => Either BadElement ()
- testDupablesDistribution :: forall a. (Typeable a, DemoteRes (CheckDupablesDistribution a)) => TestTree
- data BadElement = BadElement {}
Documentation
type family CheckDupablesDistribution a where ... Source #
For the given type, check that at the left subtree of pairs tree it contains only dupable elements, and at the right - only non-dupable ones.
On ambiguity, evaluation is delayed to avoid exposing Generic internals.
Equations
CheckDupablesDistribution ThisTypeShallNotBeExported = TypeError ('Text "impossible") | |
CheckDupablesDistribution a = GCheckDupablesDistribution (GRep a) |
type VerifyDupablesDistribution a = ResToConstraint (CheckDupablesDistribution a) Source #
A constraint that, for the given type, checks that at the left subtree of pairs tree it contains only dupable elements, and at the right - only non-dupable ones.
checkDupablesDistribution :: forall a. DemoteRes (CheckDupablesDistribution a) => Either BadElement () Source #
CheckDupablesDistribution
for term-level.
Shows decent error messages on missing Generic
instance.
>>>
checkDupablesDistribution
... ... Ambiguous type variable ‘a0’ arising from a use of ‘checkDupablesDistribution’ ... prevents the constraint ‘(Lorentz.Test.DupableScan.DemoteRes ... (CheckDupablesDistribution a0))’ from being solved. ...
The type must have a Generic
instance.
>>>
data Foo = Foo () (Ticket ())
>>>
checkDupablesDistribution @Foo
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
The type itself needn't necessarily have IsoValue
instance, but all its leaves
must.
>>>
data Foo = Foo () (Ticket ()) deriving Generic
>>>
checkDupablesDistribution @Foo
Right ()
testDupablesDistribution :: forall a. (Typeable a, DemoteRes (CheckDupablesDistribution a)) => TestTree Source #
A term-level version of VerifyDupablesDistribution
for tests.
data BadElement Source #
Error for checkDupablesDistribution
.
Constructors
BadElement | |
Instances
Show BadElement Source # | |
Defined in Lorentz.Test.DupableScan Methods showsPrec :: Int -> BadElement -> ShowS # show :: BadElement -> String # showList :: [BadElement] -> ShowS # | |
Eq BadElement Source # | |
Defined in Lorentz.Test.DupableScan | |
Buildable BadElement Source # | |
Defined in Lorentz.Test.DupableScan |