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

Pandora.Paradigm.Primary.Functor.Identity

Documentation

newtype Identity a Source #

Constructors

Identity a 

Instances

Instances details
Monoidal (-->) ((->) :: Type -> Type -> Type) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

Semigroup a => Semigroup (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(+) :: Identity a -> Identity a -> Identity a Source #

Ringoid a => Ringoid (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(*) :: Identity a -> Identity a -> Identity a Source #

Monoid a => Monoid (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

zero :: Identity a Source #

Quasiring a => Quasiring (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

one :: Identity a Source #

Group a => Group (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Supremum a => Supremum (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(\/) :: Identity a -> Identity a -> Identity a Source #

Infimum a => Infimum (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(/\) :: Identity a -> Identity a -> Identity a Source #

Lattice a => Lattice (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Setoid a => Setoid (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Chain a => Chain (Identity a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Semigroupoid (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Methods

(.) :: Lens Identity b c -> Lens Identity a b -> Lens Identity a c Source #

Category (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Semimonoidal (-->) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

mult :: forall (a :: k) (b :: k). (Identity a :*: Identity b) --> Identity (a :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

mult :: forall (a :: k) (b :: k). (Identity a :*: Identity b) <-- Identity (a :*: b) Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Impliable (P_Q_T ((->) :: Type -> Type -> Type) Store Identity source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Associated Types

type Arguments (P_Q_T (->) Store Identity source target) = (args :: Type) Source #

Methods

imply :: Arguments (P_Q_T (->) Store Identity source target) Source #

Extendable ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(<<=) :: (Identity a -> b) -> Identity a -> Identity b Source #

Bindable ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(=<<) :: (a -> Identity b) -> Identity a -> Identity b Source #

Monad ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Comonad ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Extendable ((->) :: Type -> Type -> Type) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(<$>) :: (a -> b) -> Identity a -> Identity b Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(-|) :: (Identity a -> b) -> a -> Identity b Source #

(|-) :: (a -> Identity b) -> Identity a -> b Source #

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

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 # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Identity source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Identity source target :: Type) = (source -> target) -> (source -> target -> source) -> Lens Identity source target
type Zipper (Construction Identity) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Zipper (Construction Identity) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) = Tap ((Stream <:.:> Stream) := (:*:))