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

Pandora.Pattern.Morphism.Straight

Documentation

newtype Straight (v :: * -> * -> *) a e Source #

Constructors

Straight (v a e) 

Instances

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

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 (<--) (-->) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

(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.Primary.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.State

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Environment

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

Defined in Pandora.Paradigm.Primary.Functor.Convergence

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

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- (s :*: 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.Store

Methods

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

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.Primary.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 (-->) (-->) (:*:) (:*:) ((->) e :: Type -> Type) 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, 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 #

(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 #

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

(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 m m t => Covariant m (Straight m) t Source # 
Instance details

Defined in Pandora.Pattern.Morphism.Straight

Methods

(<-|-) :: m a b -> Straight m (t a) (t b) Source #

Semigroupoid m => Semigroupoid (Straight m) Source # 
Instance details

Defined in Pandora.Pattern.Morphism.Straight

Methods

(.) :: Straight m b c -> Straight m a b -> Straight m a c Source #

Category m => Category (Straight m) Source # 
Instance details

Defined in Pandora.Pattern.Morphism.Straight

Methods

identity :: Straight m a a Source #

($) :: Straight m (Straight m a b) (Straight m a b) Source #

(#) :: Straight m (Straight m a b) (Straight m a b) Source #

Covariant m m t => Covariant (Straight m) m t Source # 
Instance details

Defined in Pandora.Pattern.Morphism.Straight

Methods

(<-|-) :: Straight m a b -> m (t a) (t 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 (-->) (:*:) (:+:) 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 (-->) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

(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 (-->) (:*:) (:*:) 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 #

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

Defined in Pandora.Paradigm.Inventory.State

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

Semigroup source => Semimonoidal (-->) (:*:) (:*:) (Lens Identity source :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Methods

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

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

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

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

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

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

mult :: forall (a :: k) (b :: k). (((t <:.:> u) := (:*:)) a :*: ((t <:.:> u) := (:*:)) b) --> ((t <:.:> u) := (:*:)) (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 m m t => Covariant (Straight m) (Straight m) t Source # 
Instance details

Defined in Pandora.Pattern.Morphism.Straight

Methods

(<-|-) :: Straight m a b -> Straight m (t a) (t b) Source #

Interpreted ((->) :: Type -> Type -> Type) (Straight v e) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Interpreted

Associated Types

type Primary (Straight v e) a Source #

Methods

run :: Straight v e a -> Primary (Straight v e) a Source #

unite :: Primary (Straight v e) a -> Straight v e a Source #

(!) :: Straight v e a -> Primary (Straight v e) a Source #

(||=) :: (Semigroupoid (->), Interpreted (->) u) => (Primary (Straight v e) a -> Primary u b) -> Straight v e a -> u b Source #

(=||) :: (Semigroupoid (->), Interpreted (->) u) => (Straight v e a -> u b) -> Primary (Straight v e) a -> Primary u b Source #

(<$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (Primary (Straight v e) a -> Primary u b) -> (j := Straight v e a) -> (j := u b) Source #

(=||$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (Straight v e a -> u b) -> (j := Primary (Straight v e) a) -> (j := Primary u b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((-->) b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

(<-|-) :: (a -> b0) -> (b --> a) -> (b --> b0) Source #

type Primary (Straight v e) a Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Interpreted

type Primary (Straight v e) a = v e a