Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type family EnableIf (condition :: Bool) (a :: Type) :: Type where ...
- newtype Return (a :: Type) where
- type family ReturnOf (f :: Type) :: Type where ...
- type family CanReturn (r :: Type) (f :: Type) :: Bool where ...
- type family TaggedReturn (r :: Type) (f :: Type) :: Type where ...
- type TagReturn (r :: Type) (f :: Type) = TagReturn' (TaggedReturn r f) f
- tagReturn :: forall r f. TagReturn r f => Proxy r -> f -> TaggedReturn r f
- type family UntaggedReturn (f :: Type) :: Type where ...
- type UntagReturn (f :: Type) = UntagReturn' f
- untagReturn :: UntagReturn f => f -> UntaggedReturn f
Documentation
type family EnableIf (condition :: Bool) (a :: Type) :: Type where ... Source #
This only compiles when the supplied type-level condition is True
newtype Return (a :: Type) where Source #
This can be used to make the return type of a function unambigious in pattern matching contexts. (Ambiguity can occur because functions in Haskell are implicitly curried.)
type family ReturnOf (f :: Type) :: Type where ... Source #
Yeilds the ultimate return type of a function (after it has been fully applied).
Since this never resolves to a function type as the return type, one must wrap
desired function returns. Return
can be used for such wrapping.
type family CanReturn (r :: Type) (f :: Type) :: Bool where ... Source #
Determines whether a function of type f
can return the type r
.
type family TaggedReturn (r :: Type) (f :: Type) :: Type where ... Source #
Tags the desired return type r
of f
with Return
.
Note: This fails to compile if r
is not a valid return type of f
.
Examples:
TaggedReturn Int Int ~ (Return Int) TaggedReturn Int (Char -> Char -> Int) ~ Char -> Char -> Return Int TaggedReturn (Char -> Int) (Char -> Char -> Int) ~ Char -> Return (Char -> Int)
TaggedReturn r r = Return r | |
TaggedReturn r (a -> b) = a -> TaggedReturn r b |
type TagReturn (r :: Type) (f :: Type) = TagReturn' (TaggedReturn r f) f Source #
The constraint required for tagReturn
.
tagReturn :: forall r f. TagReturn r f => Proxy r -> f -> TaggedReturn r f Source #
Transforms a function of type f
into a new function of type TaggedReturn r f
type family UntaggedReturn (f :: Type) :: Type where ... Source #
Removes the Return
tag from function signature of f
.
This is the inverse of TaggedReturn
in the sense that the following holds:
UntaggedReturn (TaggedReturn r f) ~ f
Note: This fails to compile if Return r
is not a valid return type of f
.
UntaggedReturn (Return r) = r | |
UntaggedReturn (a -> b) = a -> UntaggedReturn b |
type UntagReturn (f :: Type) = UntagReturn' f Source #
The constraint required for untagReturn
.
untagReturn :: UntagReturn f => f -> UntaggedReturn f Source #
Transforms a function of type TaggedReturn r f
into a new function of type f