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

Pandora.Paradigm.Inventory.Imprint

Documentation

newtype Imprint e a Source #

Constructors

Imprint (e -> a) 

Instances

Instances details
Divariant Imprint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(>->) :: (a -> b) -> (c -> d) -> Imprint b c -> Imprint a d Source #

Interpreted (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Associated Types

type Primary (Imprint e) a Source #

Methods

run :: Imprint e a -> Primary (Imprint e) a Source #

unite :: Primary (Imprint e) a -> Imprint e a Source #

(||=) :: Interpreted u => (Primary (Imprint e) a -> Primary u b) -> Imprint e a -> u b Source #

(=||) :: Interpreted u => (Imprint e a -> u b) -> Primary (Imprint e) a -> Primary u b Source #

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

(<$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Primary (Imprint e) a -> Primary u b) -> ((j :. k) := Imprint e a) -> (j :. k) := u b Source #

(<$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Primary (Imprint e) a -> Primary u b) -> ((j :. (k :. l)) := Imprint e a) -> (j :. (k :. l)) := u b Source #

(<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Primary (Imprint e) a -> Primary u b) -> ((j :. (k :. (l :. m))) := Imprint e a) -> (j :. (k :. (l :. m))) := u b Source #

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

(=||$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Imprint e a -> u b) -> ((j :. k) := Primary (Imprint e) a) -> (j :. k) := Primary u b Source #

(=||$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Imprint e a -> u b) -> ((j :. (k :. l)) := Primary (Imprint e) a) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Imprint e a -> u b) -> ((j :. (k :. (l :. m))) := Primary (Imprint e) a) -> (j :. (k :. (l :. m))) := Primary u b Source #

Monoid e => Comonadic (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

bring :: forall (u :: Type -> Type). Extractable u (->) => (Imprint e :< u) ~> Imprint e Source #

Adjoint (Accumulator e) (Imprint e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Accumulator e a -> b) -> a -> Imprint e b Source #

(|-) :: (a -> Imprint e b) -> Accumulator e a -> b Source #

Monoid e => Extractable (Imprint e) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

extract :: Imprint e a -> a Source #

Semigroup e => Extendable (Imprint e) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(<<=) :: (Imprint e a -> b) -> Imprint e a -> Imprint e b Source #

Covariant (Imprint e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(-<$>-) :: (a -> b) -> Imprint e a -> Imprint e b Source #

Distributive (Imprint e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(-<<) :: Covariant u (->) (->) => (a -> Imprint e b) -> u a -> Imprint e (u b) Source #

Contravariant (Flip Imprint a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(->$<-) :: (a0 -> b) -> Flip Imprint a b -> Flip Imprint a a0 Source #

type Primary (Imprint e) a Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

type Primary (Imprint e) a = e -> a
type Schematic Comonad (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

type Schematic Comonad (Imprint e) = (<.:>) ((->) e :: Type -> Type)

Orphan instances

(Semigroup e, Extendable u ((->) :: Type -> Type -> Type)) => Extendable (((->) e :: Type -> Type) <.:> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Methods

(<<=) :: (((->) e <.:> u) a -> b) -> ((->) e <.:> u) a -> ((->) e <.:> u) b Source #