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

Pandora.Paradigm.Primary.Transformer.Tap

Documentation

data Tap t a Source #

Constructors

Tap a (t a) 

Instances

Instances details
Lowerable Tap Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

lower :: forall (u :: Type -> Type). Covariant u => Tap u ~> u Source #

Covariant t => Covariant (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<$>) :: (a -> b) -> Tap t a -> Tap t b Source #

comap :: (a -> b) -> Tap t a -> Tap t b Source #

(<$) :: a -> Tap t b -> Tap t a Source #

($>) :: Tap t a -> b -> Tap t b Source #

void :: Tap t a -> Tap t () Source #

loeb :: Tap t (a <:= Tap t) -> Tap t a Source #

(<&>) :: Tap t a -> (a -> b) -> Tap t b Source #

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

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

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

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

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

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

(.#..) :: (Tap t ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: (Tap t ~ v a, Tap t ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source #

(.#....) :: (Tap t ~ v a, Tap t ~ v b, Tap t ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source #

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

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

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

($$>) :: Covariant u => ((Tap t :. u) := a) -> b -> (Tap t :. u) := b Source #

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

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

(Extractable t, Alternative t, Bindable t) => Bindable (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(>>=) :: Tap t a -> (a -> Tap t b) -> Tap t b Source #

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

bind :: (a -> Tap t b) -> Tap t a -> Tap t b Source #

join :: ((Tap t :. Tap t) := a) -> Tap t a Source #

(>=>) :: (a -> Tap t b) -> (b -> Tap t c) -> a -> Tap t c Source #

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

($>>=) :: Covariant u => ((u :. Tap t) := a) -> (a -> Tap t b) -> (u :. Tap t) := b Source #

Applicative t => Applicative (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<*>) :: Tap t (a -> b) -> Tap t a -> Tap t b Source #

apply :: Tap t (a -> b) -> Tap t a -> Tap t b Source #

(*>) :: Tap t a -> Tap t b -> Tap t b Source #

(<*) :: Tap t a -> Tap t b -> Tap t a Source #

forever :: Tap t a -> Tap t b Source #

(<%>) :: Tap t a -> Tap t (a -> b) -> Tap t b Source #

(<**>) :: Applicative u => ((Tap t :. u) := (a -> b)) -> ((Tap t :. u) := a) -> (Tap t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap t :. (u :. v)) := (a -> b)) -> ((Tap t :. (u :. v)) := a) -> (Tap t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap t :. (u :. (v :. w))) := (a -> b)) -> ((Tap t :. (u :. (v :. w))) := a) -> (Tap t :. (u :. (v :. w))) := b Source #

Applicative (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

apply :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(*>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<*) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a Source #

forever :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<%>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := b Source #

Applicative (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

apply :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(*>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<*) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a Source #

forever :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<%>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := b Source #

Applicative (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

apply :: Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

(*>) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b -> Tap ((List <:.:> List) := (:*:)) b Source #

(<*) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b -> Tap ((List <:.:> List) := (:*:)) a Source #

forever :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

(<%>) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((List <:.:> List) := (:*:)) :. u) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (Tap ((List <:.:> List) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := a) -> (Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := b Source #

Extendable t => Extendable (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(=>>) :: Tap t a -> (Tap t a -> b) -> Tap t b Source #

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

extend :: (Tap t a -> b) -> Tap t a -> Tap t b Source #

duplicate :: Tap t a -> (Tap t :. Tap t) := a Source #

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

(=>=) :: (Tap t a -> b) -> (Tap t b -> c) -> Tap t a -> c Source #

($=>>) :: Covariant u => ((u :. Tap t) := a) -> (Tap t a -> b) -> (u :. Tap t) := b Source #

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

Extendable (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(=>>) :: Tap ((List <:.:> List) := (:*:)) a -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) b Source #

(<<=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

extend :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

duplicate :: Tap ((List <:.:> List) := (:*:)) a -> (Tap ((List <:.:> List) := (:*:)) :. Tap ((List <:.:> List) := (:*:))) := a Source #

(=<=) :: (Tap ((List <:.:> List) := (:*:)) b -> c) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> c Source #

(=>=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> (Tap ((List <:.:> List) := (:*:)) b -> c) -> Tap ((List <:.:> List) := (:*:)) a -> c Source #

($=>>) :: Covariant u => ((u :. Tap ((List <:.:> List) := (:*:))) := a) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

(<<=$) :: Covariant u => ((u :. Tap ((List <:.:> List) := (:*:))) := a) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

Covariant t => Extractable (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

extract :: a <:= Tap t Source #

Avoidable t => Pointable (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

point :: a :=> Tap t Source #

pass :: Tap t () Source #

Traversable t => Traversable (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

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

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

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

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

Traversable (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Traversable (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(->>) :: (Pointable u, Applicative u) => Tap ((List <:.:> List) := (:*:)) a -> (a -> u b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

traverse :: (Pointable u, Applicative u) => (a -> u b) -> Tap ((List <:.:> List) := (:*:)) a -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

sequence :: (Pointable u, Applicative u) => ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (u :. Tap ((List <:.:> List) := (:*:))) := a Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Tap ((List <:.:> List) := (:*:))) := a) -> (a -> u b) -> (u :. (v :. Tap ((List <:.:> List) := (:*:)))) := b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Tap ((List <:.:> List) := (:*:)))) := a) -> (a -> u b) -> (u :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Tap ((List <:.:> List) := (:*:)))))) := b Source #

Hoistable Tap Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(/|\) :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u => (u ~> v) -> Tap u ~> Tap v Source #

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u => (u ~> v) -> Tap u ~> Tap v Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) :: 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 #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Root :: a -> Segment a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Root (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Root :: a -> Segment a) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Root (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Covariant t => Substructure ('Tail :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Tail (Tap t) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (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 ((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 Substructural ('Right :: a -> Wye a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Root :: a -> Segment a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Left :: a -> Wye a) (Tap ((List <:.:> List) := (:*:))) = List
type Substructural ('Root :: a -> Segment a) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Tail :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substructural ('Tail :: a -> Segment a) (Tap t) = t