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

Pandora.Pattern.Functor.Semimonoidal

Documentation

class Semigroupoid p => Semimonoidal p source target t | p target -> source where Source #

Methods

mult :: p (source (t a) (t b)) (t (target a b)) Source #

Instances

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

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Methods

mult :: forall (a :: k) (b :: k). (Predicate a :*: Predicate b) --> Predicate (a :+: b) Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Semimonoidal (-->) (:*:) (:*:) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Methods

mult :: forall (a :: k) (b :: k). (Predicate a :*: Predicate b) --> Predicate (a :*: b) Source #

Semimonoidal (-->) (:*:) (:*:) Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

mult :: forall (a :: k) (b :: k). (Exactly a :*: Exactly b) --> Exactly (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Semimonoidal (<--) (:*:) (:*:) Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Exactly

Methods

mult :: forall (a :: k) (b :: k). (Exactly a :*: Exactly b) <-- Exactly (a :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

mult :: forall (a :: k) (b :: k). (Maybe a :*: Maybe b) <-- Maybe (a :*: b) 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 #

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

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

Semigroup r => Semimonoidal (-->) (:*:) (:*:) (Convergence r :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Convergence

Methods

mult :: forall (a :: k) (b :: k). (Convergence r a :*: Convergence r b) --> Convergence r (a :*: b) Source #

Semimonoidal (-->) (:*:) (:*:) t => Semimonoidal (-->) (:*:) (:*:) (Tap t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

Semimonoidal (-->) (:*:) (:*:) t => Semimonoidal (-->) (:*:) (:*:) (Tap ((t <:.:> t) >>>>>> (:*:)) :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

mult :: forall (a :: k) (b :: k). (Tap ((t <:.:> t) >>>>>> (:*:)) a :*: Tap ((t <:.:> t) >>>>>> (:*:)) b) --> Tap ((t <:.:> t) >>>>>> (:*:)) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

mult :: forall (a :: k) (b :: k). (Conclusion e a :*: Conclusion e b) --> Conclusion e (a :*: b) Source #

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

Defined in Pandora.Paradigm.Inventory.Some.State

Methods

mult :: forall (a :: k) (b :: k). (State s a :*: State s b) --> State s (a :*: b) Source #

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

Defined in Pandora.Paradigm.Inventory.Some.Provision

Methods

mult :: forall (a :: k) (b :: k). (Provision e a :*: Provision e b) --> Provision e (a :*: b) Source #

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

Defined in Pandora.Paradigm.Inventory.Some.Accumulator

Methods

mult :: forall (a :: k) (b :: k). (Accumulator e a :*: Accumulator e b) --> Accumulator e (a :*: b) Source #

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

Defined in Pandora.Paradigm.Algebraic

Methods

mult :: forall (a :: k) (b :: k). ((s :*: a) :*: (s :*: b)) <-- (s :*: (a :*: b)) Source #

Semimonoidal (<--) (:*:) (:*:) t => Semimonoidal (<--) (:*:) (:*:) (Tap t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

mult :: forall (a :: k) (b :: k). (Tap t a :*: Tap t b) <-- Tap t (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

mult :: forall (a :: k) (b :: k). (Construction t a :*: Construction t b) <-- Construction t (a :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) (Store s :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

mult :: forall (a :: k) (b :: k). (Store s a :*: Store s b) <-- Store s (a :*: b) Source #

Semimonoidal (-->) (:*:) (:+:) (Schematic Monad t u) => Semimonoidal (-->) (:*:) (:+:) (t :> u :: Type -> Type) Source # 
Instance details

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

mult :: forall (a :: k) (b :: k). (Reverse t a :*: Reverse t b) --> Reverse t (a :+: b) Source #

Semimonoidal (-->) (:*:) (:*:) (Flip Conclusion a :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

mult :: forall (a0 :: k) (b :: k). (Flip Conclusion a a0 :*: Flip Conclusion a b) --> Flip Conclusion a (a0 :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

mult :: forall (a :: k) (b :: k). (Tagged tag a :*: Tagged tag b) --> Tagged tag (a :*: b) Source #

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

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

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

Methods

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

Semimonoidal (-->) (:*:) (:*:) (Lens Exactly source :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

mult :: forall (a :: k) (b :: k). (Lens Exactly source a :*: Lens Exactly source b) --> Lens Exactly source (a :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) (Flip (:*:) a :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Algebraic

Methods

mult :: forall (a0 :: k) (b :: k). (Flip (:*:) a a0 :*: Flip (:*:) a b) <-- Flip (:*:) a (a0 :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) (Tagged tag :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

mult :: forall (a :: k) (b :: k). (Tagged tag a :*: Tagged tag b) <-- Tagged tag (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

mult :: forall (a :: k) (b :: k). (Backwards t a :*: Backwards t b) <-- Backwards t (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

mult :: forall (a :: k) (b :: k). (Reverse t a :*: Reverse t b) <-- Reverse t (a :*: b) Source #

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

mult :: forall (a :: k) (b :: k). ((e -> a) :*: (e -> b)) <-- (e -> (a :*: b)) Source #

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

Semimonoidal (<--) (:*:) (:*:) t => Semimonoidal (<--) (:*:) (:*:) (Exactly <:*:> t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Interface.Zipper

Methods

mult :: forall (a :: k) (b :: k). ((Exactly <:*:> t) a :*: (Exactly <:*:> t) b) <-- (Exactly <:*:> t) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Bindable ((->) :: Type -> Type -> Type) u) => Semimonoidal (-->) (:*:) (:*:) ((t <:<.>:> t') >>>>>>>> u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

mult :: forall (a :: k) (b :: k). ((t <::> t') a :*: (t <::> t') b) --> (t <::> t') (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

mult :: forall (a :: k) (b :: k). ((t <::> t') a :*: (t <::> t') b) <-- (t <::> t') (a :*: b) Source #