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

Pandora.Paradigm.Schemes.TT

Documentation

newtype TT ct ct' t t' a Source #

Constructors

TT ((t :. t') := a) 

Instances

Instances details
Zippable List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs List :: Type -> Type Source #

Stack List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Topping List :: Type -> Type Source #

type Popping List :: Type -> Type Source #

type Pushing List :: Type -> Type Source #

Methods

top :: Lens (Topping List) (List e) e Source #

pop :: State (Popping List e) (Maybe e) Source #

push :: e -> State (Pushing List e) e Source #

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

(Semigroupoid m, Covariant m m t, Covariant (Betwixt m m) m t, Covariant m (Betwixt m m) t', Interpreted m (t <::> t')) => Covariant m m (t <::> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TT

Methods

(<-|-) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|--) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|---) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|----) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|-----) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|------) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|-------) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|--------) :: m a b -> m ((t <::> t') a) ((t <::> t') b) Source #

(<-|-|-) :: (Covariant m (Betwixt m m) u, Covariant (Betwixt m m) m (t <::> t')) => m a b -> m ((t <::> t') (u a)) ((t <::> t') (u b)) Source #

(<-|-|-|-) :: (Covariant m (Betwixt m (Betwixt m m)) v, Covariant (Betwixt m (Betwixt m m)) (Betwixt (Betwixt m m) m) u, Covariant (Betwixt (Betwixt m m) m) m (t <::> t')) => m a b -> m ((t <::> t') (u (v a))) ((t <::> t') (u (v b))) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

Semigroup (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

Monoid (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

zero :: List a Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

Morphable ('Into (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 ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Methods

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable ('Into (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 (Tape (Construction Maybe))) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (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 ('Into (Tape List)) (Tape (Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (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 ('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 ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tape List) :: 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 #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Turnover (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 -> Wye a) :: Morph (a -> Wye a)) (Turnover (Tape List)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). TT Covariant Covariant t u a -> TT Covariant Covariant t v a Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

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

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

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

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

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

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

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

(<<=========) :: (Tape List a -> b) -> Tape List a -> Tape List b 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 #

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 #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

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

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.Ability.Zipper

Associated Types

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

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.Ability.Zipper

Associated Types

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

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 #

(<<--------) :: (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) t') => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <::> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

Interpreted ((->) :: Type -> Type -> Type) (TT ct ct' t t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TT

Associated Types

type Primary (TT ct ct' t t') a Source #

Methods

run :: TT ct ct' t t' a -> Primary (TT ct ct' t t') a Source #

unite :: Primary (TT ct ct' t t') a -> TT ct ct' t t' a Source #

(!) :: TT ct ct' t t' a -> Primary (TT ct ct' t t') a Source #

(=#-) :: (Semigroupoid (->), Interpreted (->) u) => (Primary (TT ct ct' t t') a -> Primary u b) -> TT ct ct' t t' a -> u b Source #

(-#=) :: (Semigroupoid (->), Interpreted (->) u) => (TT ct ct' t t' a -> u b) -> Primary (TT ct ct' t t') a -> Primary u b Source #

(<$=#-) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (Primary (TT ct ct' t t') a -> Primary u b) -> (j := TT ct ct' t t' a) -> (j := u b) Source #

(-#=$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (TT ct ct' t t' a -> u b) -> (j := Primary (TT ct ct' t t') a) -> (j := Primary u b) Source #

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 Combinative List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Breadcrumbs List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Topping List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Popping List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Pushing List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape List) = Maybe <::> Tape List
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 ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Turnover (Tape List)) = Turnover (Tape List)
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) Binary = (((Exactly <:.:> Comparison) := (:*:)) <:.:> Binary) := ((->) :: Type -> Type -> Type)
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 = (Exactly <:.:> List) := ((->) :: Type -> Type -> Type)
type Available ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.Rose

type Available ('Right :: a -> Wye a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Available ('Right :: a -> Wye a) (Tape t <::> Tape t) = Exactly
type Available ('Left :: a -> Wye a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Available ('Left :: a -> Wye a) (Tape t <::> Tape t) = Exactly
type Available ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Available ('Up :: a -> Vertical a) (Tape t <::> Tape t) = Exactly
type Substance ('Right :: a -> Wye a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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.Ability.Zipper

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

Defined in Pandora.Paradigm.Schemes.TT

type Primary (TT ct ct' t t') a = (t :. t') := a