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

Pandora.Pattern.Functor.Covariant

Synopsis

Documentation

class (Semigroupoid source, Semigroupoid target) => Covariant source target t where Source #

When providing a new instance, you should ensure it satisfies:
* Identity morphism: (identity -<$>-) ≡ identity
* Interpreted of morphisms: (f . g -<$>-) ≡ (f -<$>-) . (g -<$>-)

Methods

(-<$>-) :: source a b -> target (t a) (t b) infixl 4 Source #

Instances

Instances details
Stack List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Measurable 'Length List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Measural 'Length List a Source #

Measurable 'Heighth Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Measural 'Heighth Binary a Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal (<--) (:*:) (:*:) t, Semimonoidal (<--) (:*:) (:*:) t', Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t t') => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) <-- ((t <:<.>:> t') := u) a Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) <-- (t <.:> u) a Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) <-- (t <:.> u) a Source #

Monotonic a ((t :. Construction t) := a) => Monotonic a ((t <:.> Construction t) := a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

reduce :: (a -> r -> r) -> r -> ((t <:.> Construction t) := a) -> r Source #

resolve :: (a -> r) -> r -> ((t <:.> Construction t) := a) -> r Source #

Semigroup (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(+) :: List a -> List a -> List a Source #

Monoid (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

zero :: List a Source #

Setoid a => Setoid (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(==) :: List a -> List a -> Boolean Source #

(!=) :: List a -> List a -> Boolean Source #

Nullable List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

null :: forall (a :: k). (Predicate :. List) := a Source #

Nullable Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Methods

null :: forall (a :: k). (Predicate :. Rose) := a Source #

Nullable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Methods

null :: forall (a :: k). (Predicate :. Binary) := a Source #

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

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

multiply :: forall (a :: k) (b :: k). ((t <.:> u) a :*: (t <.:> u) b) <-- (t <.:> u) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

multiply :: forall (a :: k) (b :: k). ((t <:.> u) a :*: (t <:.> u) b) <-- (t <:.> u) (a :*: b) Source #

(Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

catch :: forall (a :: k). (Conclusion e <.:> u) a -> (e -> (Conclusion e <.:> u) a) -> (Conclusion e <.:> u) a 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 ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'All) List :: Type -> Type Source #

Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'First) List :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) List :: Type -> Type Source #

Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into (o ds)) Binary :: Type -> Type Source #

Methods

morphing :: (Tagged ('Into (o ds)) <:.> Binary) ~> Morphing ('Into (o ds)) Binary Source #

Morphable ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right 'Zig)) Binary :: Type -> Type Source #

Morphable ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left 'Zig)) Binary :: Type -> Type Source #

Morphable ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right ('Zig 'Zag))) Binary :: Type -> Type Source #

Morphable ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left ('Zig 'Zag))) Binary :: Type -> Type Source #

Morphable ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right ('Zig 'Zig))) Binary :: Type -> Type Source #

Morphable ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left ('Zig 'Zig))) Binary :: Type -> Type Source #

Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (Tap ((t <:.:> t) := (:*:)) :: 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 #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

multiply :: forall (a :: k) (b :: k). ((t <:.> u) a :*: (t <:.> u) b) -> (t <:.> u) (a :+: b) Source #

Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:.:> t) := (:*:) :: 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t') => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

multiply :: forall (a :: k) (b :: k). ((t <.:> u) a :*: (t <.:> u) b) -> (t <.:> u) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

multiply :: forall (a :: k) (b :: k). ((t <:.> u) a :*: (t <:.> u) b) -> (t <:.> u) (a :*: b) 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) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (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 ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Associated Types

type Morphing ('Into List) (Vector r) :: Type -> Type Source #

Morphable ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (Construction Wye) :: 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 #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed List key) :: Type -> Type Source #

Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Rose k) :: Type -> Type Source #

Chain k => Morphable ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Vary 'Element) (Prefixed Binary k) :: Type -> Type Source #

Chain k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Binary k) :: Type -> Type 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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Hoistable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

(/|\) :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant (->) (->) u => (u ~> v) -> TU Covariant Covariant t u ~> TU Covariant Covariant t v Source #

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant (->) (->) u => (u ~> v) -> TU Covariant Covariant t u ~> TU Covariant Covariant t v Source #

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable ((->) :: Type -> Type -> Type) (Tap ((List <:.:> List) := (:*:))) 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 ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Pop List :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Push List :: Type -> Type Source #

Morphable ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing 'Insert Binary :: Type -> Type Source #

Substructure ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Tail List :: Type -> Type Source #

type Substance 'Tail List :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Root List :: Type -> Type Source #

type Substance 'Root List :: Type -> Type Source #

Substructure ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Right Binary :: Type -> Type Source #

type Substance 'Right Binary :: Type -> Type Source #

Substructure ('Left :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Left Binary :: Type -> Type Source #

type Substance 'Left Binary :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => 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 #

Substructure ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Available 'Tail (Construction List) :: Type -> Type Source #

type Substance 'Tail (Construction List) :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Available 'Root (Construction List) :: Type -> Type Source #

type Substance 'Root (Construction List) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => 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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

(-<$>-) :: (a -> b) -> Wye a -> Wye b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(-<$>-) :: (a -> b) -> Identity a -> Identity b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Edges Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Edges

Methods

(-<$>-) :: (a -> b) -> Edges a -> Edges b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(-<$>-) :: (a -> b) -> Maybe a -> Maybe b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Biforked Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Methods

(-<$>-) :: (a -> b) -> Biforked a -> Biforked b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

unit :: Proxy (:*:) -> (Unit (:+:) -> a) -> (t <:.> u) a Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t', Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) -> ((t <:<.>:> t') := u) a Source #

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) -> (t <.:> u) a Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) -> (t <:.> u) a Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

(-<$>-) :: (a -> b) -> Proxy a -> Proxy b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:+:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Sum

Methods

(-<$>-) :: (a -> b) -> (s :+: a) -> (s :+: b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

(-<$>-) :: (a -> b) -> Yoneda t a -> Yoneda t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Outline t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

(-<$>-) :: (a -> b) -> Outline t a -> Outline t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:*:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(-<$>-) :: (a -> b) -> (s :*: a) -> (s :*: b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Jet t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jet

Methods

(-<$>-) :: (a -> b) -> Jet t a -> Jet t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Jack t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(-<$>-) :: (a -> b) -> Jack t a -> Jack t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Wedge e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wedge

Methods

(-<$>-) :: (a -> b) -> Wedge e a -> Wedge e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Validation e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

(-<$>-) :: (a -> b) -> Validation e a -> Validation e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (These e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.These

Methods

(-<$>-) :: (a -> b) -> These e a -> These e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

(-<$>-) :: (a -> b) -> Instruction t a -> Instruction t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(-<$>-) :: (a -> b) -> Construction t a -> Construction t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(-<$>-) :: (a -> b) -> Conclusion e a -> Conclusion e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <:.> Construction t) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

(-<$>-) :: (a -> b) -> Comprehension t a -> Comprehension t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

Methods

(-<$>-) :: (a -> b) -> Store s a -> Store s b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(-<$>-) :: (a -> b) -> Tap t a -> Tap t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

(-<$>-) :: (a -> b) -> State s a -> State s b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(-<$>-) :: (a -> b) -> Imprint e a -> Imprint e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Equipment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

(-<$>-) :: (a -> b) -> Equipment e a -> Equipment e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

(-<$>-) :: (a -> b) -> Environment e a -> Environment e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

(-<$>-) :: (a -> b) -> Accumulator e a -> Accumulator e b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (Constant :: Type -> Type -> Type) b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Constant

Methods

(-<$>-) :: (a -> b0) -> Flip Constant b a -> Flip Constant b b0 Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (:+:) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Sum

Methods

(-<$>-) :: (a0 -> b) -> Flip (:+:) a a0 -> Flip (:+:) a b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (:*:) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(-<$>-) :: (a0 -> b) -> Flip (:*:) a a0 -> Flip (:*:) a b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Validation a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

(-<$>-) :: (a0 -> b) -> Flip Validation a a0 -> Flip Validation a b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (Tagged :: Type -> Type -> Type) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(-<$>-) :: (a0 -> b) -> Flip Tagged a a0 -> Flip Tagged a b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(-<$>-) :: (a -> b) -> Flip Conclusion e a -> Flip Conclusion e b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Constant a :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Constant

Methods

(-<$>-) :: (a0 -> b) -> Constant a a0 -> Constant a b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Day t u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Day

Methods

(-<$>-) :: (a -> b) -> Day t u a -> Day t u b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(-<$>-) :: (a -> b) -> Tagged tag a -> Tagged tag b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :> u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Methods

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

(-<$>-) :: (a -> b) -> Backwards t a -> Backwards t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

(-<$>-) :: (a -> b) -> Reverse t a -> Reverse t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :< u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Methods

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Methods

(-<$>-) :: (a -> b) -> Prefixed t k a -> Prefixed t k b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) a :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

(-<$>-) :: (a0 -> b) -> (a -> a0) -> (a -> b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

(-<$>-) :: (a -> b) -> Continuation r t a -> Continuation r t b Source #

(Divariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) p, Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t >:.:> u) := p) 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (p i), Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) p, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:.:> u) := p) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

(<<-) :: (Covariant (->) (->) u0, Monoidal (->) (->) (:*:) (:*:) u0) => (a -> u0 b) -> (t <:.> u) a -> u0 ((t <:.> u) b) Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <:.> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v) (w <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((t <.:> v) a -> b) -> a -> (w <:.> u) b Source #

(|-) :: (a -> (w <:.> u) b) -> (t <.:> v) a -> b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <.:> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v) (w <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((t <.:> v) a -> b) -> a -> (w <.:> u) b Source #

(|-) :: (a -> (w <.:> u) b) -> (t <.:> v) a -> b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <.:> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t) (w <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((v <:.> t) a -> b) -> a -> (w <.:> u) b Source #

(|-) :: (a -> (w <.:> u) b) -> (v <:.> t) a -> b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (u <:.> w), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t) (u <:.> w) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((v <:.> t) a -> b) -> a -> (u <:.> w) b Source #

(|-) :: (a -> (u <:.> w) b) -> (v <:.> t) a -> b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Kan ('Right :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Methods

(-<$>-) :: (a -> b0) -> Kan 'Right t u b a -> Kan 'Right t u b b0 Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:<.>:> u) t'), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((v <:<.>:> w) v'), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t w, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' v', Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t v, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u v, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v' t') => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:<.>:> u) t') ((v <:<.>:> w) v') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((t <:<.>:> u) t' a -> b) -> a -> (v <:<.>:> w) v' b Source #

(|-) :: (a -> (v <:<.>:> w) v' b) -> (t <:<.>:> u) t' a -> b Source #

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) ((t' <:<.>:> t) := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

(Semigroup e, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) (((->) e :: Type -> Type) <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(<<=) :: (((->) e <.:> u) a -> b) -> ((->) e <.:> u) a -> ((->) e <.:> u) b Source #

Extendable ((->) :: Type -> Type -> Type) u => Extendable ((->) :: Type -> Type -> Type) ((:*:) e <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

(<<=) :: (((:*:) e <:.> u) a -> b) -> ((:*:) e <:.> u) a -> ((:*:) e <:.> u) b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Bindable ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Bindable ((->) :: Type -> Type -> Type) t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t) => Liftable ((->) :: Type -> Type -> Type) (t <:<.>:> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lift :: Covariant (->) (->) u => u a -> (t <:<.>:> t') u a Source #

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t t', Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t') => Lowerable ((->) :: Type -> Type -> Type) (t <:<.>:> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lower :: Covariant (->) (->) u => (t <:<.>:> t') u a -> u a Source #

Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Liftable ((->) :: Type -> Type -> Type) (UT Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

lift :: Covariant (->) (->) u => u a -> UT Covariant Covariant t u a Source #

Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Liftable ((->) :: Type -> Type -> Type) (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

lift :: Covariant (->) (->) u => u a -> TU Covariant Covariant t u a Source #

Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Lowerable ((->) :: Type -> Type -> Type) (UT Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

lower :: Covariant (->) (->) u => UT Covariant Covariant t u a -> u a Source #

Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Lowerable ((->) :: Type -> Type -> Type) (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

lower :: Covariant (->) (->) u => TU Covariant Covariant t u a -> u a Source #

type Nonempty List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Nonempty Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Combinative List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Measural 'Length List a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Measural 'Heighth Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List = (Predicate <:.:> Maybe) := ((->) :: Type -> Type -> Type)
type Morphing ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into (o ds) :: Morph a) Binary = Maybe <:.> Morphing ('Into (o ds)) (Construction Wye)
type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary = Binary
type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary = Binary
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
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) (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 ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

type Morphing ('Into List) (Vector r) = List
type Morphing ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((->) (Nonempty List k) :: Type -> Type) <:.> Maybe
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = (((:*:) k <:.> Identity) <:.:> Prefixed Binary k) := ((->) :: Type -> Type -> Type)
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = ((->) k :: Type -> Type) <:.> Maybe
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 Zipper List (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Zipper List (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) = Tap ((List <:.:> List) := (:*:))
type Morphing ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Pop :: a -> Morph a) List = List
type Morphing ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Push :: a -> Morph a) List = (Identity <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) Binary = (((Identity <:.:> Comparison) := (:*:)) <:.:> Binary) := ((->) :: Type -> Type -> Type)
type Available ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Tail :: a -> Segment a) List = Identity
type Available ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Root :: a -> Segment a) List = Maybe
type Available ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Right :: a -> Wye a) Binary = Maybe
type Available ('Left :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Left :: a -> Wye a) Binary = Maybe
type Substance ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Tail :: a -> Segment a) List = List
type Substance ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Root :: a -> Segment a) List = Identity
type Substance ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left :: a -> Wye a) Binary = Construction Wye
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 Available ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Available ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

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 Substance ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

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

(-<$$>-) :: forall t u category a b. (Covariant category category u, Covariant category category t) => category a b -> category (t (u a)) (t (u b)) Source #

(-<<$$>-) :: forall t u source target a b. (Covariant source source u, Covariant source target t) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #

(-<$$>>-) :: forall source target t u a b. (Covariant source target u, Covariant target target t) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #

(-<$$$>-) :: forall t u v category a b. (Covariant category category t, Covariant category category u, Covariant category category v) => category a b -> category (t (u (v a))) (t (u (v b))) Source #

(-<$$$$>-) :: forall category t u v w a b. (Covariant category category t, Covariant category category u, Covariant category category v, Covariant category category w) => category a b -> category (t (u (v (w a)))) (t (u (v (w b)))) Source #