| Copyright | (c) 2014-2016 Justus Sagemüller |
|---|---|
| License | GPL v3 (see LICENSE) |
| Maintainer | (@) jsagemue $ uni-koeln.de |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Constraint.Trivial
Contents
Description
Synopsis
- class Unconstrained0
- class Disallowed "Impossible0" => Impossible0
- class Unconstrained t
- class Disallowed "Impossible" => Impossible t
- class Unconstrained2 t s
- class Disallowed "Impossible2" => Impossible2 t s
- class Unconstrained3 t s r
- class Disallowed "Impossible3" => Impossible3 t s r
- class Unconstrained4 t s r q
- class Disallowed "Impossible4" => Impossible4 t s r q
- class Unconstrained5 t s r q p
- class Disallowed "Impossible5" => Impossible5 t s r q p
- class Unconstrained6 t s r q p o
- class Disallowed "Impossible6" => Impossible6 t s r q p o
- class Unconstrained7 t s r q p o n
- class Disallowed "Impossible7" => Impossible7 t s r q p o n
- class Unconstrained8 t s r q p o n m
- class Disallowed "Impossible8" => Impossible8 t s r q p o n m
- class Unconstrained9 t s r q p o n m l
- class Disallowed "Impossible9" => Impossible9 t s r q p o n m l
- class (Bottom, TypeError ((Text "All instances of " :<>: Text t) :<>: Text " are disallowed.")) => Disallowed t
- nope :: forall (a :: TYPE rep). Bottom => a
Trivial classes
class Unconstrained0 Source #
A constraint that is always/unconditionally fulfilled. This behaves the same
way as (), when appearing in a constraint-tuple, i.e. it does not change anything
about the constraints. It is thus the identity of the (,) monoid in the constraint
kind.
Instances
| Unconstrained0 Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible0" => Impossible0 Source #
A constraint that never is fulfilled, in other words it is guaranteed that something whose context contains this constraint will never actually be invoked in a program.
class Unconstrained t Source #
A parametric non-constraint. This can be used, for instance, when you have an existential that contains endo-functions of any type of some specified constraint.
data GenEndo c where GenEndo :: c a => (a -> a) -> GenEndo c
Then, you can have values like GenEndo abs :: GenEndo Num. It is also possible
to have GenEndo id :: GenEndo Num, but here the num constraint is not actually
required. So what to use as the c argument? It should be a constraint on a type
which does not actually constrain the type.
idEndo :: GenEndo Unconstrained idEndo = GenEndo id
Instances
| Unconstrained (t :: k) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible" => Impossible t Source #
This constraint can never be fulfilled. One application in which this can be
useful is as a default for a class-associated constraint; this basically disables
any method with that constraint: so it can safely be left undefined. We provide
the nope method as a special form of undefined, which actually guarantees it
is safe through the type system. For instance, the old monad class with
its controversial fail method could be changed to
class Applicative m => Monad m where (return,(>>=)) :: ... type FailableResult m :: * -> Constraint type FailableResult m = Impossible -- fail disabled by default fail :: FailableResult m a => String -> m a fail = nope
This would turn any use of fail in a “pure” monad (which does not actually
define fail) into a type error.
Meanwhile, “safe” uses of fail, such as in the IO monad, could be kept as-is,
by making the instance
instance Monad IO where (return,(>>=)) = ... type FailableResult m = Unconstrained fail = throwErrow
Other instances could support the fail method only selectively for particular
result types, again by picking a suitable FailableResult constraint
(e.g. Monoid).
class Unconstrained2 t s Source #
Like Unconstrained, but with kind signature k -> k -> Constraint
(two unconstrained types).
Instances
| Unconstrained2 (t :: k2) (s :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible2" => Impossible2 t s Source #
class Unconstrained3 t s r Source #
Instances
| Unconstrained3 (t :: k3) (s :: k2) (r :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible3" => Impossible3 t s r Source #
class Unconstrained4 t s r q Source #
Instances
| Unconstrained4 (t :: k4) (s :: k3) (r :: k2) (q :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible4" => Impossible4 t s r q Source #
class Unconstrained5 t s r q p Source #
Instances
| Unconstrained5 (t :: k5) (s :: k4) (r :: k3) (q :: k2) (p :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible5" => Impossible5 t s r q p Source #
class Unconstrained6 t s r q p o Source #
Instances
| Unconstrained6 (t :: k6) (s :: k5) (r :: k4) (q :: k3) (p :: k2) (o :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible6" => Impossible6 t s r q p o Source #
class Unconstrained7 t s r q p o n Source #
Instances
| Unconstrained7 (t :: k7) (s :: k6) (r :: k5) (q :: k4) (p :: k3) (o :: k2) (n :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible7" => Impossible7 t s r q p o n Source #
class Unconstrained8 t s r q p o n m Source #
Instances
| Unconstrained8 (t :: k8) (s :: k7) (r :: k6) (q :: k5) (p :: k4) (o :: k3) (n :: k2) (m :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible8" => Impossible8 t s r q p o n m Source #
class Unconstrained9 t s r q p o n m l Source #
Instances
| Unconstrained9 (t :: k9) (s :: k8) (r :: k7) (q :: k6) (p :: k5) (o :: k4) (n :: k3) (m :: k2) (l :: k1) Source # | |
Defined in Data.Constraint.Trivial | |
class Disallowed "Impossible9" => Impossible9 t s r q p o n m l Source #
Utility
class (Bottom, TypeError ((Text "All instances of " :<>: Text t) :<>: Text " are disallowed.")) => Disallowed t Source #
nope :: forall (a :: TYPE rep). Bottom => a Source #
A term-level witness that the context contains a Disallowed constraint, i.e.
one of the Impossible0, Impossible ... constraints. In such a context, because
you are guaranteed that it can under no circumstances actually be invoked, you
are allowed to to anything whatsoever, even create a value of an uninhabited unlifted
type.