pandora-0.5.5: 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
Semimonoidal (<--) (:*:) (:*:) t => Monoidal (<--) (-->) (:*:) (:*:) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

Semimonoidal (-->) (:*:) (:*:) t => Semimonoidal (-->) (:*:) (:*:) (Tap t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Rest (Tap t) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

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

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

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

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

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

type Substance ('Rest :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Rest :: a -> Segment a) (Tap t) = t