pandora-0.4.6: 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
Interpreted (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 #

(||=) :: Interpreted u => (Primary (Comprehension t) a -> Primary u b) -> Comprehension t a -> u b Source #

(=||) :: Interpreted u => (Comprehension t a -> u b) -> Primary (Comprehension t) a -> Primary u b Source #

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

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

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

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

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

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

(=||$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted u) => (Comprehension t a -> u b) -> ((j :. (k :. l)) := Primary (Comprehension t) a) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) m, Interpreted u) => (Comprehension t a -> u b) -> ((j :. (k :. (l :. m))) := Primary (Comprehension t) a) -> (j :. (k :. (l :. m))) := Primary u b Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

null :: forall (a :: k). (Predicate :. Comprehension t) := a Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

multiply :: forall (a :: k) (b :: k). (Comprehension t a :*: Comprehension t b) -> Comprehension t (a :+: b) Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

multiply :: forall (a :: k) (b :: k). (Comprehension t a :*: Comprehension t b) -> Comprehension t (a :*: b) 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 #

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

(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

Methods

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) 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, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

unit :: Proxy (:*:) -> (Unit (:+:) -> a) -> Comprehension t a 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 #

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 (->) (->) (:*:) (:*:) u) => (a -> u b) -> Comprehension t a -> u (Comprehension t b) Source #

type Primary (Comprehension t) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

type Morphing ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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) = (Identity <:.:> Comprehension t) := ((->) :: Type -> Type -> Type)
type Zipper (Comprehension Maybe) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Zipper (Comprehension Maybe) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) = Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))

Orphan instances

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

Associated Types

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