Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module exports:
- The
TypeError
type family, which is used to provide custom type errors. This is a type-level analogue to the term level error function. - The
ErrorMessage
kind, used to define custom error messages. - The
Unsatisfiable
constraint, a more principled variant ofTypeError
which gives a more predictable way of reporting custom type errors.
Since: base-4.17.0.0
Synopsis
- data ErrorMessage
- type family TypeError (a :: ErrorMessage) :: b where ...
- type family Assert (check :: Bool) errMsg where ...
- class Unsatisfiable (msg :: ErrorMessage)
- unsatisfiable :: forall (msg :: ErrorMessage) a. Unsatisfiable msg => a
Documentation
data ErrorMessage Source #
A description of a custom type error.
Text Symbol | Show the text as is. |
ShowType t | Pretty print the type.
|
ErrorMessage :<>: ErrorMessage infixl 6 | Put two pieces of error message next to each other. |
ErrorMessage :$$: ErrorMessage infixl 5 | Stack two pieces of error message on top of each other. |
type family TypeError (a :: ErrorMessage) :: b where ... Source #
The type-level equivalent of error
.
The polymorphic kind of this type allows it to be used in several settings. For instance, it can be used as a constraint, e.g. to provide a better error message for a non-existent instance,
-- in a context
instance TypeError (Text "Cannot Show
functions." :$$:
Text "Perhaps there is a missing argument?")
=> Show (a -> b) where
showsPrec = error "unreachable"
It can also be placed on the right-hand side of a type-level function to provide an error for an invalid case,
type family ByteSize x where ByteSize Word16 = 2 ByteSize Word8 = 1 ByteSize a = TypeError (Text "The type " :<>: ShowType a :<>: Text " is not exportable.")
Since: base-4.9.0.0
type family Assert (check :: Bool) errMsg where ... Source #
A type-level assert function.
If the first argument evaluates to true, then the empty constraint is
returned, otherwise the second argument (which is intended to be something
which reduces to TypeError
is used).
For example, given some type level predicate P' :: Type -> Bool
, it is
possible to write the type synonym
type P a = Assert (P' a) (NotPError a)
where NotPError
reduces to a TypeError
which is reported if the
assertion fails.
Since: base-4.17.0.0
class Unsatisfiable (msg :: ErrorMessage) Source #
An unsatisfiable constraint. Similar to TypeError
when used at the
Constraint
kind, but reports errors in a more predictable manner.
See also the unsatisfiable
function.
since base-4.19.0.0
.
unsatisfiableLifted
unsatisfiable :: forall (msg :: ErrorMessage) a. Unsatisfiable msg => a Source #
Prove anything within a context with an Unsatisfiable
constraint.
This is useful for filling in instance methods when there is an Unsatisfiable
constraint in the instance head, e.g.:
instance Unsatisfiable (Text "No Eq instance for functions") => Eq (a -> b) where
(==) = unsatisfiable
since base-4.19.0.0
.