| Copyright | (c) 2011 Patrick Bahr | 
|---|---|
| License | BSD3 | 
| Maintainer | Patrick Bahr <paba@diku.dk> | 
| Stability | experimental | 
| Portability | non-portable (GHC Extensions) | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Data.Comp.Multi.Ops
Description
This module provides operators on higher-order functors. All definitions are generalised versions of those in Data.Comp.Ops.
- data (f :+: g) h e
 - caseH :: (f a b -> c) -> (g a b -> c) -> (f :+: g) a b -> c
 - type family Elem (f :: (* -> *) -> * -> *) (g :: (* -> *) -> * -> *) :: Emb where ...
 - class Subsume e f g where
 - type (:<:) f g = Subsume (ComprEmb (Elem f g)) f g
 - inj :: forall f g a. f :<: g => f a :-> g a
 - proj :: forall f g a. f :<: g => NatM Maybe (g a) (f a)
 - type (:=:) f g = (f :<: g, g :<: f)
 - spl :: f :=: (f1 :+: f2) => (f1 a :-> b) -> (f2 a :-> b) -> f a :-> b
 - data (f :&: a) g e = (f g e) :&: a
 - class DistAnn s p s' | s' -> s, s' -> p where
 - class RemA s s' | s -> s' where
 - data (f :*: g) a = (f a) :*: (g a)
 - ffst :: (f :*: g) a -> f a
 - fsnd :: (f :*: g) a -> g a
 
Documentation
data (f :+: g) h e infixr 6 Source #
Data type defining coproducts.
Instances
| (HFunctor f, HFunctor g) => HFunctor ((:+:) * f g) Source # | |
| (HFoldable f, HFoldable g) => HFoldable ((:+:) * f g) Source # | |
| (HTraversable f, HTraversable g) => HTraversable ((:+:) * f g) Source # | |
| (EqHF f, EqHF g) => EqHF ((:+:) * f g) Source # | 
  | 
| (OrdHF f, OrdHF g) => OrdHF ((:+:) * f g) Source # | 
  | 
| (Desugar f h, Desugar g h) => Desugar ((:+:) * f g) h Source # | |
| (HasVars f v0, HasVars g v0) => HasVars ((:+:) * f g) v0 Source # | |
| DistAnn s p s' => DistAnn ((:+:) * f s) p ((:+:) * ((:&:) * f p) s') Source # | |
| RemA s s' => RemA ((:+:) * ((:&:) * f p) s) ((:+:) * f s') Source # | |
caseH :: (f a b -> c) -> (g a b -> c) -> (f :+: g) a b -> c Source #
Utility function to case on a higher-order functor sum, without exposing the internal representation of sums.
type (:<:) f g = Subsume (ComprEmb (Elem f g)) f g infixl 5 Source #
A constraint f :<: g expresses that the signature f is
 subsumed by g, i.e. f can be used to construct elements in g.
data (f :&: a) g e infixr 7 Source #
This data type adds a constant product to a signature. Alternatively, this could have also been defined as
data (f :&: a) (g :: * -> *) e = f g e :&: a e
This is too general, however, for example for productHHom.
Constructors
| (f g e) :&: a infixr 7 | 
Instances
| DistAnn f p ((:&:) * f p) Source # | |
| HFunctor f => HFunctor ((:&:) * f a) Source # | |
| HFoldable f => HFoldable ((:&:) * f a) Source # | |
| HTraversable f => HTraversable ((:&:) * f a) Source # | |
| RemA ((:&:) * f p) f Source # | |
| DistAnn s p s' => DistAnn ((:+:) * f s) p ((:+:) * ((:&:) * f p) s') Source # | |
| RemA s s' => RemA ((:+:) * ((:&:) * f p) s) ((:+:) * f s') Source # | |
class DistAnn s p s' | s' -> s, s' -> p where Source #
This class defines how to distribute an annotation over a sum of signatures.