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

Pandora.Paradigm.Schemes.T_U

Documentation

newtype T_U ct cu p t u a Source #

Constructors

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

Instances

Instances details
Zippable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Breadcrumbs Binary :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

Semimonoidal (<--) (:*:) (:*:) t => Monoidal (<--) (-->) (:*:) (:*:) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Interface.Zipper

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Structure.Interface.Zipper

Methods

mult :: forall (a :: k) (b :: k). ((Exactly <:*:> t) a :*: (Exactly <:*:> t) b) <-- (Exactly <:*:> t) (a :*: b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Impliable (Tape t a :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Arguments (Tape t a) = (args :: Type) Source #

Methods

imply :: Arguments (Tape t a) Source #

Morphable ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into Binary) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tape Stream) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tape Stream) :: Type -> Type Source #

Slidable ('Right ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Sliding ('Right 'Zig) (Construction (Maybe <:*:> Maybe)) :: 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.Structure

Associated Types

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

Substructure ('Right ('Tree :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Substructure ('Left ('Tree :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Substructure ('Focused ('Forest :: a -> Segment a) :: Location (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Focused 'Forest) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Substructure ('Focused ('Tree :: a -> Segment a) :: Location (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Focused 'Tree) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Substructure ('Focused ('Tree :: a -> Segment a) :: Location (a -> Segment a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Slidable ('Down ('Right :: a -> Horizontal a) :: Vertical (a -> Horizontal a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Slidable ('Down ('Left :: a -> Horizontal a) :: Vertical (a -> Horizontal a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Morphable ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Turnover < Tape List) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Turnover < Tape List) :: Type -> Type Source #

Chain key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance ('All 'Right) (Tape t <::> Tape t) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance ('All 'Left) (Tape t <::> Tape t) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (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 :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Horizontal (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 :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (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 :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (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 :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (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 :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (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 #

Slidable (('Right :: (a -> Splay a) -> Horizontal (a -> Splay a)) > ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Methods

slide :: ((State < Binary e) :> Sliding ('Right > 'Zig) Binary) >>> () Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Comprehension Maybe) (Tape List) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Tape List) (Construction Maybe) :: Type -> Type Source #

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate > ('Right > 'Zig 'Zag)) (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate > ('Left > 'Zig 'Zag)) (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Construction Maybe) (Tape > Construction Maybe) :: Type -> Type Source #

Extendable ((->) :: Type -> Type -> Type) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Methods

(<<=) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<==) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<===) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<====) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<=====) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<======) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<=======) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<========) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Stack structure, Bindable ((->) :: Type -> Type -> Type) (Topping structure), Monoidal (-->) (-->) (:*:) (:*:) (Topping structure)) => Slidable ('Left :: a -> Horizontal a) (Tape structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Sliding 'Left (Tape structure) :: Type -> Type Source #

Methods

slide :: ((State < Tape structure e) :> Sliding 'Left (Tape structure)) >>> () Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Bindable ((->) :: Type -> Type -> Type) (Topping structure), Monoidal (-->) (-->) (:*:) (:*:) (Topping structure), Stack structure) => Slidable ('Right :: a -> Horizontal a) (Tape structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Sliding 'Right (Tape structure) :: Type -> Type Source #

Methods

slide :: ((State < Tape structure e) :> Sliding 'Right (Tape structure)) >>> () Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Substructure ('Right :: a -> Horizontal a) (t <:*:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Substructure ('Left :: a -> Horizontal a) (t <:*:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Rest (Exactly <:*:> t) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Root (Exactly <:*:> t) :: Type -> Type Source #

Substructure ('Siblings :: a -> Segment a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance 'Siblings (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Substructure ('Children :: a -> Segment a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance 'Children (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Substructure ('Ancestors :: a -> Segment a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance 'Ancestors (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Substructure ('Ancestors :: a -> Segment a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Substructure ('Children :: a -> Segment a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Slidable ('Down :: a -> Vertical a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Down (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Right :: a -> Horizontal a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Right (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Left :: a -> Horizontal a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Left (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Up :: a -> Vertical a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Up (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Up :: a -> Vertical a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance 'Down (Tape t <::> Tape t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Up :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance 'Up (Tape t <::> Tape t) :: Type -> Type Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<-/-) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<-/-------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<-/------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<-/-----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<-/----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<-/---) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<-/--) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List 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.Algebraic

Methods

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

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

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

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

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

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

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

(Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, forall a. Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (p (t a)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, forall b. Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip p (u b))) => 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 #

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

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

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

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

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

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

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

(<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|--) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|---) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|----) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|-----) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|------) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|-------) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) >>>>>> p)) => (a -> b) -> ((t >:.:> u) >>>>>> p) (u0 a) -> ((t >:.:> u) >>>>>> p) (u0 b) Source #

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

(forall i. Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (p i), forall o. Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip p o), 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 #

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

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

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

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

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

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

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

(<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|--) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|---) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|----) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|-----) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|------) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

(<-|-|-------) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t <:.:> u) >>>>>> p)) => (a -> b) -> ((t <:.:> u) >>>>>> p) (u0 a) -> ((t <:.:> u) >>>>>> p) (u0 b) Source #

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

Interpreted ((->) :: Type -> Type -> Type) (T_U ct cu p t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Associated Types

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

type Breadcrumbs Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Arguments (Tape t a :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Arguments (Tape t a :: Type) = a -> t a -> t a -> Tape t a
type Sliding ('Right ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Sliding ('Right ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) Binary = Maybe
type Morphing ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) = Tape Stream
type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) = Tape Stream
type Sliding ('Right ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Sliding ('Right ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) (Construction (Maybe <:*:> Maybe)) = Maybe
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.Structure

type Substance ('Right ('Tree :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left ('Tree :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Focused ('Forest :: a -> Segment a) :: Location (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Focused ('Tree :: a -> Segment a) :: Location (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Focused ('Tree :: a -> Segment a) :: Location (a -> Segment a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Sliding ('Down ('Right :: a -> Horizontal a) :: Vertical (a -> Horizontal a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Sliding ('Down ('Left :: a -> Horizontal a) :: Vertical (a -> Horizontal a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) = ((->) key :: Type -> Type) <::> Maybe
type Substance ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) = Tape t <::> t
type Substance ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) = Tape t <::> Reverse t
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List = Maybe <::> Tape List
type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) Binary = Binary
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) = Comprehension Maybe
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) = Tape List
type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) = Binary
type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) = Binary
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) = Construction Maybe
type Sliding ('Left :: a -> Horizontal a) (Tape structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Sliding ('Left :: a -> Horizontal a) (Tape structure) = Topping structure
type Sliding ('Right :: a -> Horizontal a) (Tape structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Sliding ('Right :: a -> Horizontal a) (Tape structure) = Topping structure
type Substance ('Right :: a -> Horizontal a) (t <:*:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

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

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Left :: a -> Horizontal a) (t <:*:> u) = t
type Substance ('Rest :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Rest :: a -> Segment a) (Exactly <:*:> t) = t
type Substance ('Root :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Root :: a -> Segment a) (Exactly <:*:> t) = Exactly
type Substance ('Siblings :: a -> Segment a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Children :: a -> Segment a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Ancestors :: a -> Segment a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Ancestors :: a -> Segment a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Children :: a -> Segment a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Sliding ('Down :: a -> Vertical a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Sliding ('Right :: a -> Horizontal a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Sliding ('Left :: a -> Horizontal a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Sliding ('Up :: a -> Vertical a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Sliding ('Up :: a -> Vertical a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('Down :: a -> Vertical a) (Tape t <::> Tape t) = Reverse t <::> Tape t
type Substance ('Up :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('Up :: a -> Vertical a) (Tape t <::> Tape t) = t <::> Tape t
type Primary (T_U ct cu p t u) a Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

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

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

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

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

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