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

Pandora.Paradigm.Primary.Transformer.Backwards

Documentation

newtype Backwards t a Source #

Constructors

Backwards (t a) 

Instances

Instances details
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t) => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) <-- Backwards t a Source #

(Semimonoidal (<--) (:*:) (:*:) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t) => Semimonoidal (<--) (:*:) (:*:) (Backwards t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

multiply :: forall (a :: k) (b :: k). (Backwards t a :*: Backwards t b) <-- Backwards t (a :*: b) Source #

Hoistable (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

(/|\) :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant (->) (->) u => (u ~> v) -> Backwards u ~> Backwards v Source #

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant (->) (->) u => (u ~> v) -> Backwards u ~> Backwards v Source #

(Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (Backwards t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

multiply :: forall (a :: k) (b :: k). (Backwards t a :*: Backwards t b) -> Backwards t (a :*: b) Source #

Interpreted (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Associated Types

type Primary (Backwards t) a Source #

Methods

run :: Backwards t a -> Primary (Backwards t) a Source #

unite :: Primary (Backwards t) a -> Backwards t a Source #

(||=) :: Interpreted u => (Primary (Backwards t) a -> Primary u b) -> Backwards t a -> u b Source #

(=||) :: Interpreted u => (Backwards t a -> u b) -> Primary (Backwards t) a -> Primary u b Source #

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

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

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

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

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

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

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

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

Liftable ((->) :: Type -> Type -> Type) (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

lift :: Covariant (->) (->) u => u a -> Backwards u a Source #

Lowerable ((->) :: Type -> Type -> Type) (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

lower :: Covariant (->) (->) u => Backwards u a -> u a Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) -> Backwards t a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

(-<<) :: Covariant (->) (->) u => (a -> Backwards t b) -> u a -> Backwards t (u b) Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (->) (->) (:*:) (:*:) u) => (a -> u b) -> Backwards t a -> u (Backwards t b) Source #

type Primary (Backwards t) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

type Primary (Backwards t) a = t a