first-class-families-0.5.0.0: First class type families

Safe HaskellSafe
LanguageHaskell2010

Fcf.Utils

Description

Miscellaneous families.

Synopsis

Documentation

data Error :: Symbol -> Exp a Source #

Type-level error.

Instances
type Eval (Error msg :: a -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Error msg :: a -> Type) = (TypeError (Text msg) :: a)

data TError :: ErrorMessage -> Exp a Source #

TypeError as a fcf.

Instances
type Eval (TError msg :: a -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (TError msg :: a -> Type) = (TypeError msg :: a)

data Constraints :: [Constraint] -> Exp Constraint Source #

Conjunction of a list of constraints.

Instances
type Eval (Constraints (a ': as) :: Constraint -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Constraints (a ': as) :: Constraint -> Type) = (a, Eval (Constraints as))
type Eval (Constraints ([] :: [Constraint])) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Constraints ([] :: [Constraint])) = ()

data TyEq :: a -> b -> Exp Bool Source #

Type equality.

Instances
type Eval (TyEq a b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (TyEq a b :: Bool -> Type)

type family Stuck :: a Source #

A stuck type that can be used like a type-level undefined.

class IsBool (b :: Bool) where Source #

Methods

_If :: (b ~ True => r) -> (b ~ False => r) -> r Source #

Instances
IsBool False Source # 
Instance details

Defined in Fcf.Utils

Methods

_If :: ((False ~ True) -> r) -> ((False ~ False) -> r) -> r Source #

IsBool True Source # 
Instance details

Defined in Fcf.Utils

Methods

_If :: ((True ~ True) -> r) -> ((True ~ False) -> r) -> r Source #

type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ... #

Type-level If. If True a b ==> a; If False a b ==> b

Equations

If True (tru :: k) (fls :: k) = tru 
If False (tru :: k) (fls :: k) = fls