Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class (Semigroupoid source, Semigroupoid target) => Covariant source target t where
- (-<$>-) :: source a b -> target (t a) (t b)
- (-<$$>-) :: forall t u category a b. (Covariant category category u, Covariant category category t) => category a b -> category (t (u a)) (t (u b))
- (-<<$$>-) :: forall t u source target a b. (Covariant source source u, Covariant source target t) => source a b -> target (t (u a)) (t (u b))
- (-<$$>>-) :: forall source target t u a b. (Covariant source target u, Covariant target target t) => source a b -> target (t (u a)) (t (u b))
- (-<$$$>-) :: forall t u v category a b. (Covariant category category t, Covariant category category u, Covariant category category v) => category a b -> category (t (u (v a))) (t (u (v b)))
- (-<$$$$>-) :: forall category t u v w a b. (Covariant category category t, Covariant category category u, Covariant category category v, Covariant category category w) => category a b -> category (t (u (v (w a)))) (t (u (v (w b))))
Documentation
class (Semigroupoid source, Semigroupoid target) => Covariant source target t where Source #
When providing a new instance, you should ensure it satisfies: * Identity morphism: (identity -<$>-) ≡ identity * Interpreted of morphisms: (f . g -<$>-) ≡ (f -<$>-) . (g -<$>-)
Instances
Stack List Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Measurable 'Length List Source # | |
Measurable 'Heighth Binary Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal (<--) (:*:) (:*:) t, Semimonoidal (<--) (:*:) (:*:) t', Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t t') => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <:.> u) 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 # | |
(Semimonoidal (<--) (:*:) (:*:) t, Semimonoidal (<--) (:*:) (:*:) u) => Semimonoidal (<--) (:*:) (:*:) ((t <:.:> u) := (:*:) :: Type -> Type) 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 # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal (<--) (:*:) (:*:) t, Semimonoidal (<--) (:*:) (:*:) u) => Semimonoidal (<--) (:*:) (:*:) (t <.:> u :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (<--) (:*:) (:*:) t, Semimonoidal (<--) (:*:) (:*:) u) => Semimonoidal (<--) (:*:) (:*:) (t <:.> u :: Type -> Type) Source # | |
(Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion catch :: forall (a :: k). (Conclusion e <.:> u) a -> (e -> (Conclusion e <.:> u) a) -> (Conclusion e <.:> u) a 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 # | |
Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (Tap ((t <:.:> t) := (:*:)) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:+:) t) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:+:) (t <:.> u :: Type -> Type) Source # | |
Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:.:> t) := (:*:) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t') => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <:.> u :: Type -> Type) Source # | |
Morphable ('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) := (:*:))) :: Type -> Type Source # 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 # | |
Defined in Pandora.Paradigm.Structure.Some.Stream | |
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 # | |
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 | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Hoistable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.TU (/|\) :: 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 # | |
Extendable ((->) :: Type -> Type -> Type) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Extendable ((->) :: Type -> Type -> Type) (Tap ((List <:.:> List) := (:*:))) 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap type Available 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # type Substance 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap type Available 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # type Substance 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap type Available 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # type Substance 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source # 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 type Available 'Tail (Construction List) :: Type -> Type Source # type Substance 'Tail (Construction List) :: Type -> Type Source # 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 type Available 'Root (Construction List) :: Type -> Type Source # type Substance 'Root (Construction List) :: Type -> Type Source # 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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Wye Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Edges Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Maybe Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Biforked Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) (t <:.> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t', Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <:.> u) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:+:) s) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Yoneda t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Outline t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:*:) s) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Jet t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Jack t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Wedge e) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Validation e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Validation (-<$>-) :: (a -> b) -> Validation e a -> Validation e b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (These e) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Instruction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction (-<$>-) :: (a -> b) -> Instruction t a -> Instruction t b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Construction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Construction (-<$>-) :: (a -> b) -> Construction t a -> Construction t b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Conclusion e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion (-<$>-) :: (a -> b) -> Conclusion e a -> Conclusion e b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <:.> Construction t) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Comprehension t) Source # | |
Defined in Pandora.Paradigm.Structure.Modification.Comprehension (-<$>-) :: (a -> b) -> Comprehension t a -> Comprehension t b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Store s) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tap t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (State s) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Imprint e) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Equipment e) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Environment e) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment (-<$>-) :: (a -> b) -> Environment e a -> Environment e b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator (-<$>-) :: (a -> b) -> Accumulator e a -> Accumulator e b Source # | |
Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tap ((t <:.:> t) := (:*:))) Source # | |
Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tap ((List <:.:> List) := (:*:))) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (Constant :: Type -> Type -> Type) b) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (:+:) a) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (:*:) a) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Validation a) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Validation (-<$>-) :: (a0 -> b) -> Flip Validation a a0 -> Flip Validation a b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip (Tagged :: Type -> Type -> Type) a) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Conclusion e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion (-<$>-) :: (a -> b) -> Flip Conclusion e a -> Flip Conclusion e b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Constant a :: Type -> Type) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Day t u) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tagged tag) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :< u) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Prefixed t k) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) a :: Type -> Type) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Continuation r t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Continuation (-<$>-) :: (a -> b) -> Continuation r t a -> Continuation r t b Source # | |
(Divariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) p, Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t >:.:> u) := p) Source # | |
(forall i. Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (p i), Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) p, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:.:> u) := p) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:<.>:> t') := u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <:.> u) Source # | |
(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <:.> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <:.> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v) (w <:.> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <.:> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v) (w <.:> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <.:> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t) (w <.:> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (u <:.> w), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t) (u <:.> w) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Kan ('Right :: Type -> Wye Type) t u b) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:<.>:> u) t'), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((v <:<.>:> w) v'), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t w, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' v', Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t v, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u v, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v' t') => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t <:<.>:> u) t') ((v <:<.>:> w) v') Source # | |
(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) ((t' <:<.>:> t) := u) Source # | |
(Semigroup e, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) (((->) e :: Type -> Type) <.:> u) Source # | |
Extendable ((->) :: Type -> Type -> Type) u => Extendable ((->) :: Type -> Type -> Type) ((:*:) e <:.> u) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) ((t <:<.>:> t') := u) Source # | |
(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Bindable ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <.:> u) Source # | |
(Bindable ((->) :: Type -> Type -> Type) t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <:.> u) Source # | |
(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t) => Liftable ((->) :: Type -> Type -> Type) (t <:<.>:> t') Source # | |
(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t t', Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t') => Lowerable ((->) :: Type -> Type -> Type) (t <:<.>:> t') Source # | |
Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Liftable ((->) :: Type -> Type -> Type) (UT Covariant Covariant t) Source # | |
Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Liftable ((->) :: Type -> Type -> Type) (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Lowerable ((->) :: Type -> Type -> Type) (UT Covariant Covariant t) Source # | |
Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Lowerable ((->) :: Type -> Type -> Type) (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 category category u, Covariant category category t) => category a b -> category (t (u a)) (t (u b)) Source #
(-<<$$>-) :: forall t u source target a b. (Covariant source source u, Covariant source target t) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #
(-<$$>>-) :: forall source target t u a b. (Covariant source target u, Covariant target target t) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #