Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Paradigm.Structure.Modification.Prefixed
Contents
Documentation
newtype Prefixed t k a Source #
Instances
Covariant t => Morphable ('Into t :: Morph (Type -> Type)) (Prefixed t k) Source # | |
Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) Source # | |
Defined in Pandora.Paradigm.Structure.Some.List | |
Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # | |
Setoid k => Morphable ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction List) k) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Rose | |
Setoid k => Morphable ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
Chain key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) Source # | |
Defined in Pandora.Paradigm.Structure.Some.Binary | |
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 # | |
Covariant t => Covariant (Prefixed t k) Source # | |
Defined in Pandora.Paradigm.Structure.Modification.Prefixed Methods (<$>) :: (a -> b) -> Prefixed t k a -> Prefixed t k b Source # comap :: (a -> b) -> Prefixed t k a -> Prefixed t k b Source # (<$) :: a -> Prefixed t k b -> Prefixed t k a Source # ($>) :: Prefixed t k a -> b -> Prefixed t k b Source # void :: Prefixed t k a -> Prefixed t k () Source # loeb :: Prefixed t k (a <:= Prefixed t k) -> Prefixed t k a Source # (<&>) :: Prefixed t k a -> (a -> b) -> Prefixed t k b Source # (<$$>) :: Covariant u => (a -> b) -> ((Prefixed t k :. u) := a) -> (Prefixed t k :. u) := b Source # (<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> ((Prefixed t k :. (u :. v)) := a) -> (Prefixed t k :. (u :. v)) := b Source # (<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((Prefixed t k :. (u :. (v :. w))) := a) -> (Prefixed t k :. (u :. (v :. w))) := b Source # (<&&>) :: Covariant u => ((Prefixed t k :. u) := a) -> (a -> b) -> (Prefixed t k :. u) := b Source # (<&&&>) :: (Covariant u, Covariant v) => ((Prefixed t k :. (u :. v)) := a) -> (a -> b) -> (Prefixed t k :. (u :. v)) := b Source # (<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Prefixed t k :. (u :. (v :. w))) := a) -> (a -> b) -> (Prefixed t k :. (u :. (v :. w))) := b Source # (.#..) :: (Prefixed t k ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source # (.#...) :: (Prefixed t k ~ v a, Prefixed t k ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source # (.#....) :: (Prefixed t k ~ v a, Prefixed t k ~ v b, Prefixed t k ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source # (<$$) :: Covariant u => b -> ((Prefixed t k :. u) := a) -> (Prefixed t k :. u) := b Source # (<$$$) :: (Covariant u, Covariant v) => b -> ((Prefixed t k :. (u :. v)) := a) -> (Prefixed t k :. (u :. v)) := b Source # (<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((Prefixed t k :. (u :. (v :. w))) := a) -> (Prefixed t k :. (u :. (v :. w))) := b Source # ($$>) :: Covariant u => ((Prefixed t k :. u) := a) -> b -> (Prefixed t k :. u) := b Source # ($$$>) :: (Covariant u, Covariant v) => ((Prefixed t k :. (u :. v)) := a) -> b -> (Prefixed t k :. (u :. v)) := b Source # ($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Prefixed t k :. (u :. (v :. w))) := a) -> b -> (Prefixed t k :. (u :. (v :. w))) := b Source # | |
Alternative t => Alternative (Prefixed t k) Source # | |
Avoidable t => Avoidable (Prefixed t k) Source # | |
Interpreted (Prefixed t k) Source # | |
Defined in Pandora.Paradigm.Structure.Modification.Prefixed Methods run :: Prefixed t k a -> Primary (Prefixed t k) a Source # unite :: Primary (Prefixed t k) a -> Prefixed t k a Source # (||=) :: Interpreted u => (Primary (Prefixed t k) a -> Primary u b) -> Prefixed t k a -> u b Source # (=||) :: Interpreted u => (Prefixed t k a -> u b) -> Primary (Prefixed t k) a -> Primary u b Source # (<$||=) :: (Covariant j, Interpreted u) => (Primary (Prefixed t k) a -> Primary u b) -> (j := Prefixed t k a) -> j := u b Source # (<$$||=) :: (Covariant j, Covariant k0, Interpreted u) => (Primary (Prefixed t k) a -> Primary u b) -> ((j :. k0) := Prefixed t k a) -> (j :. k0) := u b Source # (<$$$||=) :: (Covariant j, Covariant k0, Covariant l, Interpreted u) => (Primary (Prefixed t k) a -> Primary u b) -> ((j :. (k0 :. l)) := Prefixed t k a) -> (j :. (k0 :. l)) := u b Source # (<$$$$||=) :: (Covariant j, Covariant k0, Covariant l, Covariant m, Interpreted u) => (Primary (Prefixed t k) a -> Primary u b) -> ((j :. (k0 :. (l :. m))) := Prefixed t k a) -> (j :. (k0 :. (l :. m))) := u b Source # (=||$>) :: (Covariant j, Interpreted u) => (Prefixed t k a -> u b) -> (j := Primary (Prefixed t k) a) -> j := Primary u b Source # (=||$$>) :: (Covariant j, Covariant k0, Interpreted u) => (Prefixed t k a -> u b) -> ((j :. k0) := Primary (Prefixed t k) a) -> (j :. k0) := Primary u b Source # (=||$$$>) :: (Covariant j, Covariant k0, Covariant l, Interpreted u) => (Prefixed t k a -> u b) -> ((j :. (k0 :. l)) := Primary (Prefixed t k) a) -> (j :. (k0 :. l)) := Primary u b Source # (=||$$$$>) :: (Covariant j, Covariant k0, Covariant l, Covariant m, Interpreted u) => (Prefixed t k a -> u b) -> ((j :. (k0 :. (l :. m))) := Primary (Prefixed t k) a) -> (j :. (k0 :. (l :. m))) := Primary u b Source # | |
(Monoid k, Pointable t ((->) :: Type -> Type -> Type)) => Pointable (Prefixed t k) ((->) :: Type -> Type -> Type) Source # | |
Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant_ (Prefixed t k) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (Prefixed t k) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Structure.Modification.Prefixed Methods (<<-) :: (Covariant_ u (->) (->), Pointable u (->), Semimonoidal u (:*:) (->) (->)) => (a -> u b) -> Prefixed t k a -> u (Prefixed t k b) Source # | |
type Morphing ('Into t :: Morph (Type -> Type)) (Prefixed t k) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # | |
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction List) k) Source # | |
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) 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 Nonempty (Prefixed t k) Source # | |
type Primary (Prefixed t k) a Source # | |