Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Pattern.Functor.Covariant
Synopsis
- class (Semigroupoid source, Semigroupoid target) => Covariant t source target where
- (-<$>-) :: source a b -> target (t a) (t b)
- (-<$$>-) :: forall t u category a b. (Covariant u category category, Covariant t category category) => category a b -> category (t (u a)) (t (u b))
- (-<<$$>-) :: forall t u source target a b. (Covariant u source source, Covariant t source target) => source a b -> target (t (u a)) (t (u b))
- (-<$$>>-) :: forall t u source target a b. (Covariant u source target, Covariant t target target) => source a b -> target (t (u a)) (t (u b))
- (-<$$$>-) :: forall t u v category a b. (Covariant t category category, Covariant u category category, Covariant v category category) => category a b -> category (t (u (v a))) (t (u (v b)))
- (-<$$$$>-) :: forall t u v w category a b. (Covariant t category category, Covariant u category category, Covariant v category category, Covariant w category category) => category a b -> category (t (u (v (w a)))) (t (u (v (w b))))
Documentation
class (Semigroupoid source, Semigroupoid target) => Covariant t source target where Source #
When providing a new instance, you should ensure it satisfies: * Identity morphism: comap identity ≡ identity * Interpreted of morphisms: comap (f . g) ≡ comap f . comap g
Instances
Stack List Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Measurable 'Length List Source # | |
Measurable 'Heighth Binary Source # | |
Covariant Wye ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant Identity ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant Edges ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant Maybe ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant Biforked ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Monotonic a ((t :. Construction t) := a) => Monotonic a ((t <:.> Construction t) := a) Source # | |
Semigroup (List a) Source # | |
Monoid (List a) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Setoid a => Setoid (List a) Source # | |
Nullable List Source # | |
Nullable Rose Source # | |
Nullable Binary Source # | |
(Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion Methods catch :: forall (a :: k). (Conclusion e <.:> u) a -> (e -> (Conclusion e <.:> u) a) -> (Conclusion e <.:> u) a 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 # | |
Extendable (Tap ((Stream <:.:> Stream) := (:*:))) ((->) :: Type -> Type -> Type) Source # | |
Extendable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) Source # | |
Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # | |
Morphable ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # | |
Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # | |
Morphable ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # | |
Morphable ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # | |
Morphable ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
Morphable ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
Morphable ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
Morphable ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
Morphable ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List Associated Types type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source # Methods morphing :: (Tagged ('Into (Construction Maybe)) <:.> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) ~> Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Morphable ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Morphable ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # | |
Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # | |
Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Morphable ('Into List) (Construction Maybe) Source # | |
Morphable ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Morphable ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # | |
Morphable ('Into List) (Vector r) Source # | |
Morphable ('Into Binary) (Construction Wye) Source # | |
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Covariant (Proxy :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant ((:+:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Yoneda t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Outline t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant ((:*:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Jack t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Wedge e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (These e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Validation e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Validation Methods (-<$>-) :: (a -> b) -> Validation e a -> Validation e b Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Jet t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Instruction t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods (-<$>-) :: (a -> b) -> Instruction t a -> Instruction t b Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Construction t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Construction Methods (-<$>-) :: (a -> b) -> Construction t a -> Construction t b Source # | |
Covariant (Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion Methods (-<$>-) :: (a -> b) -> Conclusion e a -> Conclusion e b Source # | |
Covariant (t <:.> Construction t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Comprehension t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Structure.Modification.Comprehension Methods (-<$>-) :: (a -> b) -> Comprehension t a -> Comprehension t b Source # | |
Covariant (Store s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Tap t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Imprint e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Equipment e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Environment e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment Methods (-<$>-) :: (a -> b) -> Environment e a -> Environment e b Source # | |
Covariant (Accumulator e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator Methods (-<$>-) :: (a -> b) -> Accumulator e a -> Accumulator e b Source # | |
Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (Tap ((t <:.:> t) := (:*:))) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Traversable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # | |
Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
Chain k => Morphable ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # | |
Chain k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # | |
Morphable ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # | |
Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
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 # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Hoistable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.TU Methods (/|\) :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u (->) (->) => (u ~> v) -> TU Covariant Covariant t u ~> TU Covariant Covariant t v Source # hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u (->) (->) => (u ~> v) -> TU Covariant Covariant t u ~> TU Covariant Covariant t v Source # | |
Morphable ('Pop :: a -> Morph a) List Source # | |
Morphable ('Push :: a -> Morph a) List Source # | |
Morphable ('Insert :: a -> Morph a) Binary Source # | |
Substructure ('Tail :: a -> Segment a) List Source # | |
Substructure ('Root :: a -> Segment a) List Source # | |
Substructure ('Right :: a -> Wye a) Binary Source # | |
Substructure ('Left :: a -> Wye a) Binary Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap Associated Types type Available 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # type Substance 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # Methods substructure :: ((Tagged 'Right <:.> Tap ((t <:.:> t) := (:*:))) #=@ Substance 'Right (Tap ((t <:.:> t) := (:*:)))) := Available 'Right (Tap ((t <:.:> t) := (:*:))) Source # sub :: (Tap ((t <:.:> t) := (:*:)) #=@ Substance 'Right (Tap ((t <:.:> t) := (:*:)))) := Available 'Right (Tap ((t <:.:> t) := (:*:))) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap Associated Types type Available 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # type Substance 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # Methods substructure :: ((Tagged 'Left <:.> Tap ((t <:.:> t) := (:*:))) #=@ Substance 'Left (Tap ((t <:.:> t) := (:*:)))) := Available 'Left (Tap ((t <:.:> t) := (:*:))) Source # sub :: (Tap ((t <:.:> t) := (:*:)) #=@ Substance 'Left (Tap ((t <:.:> t) := (:*:)))) := Available 'Left (Tap ((t <:.:> t) := (:*:))) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap Associated Types type Available 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # type Substance 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # Methods substructure :: ((Tagged 'Root <:.> Tap ((t <:.:> t) := (:*:))) #=@ Substance 'Root (Tap ((t <:.:> t) := (:*:)))) := Available 'Root (Tap ((t <:.:> t) := (:*:))) Source # sub :: (Tap ((t <:.:> t) := (:*:)) #=@ Substance 'Root (Tap ((t <:.:> t) := (:*:)))) := Available 'Root (Tap ((t <:.:> t) := (:*:))) Source # | |
Substructure ('Tail :: a -> Segment a) (Construction List) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose Associated Types type Available 'Tail (Construction List) :: Type -> Type Source # type Substance 'Tail (Construction List) :: Type -> Type Source # Methods substructure :: ((Tagged 'Tail <:.> Construction List) #=@ Substance 'Tail (Construction List)) := Available 'Tail (Construction List) Source # sub :: (Construction List #=@ Substance 'Tail (Construction List)) := Available 'Tail (Construction List) Source # | |
Substructure ('Root :: a -> Segment a) (Construction List) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose Associated Types type Available 'Root (Construction List) :: Type -> Type Source # type Substance 'Root (Construction List) :: Type -> Type Source # Methods substructure :: ((Tagged 'Root <:.> Construction List) #=@ Substance 'Root (Construction List)) := Available 'Root (Construction List) Source # sub :: (Construction List #=@ Substance 'Root (Construction List)) := Available 'Root (Construction List) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Covariant (Flip (Constant :: Type -> Type -> Type) b) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (:+:) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (:*:) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (Tagged :: Type -> Type -> Type) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip Validation a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Validation Methods (-<$>-) :: (a0 -> b) -> Flip Validation a a0 -> Flip Validation a b Source # | |
Covariant (Flip Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion Methods (-<$>-) :: (a -> b) -> Flip Conclusion e a -> Flip Conclusion e b Source # | |
Covariant (Constant a :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Tagged tag) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Schematic Monad t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (t :> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Day t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Backwards t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Reverse t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Schematic Comonad t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (t :< u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Prefixed t k) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant ((->) a :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Continuation r t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Continuation Methods (-<$>-) :: (a -> b) -> Continuation r t a -> Continuation r t b Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Pointable u ((->) :: Type -> Type -> Type), Adjoint t' t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Pointable ((t <:<.>:> t') := u) ((->) :: Type -> Type -> Type) Source # | |
(Pointable t ((->) :: Type -> Type -> Type), Pointable u ((->) :: Type -> Type -> Type)) => Pointable (t <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.UT | |
(Pointable u ((->) :: Type -> Type -> Type), Monoid e) => Pointable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Pointable t ((->) :: Type -> Type -> Type), Pointable u ((->) :: Type -> Type -> Type)) => Pointable (t <:.> u) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.TU | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Extractable u ((->) :: Type -> Type -> Type)) => Extractable ((t <:<.>:> t') := u) ((->) :: Type -> Type -> Type) Source # | |
(Extractable t ((->) :: Type -> Type -> Type), Extractable u ((->) :: Type -> Type -> Type)) => Extractable (t <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.UT | |
(Extractable t ((->) :: Type -> Type -> Type), Extractable u ((->) :: Type -> Type -> Type)) => Extractable (t <:.> u) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.TU | |
(Adjoint t' t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Extendable u ((->) :: Type -> Type -> Type)) => Extendable ((t' <:<.>:> t) := u) ((->) :: Type -> Type -> Type) Source # | |
(Semigroup e, Extendable u ((->) :: Type -> Type -> Type)) => Extendable (((->) e :: Type -> Type) <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Extendable u ((->) :: Type -> Type -> Type) => Extendable ((:*:) e <:.> u) ((->) :: Type -> Type -> Type) Source # | |
(Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bindable t ((->) :: Type -> Type -> Type), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:), Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable (t <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Semigroup e, Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Bindable t ((->) :: Type -> Type -> Type), Distributive t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable (t <:.> u) ((->) :: Type -> Type -> Type) Source # | |
(Divariant p ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Contravariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant ((t >:.:> u) := p) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(forall i. Covariant (p i) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bivariant p ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant ((t <:.:> u) := p) ((->) :: Type -> 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)) => Covariant ((t <:<.>:> t') := u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant (t <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant (t <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Traversable u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Traversable (t <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (t <.:> v) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (w <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (t <.:> v) (w <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (t <.:> v) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (t <.:> v) (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (v <:.> t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (v <:.> t) (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (v <:.> t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (u <:.> w) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (v <:.> t) (u <:.> w) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Adjoint t' t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Distributive t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Liftable (t <:<.>:> t') Source # | |
(Adjoint t t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Distributive t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Lowerable (t <:<.>:> t') Source # | |
Covariant (Kan ('Right :: Type -> Wye Type) t u b) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant ((t <:<.>:> u) t') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant ((v <:<.>:> w) v') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t' v' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t v ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint u v ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v' t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint ((t <:<.>:> u) t') ((v <:<.>:> w) v') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Pointable t ((->) :: Type -> Type -> Type) => Liftable (UT Covariant Covariant t) Source # | |
Pointable t ((->) :: Type -> Type -> Type) => Liftable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
Extractable t ((->) :: Type -> Type -> Type) => Lowerable (UT Covariant Covariant t) Source # | |
Extractable t ((->) :: Type -> Type -> Type) => Lowerable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
type Nonempty List Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Nonempty Rose Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose | |
type Nonempty Binary Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
type Combinative List Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Measural 'Length List a Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Measural 'Heighth Binary a Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # | |
type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # | |
type Morphing ('Into (o ds) :: Morph a) Binary Source # | |
type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # | |
type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # | |
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # | |
type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) = Construction Maybe | |
type Morphing ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # | |
type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # | |
type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
type Morphing ('Into List) (Construction Maybe) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # | |
type Morphing ('Into List) (Vector r) Source # | |
type Morphing ('Into Binary) (Construction Wye) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # | |
type Morphing ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # | |
type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
type Zipper List (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # | |
type Morphing ('Pop :: a -> Morph a) List Source # | |
type Morphing ('Push :: a -> Morph a) List Source # | |
type Morphing ('Insert :: a -> Morph a) Binary Source # | |
type Available ('Tail :: a -> Segment a) List Source # | |
type Available ('Root :: a -> Segment a) List Source # | |
type Available ('Right :: a -> Wye a) Binary Source # | |
type Available ('Left :: a -> Wye a) Binary Source # | |
type Substance ('Tail :: a -> Segment a) List Source # | |
type Substance ('Root :: a -> Segment a) List Source # | |
type Substance ('Right :: a -> Wye a) Binary Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
type Substance ('Left :: a -> Wye a) Binary Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
type Available ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
type Available ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
type Available ('Tail :: a -> Segment a) (Construction List) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose | |
type Available ('Root :: a -> Segment a) (Construction List) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose | |
type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
type Substance ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
type Substance ('Tail :: a -> Segment a) (Construction List) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose | |
type Substance ('Root :: a -> Segment a) (Construction List) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose | |
type Available ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
type Available ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
type Substance ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
type Substance ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
(-<$$>-) :: forall t u category a b. (Covariant u category category, Covariant t category category) => category a b -> category (t (u a)) (t (u b)) Source #
(-<<$$>-) :: forall t u source target a b. (Covariant u source source, Covariant t source target) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #
(-<$$>>-) :: forall t u source target a b. (Covariant u source target, Covariant t target target) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #