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

Pandora.Paradigm.Primary.Functor.Identity

Documentation

newtype Identity a Source #

Constructors

Identity a 

Instances

Instances details
Lensic Identity Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Associated Types

type Lensally Identity Maybe :: Type -> Type Source #

Methods

(>>>) :: Lens Identity source between -> Lens Maybe between target -> Lens (Lensally Identity Maybe) source target Source #

Lensic Maybe Identity Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Associated Types

type Lensally Maybe Identity :: Type -> Type Source #

Methods

(>>>) :: Lens Maybe source between -> Lens Identity between target -> Lens (Lensally Maybe Identity) source target Source #

Monoidal (-->) (-->) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Monoidal (<--) (-->) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Accessible a (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

Ringoid a => Ringoid (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(*) :: Identity a -> Identity a -> Identity a Source #

Monoid a => Monoid (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

zero :: Identity a Source #

Quasiring a => Quasiring (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

one :: Identity a Source #

Group a => Group (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Supremum a => Supremum (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(\/) :: Identity a -> Identity a -> Identity a Source #

Infimum a => Infimum (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(/\) :: Identity a -> Identity a -> Identity a Source #

Lattice a => Lattice (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Chain a => Chain (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Semigroupoid (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Methods

(.) :: Lens Identity b c -> Lens Identity a b -> Lens Identity a c Source #

Category (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Zippable (Construction Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Breadcrumbs (Construction Identity) :: Type -> Type Source #

Semimonoidal (-->) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

mult :: forall (a :: k) (b :: k). (Identity a :*: Identity b) --> Identity (a :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

mult :: forall (a :: k) (b :: k). (Identity a :*: Identity b) <-- Identity (a :*: b) Source #

Semimonoidal (-->) (:*:) (:*:) (Lens Identity source :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Methods

mult :: forall (a :: k) (b :: k). (Lens Identity source a :*: Lens Identity source b) --> Lens Identity source (a :*: b) Source #

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Methods

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

Monoidal (-->) (-->) (:*:) (:*:) u => Adaptable (u :: Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Adaptable

Methods

adapt :: forall (a :: k). Identity a -> u a Source #

Morphable ('Into ((Identity <:.:> ((List <:.:> List) := (:*:))) := (:*:))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) ((Identity <:.:> ((List <:.:> List) := (:*:))) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

Impliable (P_Q_T ((->) :: Type -> Type -> Type) Store Identity source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Associated Types

type Arguments (P_Q_T (->) Store Identity source target) = (args :: Type) Source #

Methods

imply :: Arguments (P_Q_T (->) Store Identity source target) Source #

Extendable ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(<<=) :: (Identity a -> b) -> Identity a -> Identity b Source #

Bindable ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(=<<) :: (a -> Identity b) -> Identity a -> Identity b Source #

Monad ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Comonad ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

type Substance 'Root (Tape t) :: 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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(<-|-) :: (a -> b) -> Identity a -> Identity b Source #

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

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

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(-|) :: (Identity a -> b) -> a -> Identity b Source #

(|-) :: (a -> Identity b) -> Identity a -> b Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((Identity <:.:> ((List <:.:> List) := (:*:))) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

Extendable ((->) :: Type -> Type -> Type) ((Identity <:.:> ((Stream <:.:> Stream) := (:*:))) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable ((->) :: Type -> Type -> Type) ((Identity <:.:> ((List <:.:> List) := (:*:))) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Lensally Identity Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

type Lensally Maybe Identity Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

type Breadcrumbs (Construction Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) ((Identity <:.:> ((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)) ((Identity <:.:> ((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)) ((Identity <:.:> ((List <:.:> List) := (:*:))) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Identity source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Identity source target :: Type) = (source -> target) -> (source -> target -> source) -> Lens Identity source target
type Available ('Right :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Available ('Left :: a -> Wye a) (Tape t) = Identity
type Available ('Root :: a -> Segment a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Available ('Root :: a -> Segment a) (Tape t) = Identity
type Substance ('Right :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Substance ('Root :: a -> Segment a) (Tape t) = Identity
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) = Identity
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) = Identity
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) = Identity
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) = Identity
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 <::> 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) = 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