pandora-0.4.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
Lowerable Tap Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

lower :: forall (u :: Type -> Type). Covariant u (->) (->) => Tap u ~> u 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 #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

extract :: Tap t a -> a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) 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 #

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Tap t a -> u (Tap t b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Tap ((t <:.:> t) := (:*:)) a -> u (Tap ((t <:.:> t) := (:*:)) b) Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Tail :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Tail :: a -> Segment a) (Tap t) = Identity
type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Substance ('Tail :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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