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

Pandora.Paradigm.Primary.Transformer.Reverse

Documentation

newtype Reverse t a Source #

Constructors

Reverse (t a) 

Instances

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

Impliable (Tape t a :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

Methods

imply :: Arguments (Tape t a) 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 #

Hoistable ((->) :: Type -> Type -> Type) (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

Morphable ('Into (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 #

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 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 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 -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye 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 -> Wye a) :: Morph (a -> Wye 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 -> 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 #

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 #

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 #

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

Liftable ((->) :: Type -> Type -> Type) (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

Lowerable ((->) :: Type -> Type -> Type) (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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 #

Interpreted ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Associated Types

type Primary (Reverse t) a Source #

Methods

run :: Reverse t a -> Primary (Reverse t) a Source #

unite :: Primary (Reverse t) a -> Reverse t a Source #

(!) :: Reverse t a -> Primary (Reverse t) a Source #

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

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

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

(-#=$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (Reverse t a -> u b) -> (j := Primary (Reverse t) a) -> (j := Primary u b) 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 #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

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

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

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

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

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

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

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

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

Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

(-<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(--<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(---<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(----<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(-----<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(------<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(-------<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(--------<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

(---------<<) :: Covariant (->) (->) u => (a -> Reverse t b) -> u a -> Reverse t (u b) Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

(>-|-) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|--) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|---) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|----) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|-----) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|------) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|-------) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|--------) :: (a -> b) -> Reverse t b -> Reverse t a Source #

(>-|-|-) :: (Contravariant (->) (Betwixt (->) (->)) u, Contravariant (Betwixt (->) (->)) (->) (Reverse t)) => (a -> b) -> Reverse t (u a) -> Reverse t (u b) Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

type Arguments (Tape t a :: Type) = a -> t a -> t a -> Tape t a
type Morphing ('Into (Tape List)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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 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 Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape (Construction Maybe)) = Maybe <::> Tape (Construction Maybe)
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 ('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 Primary (Reverse t) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

type Primary (Reverse t) a = t a
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) = Exactly
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) = Exactly
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) = Exactly
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) = Reverse 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) = Exactly
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