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

Pandora.Paradigm.Structure.Modification.Comprehension

Documentation

newtype Comprehension t a Source #

Constructors

Comprehension ((t <::> Construction t) >>>>> a) 

Instances

Instances details
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t, Semimonoidal (-->) (:*:) (:*:) (Construction t), Semimonoidal (-->) (:*:) (:+:) t, Semimonoidal (-->) (:*:) (:+:) (Construction t), Monoidal (-->) (-->) (:*:) (:+:) t) => Monoidal (-->) (-->) (:*:) (:+:) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Zippable (Comprehension Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs (Comprehension Maybe) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) right t, Semimonoidal (-->) (:*:) right (t <::> Construction t)) => Semimonoidal (-->) (:*:) (right :: Type -> Type -> Type) (Comprehension t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Comprehension Maybe) (Tape List) :: Type -> Type Source #

Semigroup ((t <::> Construction t) >>>>> a) => Semigroup (Comprehension t a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

(+) :: Comprehension t a -> Comprehension t a -> Comprehension t a Source #

Monoid ((t <::> Construction t) >>>>> a) => Monoid (Comprehension t a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

zero :: Comprehension t a Source #

Setoid ((t <::> Construction t) >>>>> a) => Setoid (Comprehension t a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

(==) :: Comprehension t a -> Comprehension t a -> Boolean Source #

(!=) :: Comprehension t a -> Comprehension t a -> Boolean Source #

(?=) :: Comprehension t a -> Comprehension t a -> r -> r -> r Source #

(forall a. Semigroup ((t <::> Construction t) >>>>> a), Bindable ((->) :: Type -> Type -> Type) t) => Bindable ((->) :: Type -> Type -> Type) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Interpreted ((->) :: Type -> Type -> Type) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Associated Types

type Primary (Comprehension t) a Source #

Methods

run :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

unite :: ((->) < Primary (Comprehension t) a) < Comprehension t a Source #

(<~~~~~~~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~~~~~~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~~~~~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~~~~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~~~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(<~) :: ((->) < Comprehension t a) < Primary (Comprehension t) a Source #

(=#-) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Primary (Comprehension t) a) < Primary u b) -> ((->) < Comprehension t a) < u b Source #

(-#=) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Comprehension t a) < u b) -> ((->) < Primary (Comprehension t) a) < Primary u b Source #

(<$=#-) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (((->) < Primary (Comprehension t) a) < Primary u b) -> (j > Comprehension t a) -> (j > u b) Source #

(-#=$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (((->) < Comprehension t a) < u b) -> (j > Primary (Comprehension t) a) -> (j > Primary u b) Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (-->) (-->) (:*:) (:*:) t) => Morphable ('Push :: a -> Morph a) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Associated Types

type Morphing 'Push (Comprehension t) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

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

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

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

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

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

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

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

type Breadcrumbs (Comprehension Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Primary (Comprehension t) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) = Comprehension Maybe
type Morphing ('Push :: a -> Morph a) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

type Morphing ('Push :: a -> Morph a) (Comprehension t) = (Exactly <:.:> Comprehension t) >>>>>> ((->) :: Type -> Type -> Type)

Orphan instances

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (-->) (-->) (:*:) (:*:) t) => Morphable ('Push :: a -> Morph a) (Comprehension t) Source # 
Instance details

Associated Types

type Morphing 'Push (Comprehension t) :: Type -> Type Source #