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

Pandora.Paradigm.Schemes.TU

Documentation

newtype TU ct cu t u a Source #

Constructors

TU ((t :. u) := a) 

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 #

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

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

sequence :: (Pointable u, Applicative u) => ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (u :. Tap ((List <:.:> List) := (:*:))) := a Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Tap ((List <:.:> List) := (:*:))) := a) -> (a -> u b) -> (u :. (v :. Tap ((List <:.:> List) := (:*:)))) := b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Tap ((List <:.:> List) := (:*:)))) := a) -> (a -> u b) -> (u :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Tap ((List <:.:> List) := (:*:)))))) := b 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 #

Focusable ('Root :: Type -> Location Type) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Focusing 'Root Rose a Source #

(forall a. Chain a) => Focusable ('Root :: Type -> Location Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Focusing 'Root Binary a Source #

Focusable ('Head :: Type -> Location Type) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Focusing 'Head List a Source #

Focusable ('Root :: Type -> Location Type) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Focusing 'Root (Construction List) a Source #

Focusable ('Head :: Type -> Location Type) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Focusing 'Head (Tap ((List <:.:> List) := (:*:))) 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 ('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) := (:*:)))) (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 (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 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) (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 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 ((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 k => Morphable ('Lookup ('Element :: 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 'Element) (Prefixed Rose k) :: 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 t => Hoistable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u => (u ~> v) -> TU Covariant Covariant t u ~> TU Covariant Covariant t v 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 Substructural 'Tail List :: Type -> Type Source #

Substructure ('Just :: a -> Maybe a) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Just Rose :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

Substructure ('Just :: a -> Maybe a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Just (Construction List) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

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

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

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

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

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

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

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

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

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

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

(<&&&&>) :: (Covariant u0, Covariant v, Covariant w) => (((t <:.> u) :. (u0 :. (v :. w))) := a) -> (a -> b) -> ((t <:.> u) :. (u0 :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

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

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

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

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

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

(Applicative t, Applicative u) => Applicative (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

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

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

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

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

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

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

(<****>) :: (Applicative u0, Applicative v, Applicative w) => (((t <:.> u) :. (u0 :. (v :. w))) := (a -> b)) -> (((t <:.> u) :. (u0 :. (v :. w))) := a) -> ((t <:.> u) :. (u0 :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

empty :: (t <:.> u) a Source #

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

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

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

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

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

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

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

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

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

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

(Extractable t, Extractable u) => Extractable (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

(Pointable t, Pointable u) => Pointable (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

pass :: (t <:.> u) () Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

(->>) :: (Pointable u0, Applicative u0) => (t <:.> u) a -> (a -> u0 b) -> (u0 :. (t <:.> u)) := b Source #

traverse :: (Pointable u0, Applicative u0) => (a -> u0 b) -> (t <:.> u) a -> (u0 :. (t <:.> u)) := b Source #

sequence :: (Pointable u0, Applicative u0) => (((t <:.> u) :. u0) := a) -> (u0 :. (t <:.> u)) := a Source #

(->>>) :: (Pointable u0, Applicative u0, Traversable v) => ((v :. (t <:.> u)) := a) -> (a -> u0 b) -> (u0 :. (v :. (t <:.> u))) := b Source #

(->>>>) :: (Pointable u0, Applicative u0, Traversable v, Traversable w) => ((w :. (v :. (t <:.> u))) := a) -> (a -> u0 b) -> (u0 :. (w :. (v :. (t <:.> u)))) := b Source #

(->>>>>) :: (Pointable u0, Applicative u0, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. (t <:.> u)))) := a) -> (a -> u0 b) -> (u0 :. (j :. (w :. (v :. (t <:.> u))))) := b Source #

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

Defined in Pandora.Paradigm.Schemes

Methods

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

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

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

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

eta :: a -> ((w <:.> u) :. (t <.:> v)) := a Source #

epsilon :: (((t <.:> v) :. (w <:.> u)) := a) -> a Source #

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

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

($$|-) :: (Covariant v0, Covariant w0) => ((v0 :. (w0 :. (t <.:> v))) := a) -> (a -> (w <:.> u) b) -> (v0 :. w0) := b Source #

($$$|-) :: (Covariant v0, Covariant w0, Covariant x) => ((v0 :. (w0 :. (x :. (t <.:> v)))) := a) -> (a -> (w <:.> u) b) -> (v0 :. (w0 :. x)) := b Source #

($$$$|-) :: (Covariant v0, Covariant w0, Covariant x, Covariant y) => ((v0 :. (w0 :. (x :. (y :. (t <.:> v))))) := a) -> (a -> (w <:.> u) b) -> (v0 :. (w0 :. (x :. y))) := b Source #

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

Defined in Pandora.Paradigm.Schemes

Methods

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

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

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

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

eta :: a -> ((w <.:> u) :. (v <:.> t)) := a Source #

epsilon :: (((v <:.> t) :. (w <.:> u)) := a) -> a Source #

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

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

($$|-) :: (Covariant v0, Covariant w0) => ((v0 :. (w0 :. (v <:.> t))) := a) -> (a -> (w <.:> u) b) -> (v0 :. w0) := b Source #

($$$|-) :: (Covariant v0, Covariant w0, Covariant x) => ((v0 :. (w0 :. (x :. (v <:.> t)))) := a) -> (a -> (w <.:> u) b) -> (v0 :. (w0 :. x)) := b Source #

($$$$|-) :: (Covariant v0, Covariant w0, Covariant x, Covariant y) => ((v0 :. (w0 :. (x :. (y :. (v <:.> t))))) := a) -> (a -> (w <.:> u) b) -> (v0 :. (w0 :. (x :. y))) := b Source #

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

Defined in Pandora.Paradigm.Schemes

Methods

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

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

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

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

eta :: a -> ((u <:.> w) :. (v <:.> t)) := a Source #

epsilon :: (((v <:.> t) :. (u <:.> w)) := a) -> a Source #

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

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

($$|-) :: (Covariant v0, Covariant w0) => ((v0 :. (w0 :. (v <:.> t))) := a) -> (a -> (u <:.> w) b) -> (v0 :. w0) := b Source #

($$$|-) :: (Covariant v0, Covariant w0, Covariant x) => ((v0 :. (w0 :. (x :. (v <:.> t)))) := a) -> (a -> (u <:.> w) b) -> (v0 :. (w0 :. x)) := b Source #

($$$$|-) :: (Covariant v0, Covariant w0, Covariant x, Covariant y) => ((v0 :. (w0 :. (x :. (y :. (v <:.> t))))) := a) -> (a -> (u <:.> w) b) -> (v0 :. (w0 :. (x :. y))) := b Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

Interpreted (TU ct cu t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Associated Types

type Primary (TU ct cu t u) a Source #

Methods

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

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

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

(=||) :: Interpreted u0 => (TU ct cu t u a -> u0 b) -> Primary (TU ct cu t u) a -> Primary u0 b 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 Zipper 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 Focusing ('Root :: Type -> Location Type) Rose a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Focusing ('Root :: Type -> Location Type) Rose a = Maybe a
type Focusing ('Root :: Type -> Location Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Focusing ('Root :: Type -> Location Type) Binary a = Maybe a
type Focusing ('Head :: Type -> Location Type) List a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Focusing ('Head :: Type -> Location Type) List a = Maybe a
type Focusing ('Root :: Type -> Location Type) (Construction List) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Focusing ('Root :: Type -> Location Type) (Construction List) a = a
type Focusing ('Head :: Type -> Location Type) (Tap ((List <:.:> List) := (:*:))) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Focusing ('Head :: Type -> Location Type) (Tap ((List <:.:> List) := (:*:))) a = a
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 ('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) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) 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 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) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.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 ((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 <:.> Zipper 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 <:.> Zipper List
type Morphing ('Lookup ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Lookup ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((->) (Nonempty List k) :: Type -> Type) <:.> Maybe
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 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 Substructural ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Tail :: a -> Segment a) List = List
type Substructural ('Just :: a -> Maybe a) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substructural ('Left :: a -> Wye a) Binary = Binary
type Substructural ('Just :: a -> Maybe a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Primary (TU ct cu t u) a Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

type Primary (TU ct cu t u) a = (t :. u) := a