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

Pandora.Pattern.Functor.Monoidal

Documentation

type family Unit (p :: * -> * -> *) = r | r -> p Source #

Instances

Instances details
type Unit (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Algebraic.Functor

type Unit (:+:) = Zero
type Unit (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Algebraic.Functor

type Unit (:*:) = One

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

Methods

unit :: Proxy source -> p (q (Unit target) a) (t a) Source #

Instances

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Exactly

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Monoidal (-->) (<--) (:*:) (:*:) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Monoidal (<--) (-->) (:*:) (:*:) Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Exactly

(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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Validation

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

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

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

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

Defined in Pandora.Paradigm.Inventory.Some.State

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> State s a Source #

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

Defined in Pandora.Paradigm.Inventory.Some.Provision

Methods

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

Monoid r => Monoidal (-->) (<--) (:*:) (:*:) (Convergence r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Convergence

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

Defined in Pandora.Paradigm.Algebraic

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- (s :*: a) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- Tap t a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

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

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- Store s a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

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

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> Tagged tag a Source #

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

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> Backwards t a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> Reverse t a Source #

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

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

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a0) <-- Flip (:*:) a a0 Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- Tagged tag a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- Backwards t a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- Reverse t a Source #

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Structure.Interface.Zipper

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- (Exactly <:*:> t) a Source #

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> (t <::> t') a Source #

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TT

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- (t <::> t') a Source #