Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal.Data.Basic.TypeLevel
- class AllSatisfy c (l :: [k]) where
- type family Elem (x :: k) (xs :: [k]) :: Bool where ...
- type family EqualOrError (a :: k) (b :: k) (err :: ErrorMessage) :: Constraint where ...
- type CheckWithError (b :: Bool) (err :: ErrorMessage) = EqualOrError b True err
- type family Not (b :: Bool) where ...
- type ErrorText = Text
- type family xs ++ ys where ...
- type family Without (xs :: [k]) (ys :: [k]) :: [k] where ...
- type family IsSubset xs ys :: Constraint where ...
- class c x => TypeSatisfies (c :: * -> Constraint) (x :: *) (field :: Symbol)
- type family OnMaybe (a :: k) (f :: b -> k) (m :: Maybe b) :: k where ...
- class CheckWithError (NotMaybe a) (FieldNullErr field) => NotNull (a :: *) (field :: Symbol)
- type family ListToTuple (f :: k -> *) (l :: [k]) where ...
- class Trivial a
- type family SetEqual (as :: [k]) (bs :: [k]) :: Constraint where ...
- data ErrorMessage :: * where
- type family TypeError b (a :: ErrorMessage) :: b where ...
Documentation
class AllSatisfy c (l :: [k]) where Source #
Minimal complete definition
Methods
mapTypeList :: proxy1 c -> (forall proxy2 (x :: k). c x => proxy2 x -> a) -> proxy3 l -> [a] Source #
Instances
AllSatisfy k c ([] k) Source # | |
(c k, AllSatisfy a c ks) => AllSatisfy a c ((:) a k ks) Source # | |
type family EqualOrError (a :: k) (b :: k) (err :: ErrorMessage) :: Constraint where ... Source #
Equations
EqualOrError a a err = () | |
EqualOrError a b err = TypeError err |
type CheckWithError (b :: Bool) (err :: ErrorMessage) = EqualOrError b True err Source #
type family IsSubset xs ys :: Constraint where ... Source #
class c x => TypeSatisfies (c :: * -> Constraint) (x :: *) (field :: Symbol) Source #
Instances
c x => TypeSatisfies c x field Source # | |
class CheckWithError (NotMaybe a) (FieldNullErr field) => NotNull (a :: *) (field :: Symbol) Source #
Instances
CheckWithError (NotMaybe a) (FieldNullErr Symbol field) => NotNull a field Source # | |
type family ListToTuple (f :: k -> *) (l :: [k]) where ... Source #
Equations
ListToTuple f '[] = () | |
ListToTuple f '[a] = f a | |
ListToTuple f '[a, b] = (f a, f b) | |
ListToTuple f '[a, b, c] = (f a, f b, f c) | |
ListToTuple f '[a, b, c, d] = (f a, f b, f c, f d) | |
ListToTuple f '[a, b, c, d, e] = (f a, f b, f c, f d, f e) |
type family SetEqual (as :: [k]) (bs :: [k]) :: Constraint where ... Source #
data ErrorMessage :: * where #
A description of a custom type error.
Constructors
ShowType :: ErrorMessage | Pretty print the type.
|
(:<>:) :: ErrorMessage infixl 6 | Put two pieces of error message next to each other. |
(:$$:) :: ErrorMessage infixl 5 | Stack two pieces of error message on top of each other. |
type family TypeError b (a :: ErrorMessage) :: b where ... #
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: 4.9.0.0