pandora-0.3.3: 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
Insertable Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

insert :: a -> Stack a -> Stack a Source #

(forall a. Chain a) => Insertable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Methods

insert :: a -> Binary a -> Binary a Source #

Extendable (Tap (Delta <:.> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Methods

(=>>) :: Tap (Delta <:.> Stream) a -> (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) b Source #

(<<=) :: (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) a -> Tap (Delta <:.> Stream) b Source #

extend :: (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) a -> Tap (Delta <:.> Stream) b Source #

duplicate :: Tap (Delta <:.> Stream) a -> (Tap (Delta <:.> Stream) :. Tap (Delta <:.> Stream)) := a Source #

(=<=) :: (Tap (Delta <:.> Stream) b -> c) -> (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) a -> c Source #

(=>=) :: (Tap (Delta <:.> Stream) a -> b) -> (Tap (Delta <:.> Stream) b -> c) -> Tap (Delta <:.> Stream) a -> c Source #

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

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

Semigroup (Stack a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

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

Monoid (Stack a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

zero :: Stack a Source #

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

Defined in Pandora.Paradigm.Structure.Stack

Methods

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

(/=) :: Stack a -> Stack a -> Boolean Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Left Binary a Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Right Binary a Source #

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

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural 'Just Rose a Source #

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

Defined in Pandora.Paradigm.Structure.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.Binary

Associated Types

type Focusing 'Root Binary a Source #

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

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Focusing 'Head Stack a Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Left (Tap (t <:.> u)) a Source #

Methods

substructure :: Tagged 'Left (Tap (t <:.> u) a) :-. Substructural 'Left (Tap (t <:.> u)) a Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right (Tap (t <:.> u)) a Source #

Substructure ('Just :: Type -> Maybe Type) (Construction Stack) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural 'Just (Construction Stack) a Source #

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

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Focusing 'Root (Construction Stack) a Source #

Rotatable ('Down ('Right :: a -> Wye a) :: Direction (a -> Wye a)) (Construction Wye <:.:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable ('Down ('Left :: a -> Wye a) :: Direction (a -> Wye a)) (Construction Wye <:.:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

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 #

Rotatable ('Right :: a -> Wye a) (Tap (Delta <:.> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Rotational 'Right (Tap (Delta <:.> Stream)) a Source #

Rotatable ('Left :: a -> Wye a) (Tap (Delta <:.> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Rotational 'Left (Tap (Delta <:.> Stream)) a Source #

Rotatable ('Right :: a -> Wye a) (Tap (Delta <:.> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Right (Tap (Delta <:.> Construction Maybe)) a Source #

Rotatable ('Left :: a -> Wye a) (Tap (Delta <:.> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Left (Tap (Delta <:.> Construction Maybe)) a Source #

Rotatable ('Right :: a -> Wye a) (Tap (Delta <:.> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Right (Tap (Delta <:.> Stack)) a Source #

Rotatable ('Left :: a -> Wye a) (Tap (Delta <:.> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Left (Tap (Delta <:.> Stack)) a Source #

Rotatable ('Up :: a -> Direction a) (Construction Wye <:.:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

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

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

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

loeb :: ((->) e <:.> u) (a <-| ((->) e <:.> u)) -> ((->) e <:.> u) a Source #

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

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

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

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

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

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

loeb :: ((:*:) e <:.> u) (a <-| ((:*:) e <:.> u)) -> ((:*:) e <:.> u) a Source #

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

empty :: (t <:.> Construction 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 => (((:*:) e <:.> u) a -> b) -> ((u0 :. ((:*:) e <:.> u)) := a) -> (u0 :. ((:*:) e <:.> u)) := b Source #

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

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

point :: a |-> ((->) e <:.> u) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

point :: a |-> (t <:.> Construction u) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

extract :: a <-| ((:*:) e <:.> u) Source #

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

Defined in Pandora.Paradigm.Structure.Stack

Methods

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

resolve :: (a -> r) -> r -> ((Maybe <:.> Construction Maybe) := a) -> r 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 (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 (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 #

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 #

type Nonempty Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Nonempty Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Zipper Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

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

Defined in Pandora.Paradigm.Structure.Binary

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

Defined in Pandora.Paradigm.Structure.Binary

type Substructural ('Right :: Type -> Wye Type) Binary a = Binary a
type Substructural ('Just :: Type -> Maybe Type) Rose a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Substructural ('Just :: Type -> Maybe Type) Rose a = (Stack :. Construction Stack) := a
type Focusing ('Root :: Type -> Location Type) Rose a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.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.Binary

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

Defined in Pandora.Paradigm.Structure.Stack

type Focusing ('Head :: Type -> Location Type) Stack a = Maybe a
type Substructural ('Left :: Type -> Wye Type) (Tap (t <:.> u)) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure

type Substructural ('Right :: Type -> Wye Type) (Tap (t <:.> u)) a = Substructural ('Right :: Type -> Wye Type) t (u a)
type Substructural ('Just :: Type -> Maybe Type) (Construction Stack) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Focusing ('Root :: Type -> Location Type) (Construction Stack) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Focusing ('Root :: Type -> Location Type) (Construction Stack) a = a
type Rotational ('Down ('Right :: a1 -> Wye a1) :: Direction (a1 -> Wye a1)) (Construction Wye <:.:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Down ('Left :: a1 -> Wye a1) :: Direction (a1 -> Wye a1)) (Construction Wye <:.:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 = Tap (Delta <:.> Stream) a2
type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 = Tap (Delta <:.> Stream) a2
type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Construction Maybe)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Construction Maybe)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 = (Maybe :. Zipper Stack) := a2
type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 = (Maybe :. Zipper Stack) := a2
type Rotational ('Up :: a1 -> Direction a1) (Construction Wye <:.:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

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