Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Miscellaneous families.
Synopsis
- data Error :: Symbol -> Exp a
- data TError :: ErrorMessage -> Exp a
- data Constraints :: [Constraint] -> Exp Constraint
- data TyEq :: a -> b -> Exp Bool
- type family Stuck :: a
- class IsBool (b :: Bool) where
- data Case :: [Match j k] -> j -> Exp k
- data Match j k
- type (-->) = (Match_ :: j -> k -> Match j k)
- type Is = (Is_ :: (j -> Exp Bool) -> k -> Match j k)
- type Any = (Any_ :: k -> Match j k)
- type Else = (Else_ :: (j -> Exp k) -> Match j k)
- type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ...
Documentation
data Constraints :: [Constraint] -> Exp Constraint Source #
Conjunction of a list of constraints.
Instances
type Eval (Constraints (a ': as) :: Constraint -> Type) Source # | |
Defined in Fcf.Utils | |
type Eval (Constraints ([] :: [Constraint])) Source # | |
Defined in Fcf.Utils |
data Case :: [Match j k] -> j -> Exp k Source #
(Limited) equivalent of \case { .. }
syntax. Supports matching of exact
values (-->
) and final matches for any value (Any
) or for passing value
to subcomputation (Else
). Examples:
type BoolToNat =Case
[ 'True-->
0 , 'False-->
1 ] type NatToBool =Case
[ 0-->
'False ,Any
'True ] type ZeroOneOrSucc =Case
[ 0-->
0 , 1-->
1 ,Else
((+
) 1) ]
type Is = (Is_ :: (j -> Exp Bool) -> k -> Match j k) Source #
Match on predicate being successful with type in Case
.
type Any = (Any_ :: k -> Match j k) Source #
Match any type in Case
. Should be used as a final branch.
Note: this identifier conflicts with Any
(from Fcf.Class.Foldable)
Any
(from Data.Monoid), and Any
(from GHC.Exts).
We recommend importing this one qualified.
type Else = (Else_ :: (j -> Exp k) -> Match j k) Source #
Pass type being matched in Case
to subcomputation. Should be used as a
final branch.