Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data FromCompositeS :: Type -> Exp (Symbol, Type)
- data FromComposite :: [Type] -> Exp (MapC Symbol Type)
- data ToCompositeS :: (Symbol, Type) -> Exp Type
- data ToComposite :: MapC Symbol Type -> Exp [Type]
- data Union :: [Type] -> [Type] -> Exp [Type]
- data Difference :: [Type] -> [Type] -> Exp [Type]
- data Intersection :: [Type] -> [Type] -> Exp [Type]
- difference :: forall f xs ys zs. (zs ~ Eval (Difference xs ys), zs ⊆ (xs ++ ys)) => Rec f xs -> Rec f ys -> Rec f zs
- union :: forall f xs ys zs. (zs ~ Eval (Union xs ys), zs ⊆ (xs ++ ys)) => Rec f xs -> Rec f ys -> Rec f zs
- intersection :: forall f xs ys zs. (zs ~ Eval (Intersection xs ys), zs ⊆ (xs ++ ys)) => Rec f xs -> Rec f ys -> Rec f zs
Documentation
data FromCompositeS :: Type -> Exp (Symbol, Type) Source #
Turn a single `s :-> a` into an `'(s, a)`
Since: 0.1.0.0
Instances
type Eval (FromCompositeS (s :-> x) :: (Symbol, Type) -> Type) Source # | |
Defined in Composite.Fcf |
data FromComposite :: [Type] -> Exp (MapC Symbol Type) Source #
Turn a list of `(s -> a)` into a `MapC s a`
Since: 0.1.0.0
data ToCompositeS :: (Symbol, Type) -> Exp Type Source #
Turn a single `(s, a)` into a `s :-> a`
Since: 0.1.0.0
Instances
type Eval (ToCompositeS '(s, x) :: Type -> Type) Source # | |
Defined in Composite.Fcf |
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
type Eval (ToComposite x :: [Type] -> Type) Source # | |
Defined in Composite.Fcf |
data Union :: [Type] -> [Type] -> Exp [Type] Source #
Difference
Since: 0.1.0.0
Instances
type Eval (Union xs ys :: [Type] -> Type) Source # | |
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
type Eval (Difference xs ys :: [Type] -> Type) Source # | |
Defined in Composite.Fcf type Eval (Difference xs ys :: [Type] -> Type) = Eval (ToComposite =<< Difference (Eval (FromComposite xs)) (Eval (FromComposite ys))) |
data Intersection :: [Type] -> [Type] -> Exp [Type] Source #
Intersection
Since: 0.1.0.0
Instances
type Eval (Intersection xs ys :: [Type] -> Type) Source # | |
Defined in Composite.Fcf type Eval (Intersection xs ys :: [Type] -> Type) = Eval (ToComposite =<< Intersection (Eval (FromComposite xs)) (Eval (FromComposite ys))) |
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