pandora-0.4.5: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Paradigm.Schemes.T_U

Documentation

newtype T_U ct cu p t u a Source #

Constructors

T_U (p (t a) (u a)) 

Instances

Instances details
Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (Tap ((t <:.:> t) := (:*:)) :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

multiply_ :: forall (a :: k) (b :: k). (Tap ((t <:.:> t) := (:*:)) a :*: Tap ((t <:.:> t) := (:*:)) b) -> Tap ((t <:.:> t) := (:*:)) (a :*: b) Source #

Semimonoidal (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Extendable (Tap ((Stream <:.:> Stream) := (:*:))) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List :: Type -> Type Source #

Morphable ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) :: Type -> Type Source #

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (Tap ((t <:.:> t) := (:*:))) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Tap ((t <:.:> t) := (:*:)) a -> u (Tap ((t <:.:> t) := (:*:)) b) Source #

Traversable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Tap ((List <:.:> List) := (:*:)) a -> u (Tap ((List <:.:> List) := (:*:)) b) Source #

Morphable ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal ((t <:.:> t) := (:*:) :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

multiply_ :: forall (a :: k) (b :: k). (((t <:.:> t) := (:*:)) a :*: ((t <:.:> t) := (:*:)) b) -> ((t <:.:> t) := (:*:)) (a :*: b) Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

type Available 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

type Substance 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

type Available 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

type Substance 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

type Available 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

type Substance 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Right ((t <:.:> t) := (:*:)) :: Type -> Type Source #

type Substance 'Right ((t <:.:> t) := (:*:)) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Left ((t <:.:> t) := (:*:)) :: Type -> Type Source #

type Substance 'Left ((t <:.:> t) := (:*:)) :: Type -> Type Source #

(Divariant p ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Contravariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant ((t >:.:> u) := p) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

(-<$>-) :: (a -> b) -> ((t >:.:> u) := p) a -> ((t >:.:> u) := p) b Source #

(forall i. Covariant (p i) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bivariant p ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant ((t <:.:> u) := p) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

(-<$>-) :: (a -> b) -> ((t <:.:> u) := p) a -> ((t <:.:> u) := p) b Source #

(forall i. Covariant (p i) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bivariant p ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Contravariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Contravariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Contravariant ((t >:.:< u) := p) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

(->$<-) :: (a -> b) -> ((t >:.:< u) := p) b -> ((t >:.:< u) := p) a Source #

Interpreted (T_U ct cu p t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Associated Types

type Primary (T_U ct cu p t u) a Source #

Methods

run :: T_U ct cu p t u a -> Primary (T_U ct cu p t u) a Source #

unite :: Primary (T_U ct cu p t u) a -> T_U ct cu p t u a Source #

(||=) :: Interpreted u0 => (Primary (T_U ct cu p t u) a -> Primary u0 b) -> T_U ct cu p t u a -> u0 b Source #

(=||) :: Interpreted u0 => (T_U ct cu p t u a -> u0 b) -> Primary (T_U ct cu p t u) a -> Primary u0 b Source #

(<$||=) :: (Covariant j (->) (->), Interpreted u0) => (Primary (T_U ct cu p t u) a -> Primary u0 b) -> (j := T_U ct cu p t u a) -> j := u0 b Source #

(<$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u0) => (Primary (T_U ct cu p t u) a -> Primary u0 b) -> ((j :. k) := T_U ct cu p t u a) -> (j :. k) := u0 b Source #

(<$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u0) => (Primary (T_U ct cu p t u) a -> Primary u0 b) -> ((j :. (k :. l)) := T_U ct cu p t u a) -> (j :. (k :. l)) := u0 b Source #

(<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u0) => (Primary (T_U ct cu p t u) a -> Primary u0 b) -> ((j :. (k :. (l :. m))) := T_U ct cu p t u a) -> (j :. (k :. (l :. m))) := u0 b Source #

(=||$>) :: (Covariant j (->) (->), Interpreted u0) => (T_U ct cu p t u a -> u0 b) -> (j := Primary (T_U ct cu p t u) a) -> j := Primary u0 b Source #

(=||$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u0) => (T_U ct cu p t u a -> u0 b) -> ((j :. k) := Primary (T_U ct cu p t u) a) -> (j :. k) := Primary u0 b Source #

(=||$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u0) => (T_U ct cu p t u a -> u0 b) -> ((j :. (k :. l)) := Primary (T_U ct cu p t u) a) -> (j :. (k :. l)) := Primary u0 b Source #

(=||$$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u0) => (T_U ct cu p t u a -> u0 b) -> ((j :. (k :. (l :. m))) := Primary (T_U ct cu p t u) a) -> (j :. (k :. (l :. m))) := Primary u0 b Source #

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) = Maybe <:.> Tap ((List <:.:> List) := (:*:))
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) = Maybe <:.> Tap ((List <:.:> List) := (:*:))
type Morphing ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = t
type Substance ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = t
type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) = Identity
type Available ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) = Identity
type Substance ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) = t
type Substance ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) = t
type Primary (T_U ct cu p t u) a Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

type Primary (T_U ct cu p t u) a = p (t a) (u a)

type (<:.:>) t u p = T_U Covariant Covariant p t u infixr 2 Source #

type (>:.:>) t u p = T_U Contravariant Covariant p t u infixr 2 Source #

type (<:.:<) t u p = T_U Covariant Contravariant p t u infixr 2 Source #

type (>:.:<) t u p = T_U Contravariant Contravariant p t u infixr 2 Source #