fcf-composite-0.1.1.0: Type-level computation for composite using first-class-families.
Safe HaskellNone
LanguageHaskell2010

Composite.Fcf

Synopsis

Documentation

data FromCompositeS :: Type -> Exp (Symbol, Type) Source #

Turn a single `s :-> a` into an `'(s, a)`

Since: 0.1.0.0

Instances

Instances details
type Eval (FromCompositeS (s :-> x) :: (Symbol, Type) -> Type) Source # 
Instance details

Defined in Composite.Fcf

type Eval (FromCompositeS (s :-> x) :: (Symbol, Type) -> Type) = '(s, x)

data FromComposite :: [Type] -> Exp (MapC Symbol Type) Source #

Turn a list of `(s -> a)` into a `MapC s a`

Since: 0.1.0.0

Instances

Instances details
type Eval (FromComposite x :: MapC Symbol Type -> Type) Source # 
Instance details

Defined in Composite.Fcf

data ToCompositeS :: (Symbol, Type) -> Exp Type Source #

Turn a single `(s, a)` into a `s :-> a`

Since: 0.1.0.0

Instances

Instances details
type Eval (ToCompositeS '(s, x) :: Type -> Type) Source # 
Instance details

Defined in Composite.Fcf

type Eval (ToCompositeS '(s, x) :: Type -> Type) = s :-> x

data ToComposite :: MapC Symbol Type -> Exp [Type] Source #

Turn a `MapC s a` into a list of `(s :-> a)`

Since: 0.1.0.0

Instances

Instances details
type Eval (ToComposite x :: [Type] -> Type) Source # 
Instance details

Defined in Composite.Fcf

type Eval (ToComposite x :: [Type] -> Type) = Eval ((Map ToCompositeS :: [(Symbol, Type)] -> [Type] -> Type) =<< ToList x)

data Union :: [Type] -> [Type] -> Exp [Type] Source #

Difference

Since: 0.1.0.0

Instances

Instances details
type Eval (Union xs ys :: [Type] -> Type) Source # 
Instance details

Defined in Composite.Fcf

type Eval (Union xs ys :: [Type] -> Type) = Eval (ToComposite =<< Union (Eval (FromComposite xs)) (Eval (FromComposite ys)))

data Difference :: [Type] -> [Type] -> Exp [Type] Source #

Difference

Since: 0.1.0.0

Instances

Instances details
type Eval (Difference xs ys :: [Type] -> Type) Source # 
Instance details

Defined in Composite.Fcf

data Intersection :: [Type] -> [Type] -> Exp [Type] Source #

Intersection

Since: 0.1.0.0

Instances

Instances details
type Eval (Intersection xs ys :: [Type] -> Type) Source # 
Instance details

Defined in Composite.Fcf

difference :: forall f xs ys zs. (zs ~ Eval (Difference xs ys), zs (xs ++ ys)) => Rec f xs -> Rec f ys -> Rec f zs Source #

Take the difference of two records by casting to the result of Difference.

Since: 0.1.1.0

union :: forall f xs ys zs. (zs ~ Eval (Union xs ys), zs (xs ++ ys)) => Rec f xs -> Rec f ys -> Rec f zs Source #

Take the union of two records by casting to the result of Union.

Since: 0.1.1.0

intersection :: forall f xs ys zs. (zs ~ Eval (Intersection xs ys), zs (xs ++ ys)) => Rec f xs -> Rec f ys -> Rec f zs Source #

Take the intersection of two records by casting to the result of Intersection.

Since: 0.1.1.0