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

Pandora.Pattern.Functor.Traversable

Synopsis

Documentation

class Covariant t source target => Traversable t source target where Source #

Let f :: (Applicative t, Applicative g) => t a -> u a
Let p :: (Pointable t, Pointable g) => t a -> u a
When providing a new instance, you should ensure it satisfies:
* Numeratority of traversing: g . (f <<--) ≡ (g . f <<--)
* Numeratority of sequencing: f . (identity <<--)= (identity <<--) . (f -<$>-)
* Preserving point: p (point x) ≡ point x
* Preserving apply: f (x -<*>- y) ≡ f x -<*>- f y

Methods

(<<-) :: (Covariant u source target, Pointable u target, Semimonoidal u target (:*:) (:*:)) => source a (u b) -> target (t a) (u (t b)) infixl 5 Source #

Instances

Instances details
Traversable Identity ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Edges

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Traversable ((:*:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

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

Traversable (Wedge e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wedge

Methods

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

Traversable (These e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.These

Methods

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

Traversable (Validation e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Jet

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

Traversable (Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

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

Traversable (t <:.> Construction t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (Comprehension t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Comprehension t a -> u (Comprehension 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 #

Traversable (Equipment e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

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

Traversable (Tagged tag) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

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

Traversable (Schematic Monad t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (t :> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

Traversable (Schematic Comonad t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (t :< u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Methods

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

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

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Methods

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

(Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Traversable u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Traversable (t <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

(-<<-<<-) :: forall t u v category a b. (Traversable t category category, Covariant u category category, Pointable u category, Semimonoidal u category (:*:) (:*:), Traversable v category category) => category a (u b) -> category (v (t a)) (u (v (t b))) infixl 5 Source #