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

Pandora.Paradigm.Primary.Functor.Exactly

Documentation

newtype Exactly a Source #

Constructors

Exactly a 

Instances

Instances details
Lensic Exactly Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

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

Methods

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

Lensic Maybe Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

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

Methods

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

Zoomable State Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

zoom :: forall bg ls (t :: Type -> Type). Adaptable t (->) (State bg) => Lens Exactly bg ls -> State (Simplification Exactly ls) ~> t Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Methods

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

Accessible a (Exactly a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

access :: Lens Exactly (Exactly a) a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

zero :: Exactly a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

one :: Exactly a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

invert :: Exactly a -> Exactly a Source #

(-) :: Exactly a -> Exactly a -> Exactly a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Semigroupoid (Lens Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

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

Category (Lens Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Zippable (Construction Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Methods

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

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

Defined in Pandora.Paradigm.Controlflow.Effect.Adaptable

Methods

adapt :: forall (a :: k). Exactly a -> u a 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 #

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 #

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 #

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

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Gettable (Lens Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Getting (Lens Exactly) e r Source #

Methods

get :: Getting (Lens Exactly) e r 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 #

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(---------|) :: (Exactly a -> b) -> a -> Exactly 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 #

type Lensally Exactly Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Lensally Maybe Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Breadcrumbs (Construction Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

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 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 Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Exactly source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Exactly source target :: Type) = (source -> target) -> (source -> target -> source) -> Lens Exactly source target
type Getting (Lens Exactly) source target Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Getting (Lens Exactly) source target = Lens Exactly source target -> 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) = 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

type family Simplification (t :: * -> *) (a :: *) where ... Source #

Equations

Simplification Exactly a = a 
Simplification t a = t a