Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Pattern.Functor.Semimonoidal
Documentation
class Semigroupoid p => Semimonoidal t p source target where Source #
Instances
Semimonoidal Maybe ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # | |
Semimonoidal Maybe ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal ((:+:) e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # | |
Semigroup e => Semimonoidal (Validation e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # | |
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 (Validation e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
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 # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (Instruction t :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods multiply_ :: forall (a :: k) (b :: k). (Instruction t a :*: Instruction t b) -> Instruction t (a :*: b) Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (Construction t :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Construction Methods multiply_ :: forall (a :: k) (b :: k). (Construction t a :*: Construction t b) -> Construction t (a :*: b) Source # | |
Semigroup e => Semimonoidal (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # | |
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 # | |
Semimonoidal (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
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 t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (Comprehension t :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
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 t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (Tap t :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (Tap ((t <:.:> t) := (:*:)) :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List Methods multiply_ :: forall (a :: k) (b :: k). (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a :*: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a :*: b) Source # | |
Semimonoidal (State s :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal (Environment e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment Methods multiply_ :: forall (a :: k) (b :: k). (Environment e a :*: Environment e b) -> Environment e (a :*: b) Source # | |
Semigroup e => Semimonoidal (Accumulator e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator Methods multiply_ :: forall (a :: k) (b :: k). (Accumulator e a :*: Accumulator e b) -> Accumulator e (a :*: b) Source # | |
Semimonoidal (Schematic Monad t u) ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (t :> u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
(Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:), Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Semimonoidal (Backwards t :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal (Schematic Comonad t u) ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (t :< u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal ((->) e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal ((t <:.:> t) := (:*:) :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:), Semimonoidal t' ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal ((t <:<.>:> t') := u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
(Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (t <.:> u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (t <:.> u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |