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

Pandora.Paradigm.Primary.Functor.Wye

Documentation

data Wye a Source #

Constructors

End 
Left a 
Right a 
Both a a 

Instances

Instances details
Covariant Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

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

comap :: (a -> b) -> Wye a -> Wye b Source #

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

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

void :: Wye a -> Wye () Source #

loeb :: Wye (a <:= Wye) -> Wye a Source #

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

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

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

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

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

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

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

Traversable Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

(->>) :: (Pointable u, Applicative u) => Wye a -> (a -> u b) -> (u :. Wye) := b Source #

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

sequence :: (Pointable u, Applicative u) => ((Wye :. u) := a) -> (u :. Wye) := a Source #

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

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

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

Measurable 'Heighth Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Measural 'Heighth Binary a Source #

Measurable 'Heighth (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Measural 'Heighth (Construction Wye) a Source #

Monotonic a (Wye a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

reduce :: (a -> r -> r) -> r -> Wye a -> r Source #

resolve :: (a -> r) -> r -> Wye a -> r Source #

Semigroup a => Semigroup (Wye a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

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

Semigroup a => Monoid (Wye a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

zero :: Wye a Source #

Nullable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Methods

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Focusing 'Root Binary a Source #

Focusable ('Left :: Type -> Wye Type) (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Focusing 'Left (Product s) a Source #

Focusable ('Right :: Type -> Wye Type) (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Focusing 'Right (Product s) a Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Focusing 'Root (Construction Wye) a Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Methods

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

Morphable ('Into ('Left Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

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

Morphable ('Into ('Right Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (Construction Wye) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing 'Insert (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substructural 'Right (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substructural 'Left (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right (Product s) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Methods

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

contramap :: (a -> b0) -> Kan 'Left t u b b0 -> Kan 'Left t u b a Source #

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

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

full :: Kan 'Left t u b () -> Kan 'Left t u b a Source #

(>&<) :: Kan 'Left t u b b0 -> (a -> b0) -> Kan 'Left t u b a Source #

(>$$<) :: Contravariant u0 => (a -> b0) -> ((Kan 'Left t u b :. u0) := a) -> (Kan 'Left t u b :. u0) := b0 Source #

(>$$$<) :: (Contravariant u0, Contravariant v) => (a -> b0) -> ((Kan 'Left t u b :. (u0 :. v)) := b0) -> (Kan 'Left t u b :. (u0 :. v)) := a Source #

(>$$$$<) :: (Contravariant u0, Contravariant v, Contravariant w) => (a -> b0) -> ((Kan 'Left t u b :. (u0 :. (v :. w))) := a) -> (Kan 'Left t u b :. (u0 :. (v :. w))) := b0 Source #

(>&&<) :: Contravariant u0 => ((Kan 'Left t u b :. u0) := a) -> (a -> b0) -> (Kan 'Left t u b :. u0) := b0 Source #

(>&&&<) :: (Contravariant u0, Contravariant v) => ((Kan 'Left t u b :. (u0 :. v)) := b0) -> (a -> b0) -> (Kan 'Left t u b :. (u0 :. v)) := a Source #

(>&&&&<) :: (Contravariant u0, Contravariant v, Contravariant w) => ((Kan 'Left t u b :. (u0 :. (v :. w))) := a) -> (a -> b0) -> (Kan 'Left t u b :. (u0 :. (v :. w))) := b0 Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Methods

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

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

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

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

void :: Kan 'Right t u b a -> Kan 'Right t u b () Source #

loeb :: Kan 'Right t u b (a <:= Kan 'Right t u b) -> Kan 'Right t u b a Source #

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Associated Types

type Primary (Kan 'Left t u b) a Source #

Methods

run :: Kan 'Left t u b a -> Primary (Kan 'Left t u b) a Source #

unite :: Primary (Kan 'Left t u b) a -> Kan 'Left t u b a Source #

(||=) :: Interpreted u0 => (Primary (Kan 'Left t u b) a -> Primary u0 b0) -> Kan 'Left t u b a -> u0 b0 Source #

(=||) :: Interpreted u0 => (Kan 'Left t u b a -> u0 b0) -> Primary (Kan 'Left t u b) a -> Primary u0 b0 Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Associated Types

type Primary (Kan 'Right t u b) a Source #

Methods

run :: Kan 'Right t u b a -> Primary (Kan 'Right t u b) a Source #

unite :: Primary (Kan 'Right t u b) a -> Kan 'Right t u b a Source #

(||=) :: Interpreted u0 => (Primary (Kan 'Right t u b) a -> Primary u0 b0) -> Kan 'Right t u b a -> u0 b0 Source #

(=||) :: Interpreted u0 => (Kan 'Right t u b a -> u0 b0) -> Primary (Kan 'Right t u b) a -> Primary u0 b0 Source #

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Measural 'Heighth Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Measural 'Heighth (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Zipper (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

data Kan ('Left :: Type -> Wye Type) t u b a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

data Kan ('Left :: Type -> Wye Type) t u b a = Lan ((t b -> a) -> u b)
data Kan ('Right :: Type -> Wye Type) t u b a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

data Kan ('Right :: Type -> Wye Type) t u b a = Ran ((a -> t b) -> u b)
type Focusing ('Root :: Type -> Location Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Focusing ('Root :: Type -> Location Type) Binary a = Maybe a
type Focusing ('Left :: Type -> Wye Type) (Product s) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Focusing ('Left :: Type -> Wye Type) (Product s) a = s
type Focusing ('Right :: Type -> Wye Type) (Product s) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Focusing ('Right :: Type -> Wye Type) (Product s) a = a
type Focusing ('Root :: Type -> Location Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Focusing ('Root :: Type -> Location Type) (Construction Wye) a = a
type Morphing ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into (o ds) :: Morph a) Binary = Maybe <:.> Morphing ('Into (o ds)) (Construction Wye)
type Morphing ('Into ('Left Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into ('Right Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) = Binary
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) 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)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) 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)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) 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)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) 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)))) (Construction Wye) = Binary
type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Primary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) Binary = (((Identity <:.:> Comparison) := (:*:)) <:.:> Binary) := ((->) :: Type -> Type -> Type)
type Substructural ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substructural ('Left :: a -> Wye a) Binary = Binary
type Morphing ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) (Construction Wye) = (((Identity <:.:> Comparison) := (:*:)) <:.:> Construction Wye) := ((->) :: Type -> Type -> Type)
type Substructural ('Right :: a -> Wye a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure

type Substructural ('Right :: a -> Wye a) (Product s) = Identity
type Primary (Kan ('Left :: Type -> Wye Type) t u b) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

type Primary (Kan ('Left :: Type -> Wye Type) t u b) a = (t b -> a) -> u b
type Primary (Kan ('Right :: Type -> Wye Type) t u b) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

type Primary (Kan ('Right :: Type -> Wye Type) t u b) a = (a -> t b) -> u b

wye :: r -> (a -> r) -> (a -> r) -> (a -> a -> r) -> Wye a -> r Source #