pandora-0.3.7: 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 #

(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 #

(<**>) :: 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 #

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Stack

Methods

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

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

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

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

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

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

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

(<<=$) :: Covariant u => ((u :. Tap ((:*:) <:.:> Stack)) := a) -> (Tap ((:*:) <:.:> Stack) a -> b) -> (u :. Tap ((:*:) <:.:> Stack)) := 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 #

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 #

Hoistable Tap Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stack)) :: 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 ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.Stack

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

Defined in Pandora.Paradigm.Structure.Some.Stack

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

Defined in Pandora.Paradigm.Structure.Some.Stack

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

Defined in Pandora.Paradigm.Structure.Some.Stack

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) = Maybe <:.> Zipper Stack
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