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

Pandora.Paradigm.Primary.Algebraic.Sum

Documentation

data s :+: a infixr 0 Source #

Constructors

Option s 
Adoption a 

Instances

Instances details
Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:+:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:+:) ((:+:) e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

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

Semigroup e => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:+:) (Validation e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

multiply :: forall (a :: k) (b :: k). (Validation e a :*: Validation e b) -> Validation e (a :+: b) Source #

Semigroup e => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:+:) (Conclusion e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

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

Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) ((:+:) e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) ((:+:) e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) -> (e :+: a) Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

unit :: Proxy (:*:) -> (Unit (:+:) -> a) -> (t <:.> u) a Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:+:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Sum

Methods

(-<$>-) :: (a -> b) -> (s :+: a) -> (s :+: b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (:+:) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Sum

Methods

(-<$>-) :: (a0 -> b) -> Flip (:+:) a a0 -> Flip (:+:) a b Source #

Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Sum

Methods

(<->) :: (a -> b) -> (c -> d) -> (a :+: c) -> (b :+: d) Source #

type Unit (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

type Unit (:+:) = Zero

sum :: (e -> r) -> (a -> r) -> (e :+: a) -> r Source #