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

Pandora.Paradigm.Structure.Modification.Prefixed

Documentation

newtype Prefixed t k a Source #

Constructors

Prefixed ((t :. (:*:) k) := a) 

Instances

Instances details
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Morphable ('Into t :: Morph (Type -> Type)) (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Associated Types

type Morphing ('Into t) (Prefixed t k) :: Type -> Type Source #

Methods

morphing :: (Tagged ('Into t) <:.> Prefixed t k) ~> Morphing ('Into t) (Prefixed t k) Source #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed (Construction Maybe) key) :: Type -> Type Source #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed List key) :: Type -> Type Source #

Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Rose k) :: Type -> Type Source #

Chain key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed (Construction Wye) key) :: Type -> Type Source #

Chain k => Morphable ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Vary 'Element) (Prefixed Binary k) :: Type -> Type Source #

Chain k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Binary k) :: Type -> Type Source #

Interpreted (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Associated Types

type Primary (Prefixed t k) a Source #

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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Methods

(-<$>-) :: (a -> b) -> Prefixed t k a -> Prefixed t k b Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (->) (->) (:*:) (:*:) 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 # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

type Morphing ('Into t :: Morph (Type -> Type)) (Prefixed t k) = t
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((->) (Nonempty List k) :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = (((:*:) k <:.> Identity) <:.:> Prefixed Binary k) := ((->) :: Type -> Type -> Type)
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = ((->) k :: Type -> Type) <:.> Maybe
type Nonempty (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

type Nonempty (Prefixed t k) = Prefixed (Nonempty t) k
type Primary (Prefixed t k) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

type Primary (Prefixed t k) a = (t :. (:*:) k) := a

Orphan instances

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Morphable ('Into t :: Morph (Type -> Type)) (Prefixed t k) Source # 
Instance details

Associated Types

type Morphing ('Into t) (Prefixed t k) :: Type -> Type Source #

Methods

morphing :: (Tagged ('Into t) <:.> Prefixed t k) ~> Morphing ('Into t) (Prefixed t k) Source #