pandora-0.4.4: 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
Covariant Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

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

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

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

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

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

(<$$>) :: Covariant u => (a -> b) -> ((Identity :. u) := a) -> (Identity :. u) := b Source #

(<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> ((Identity :. (u :. v)) := a) -> (Identity :. (u :. v)) := b Source #

(<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((Identity :. (u :. (v :. w))) := a) -> (Identity :. (u :. (v :. w))) := b Source #

(<&&>) :: Covariant u => ((Identity :. u) := a) -> (a -> b) -> (Identity :. u) := b Source #

(<&&&>) :: (Covariant u, Covariant v) => ((Identity :. (u :. v)) := a) -> (a -> b) -> (Identity :. (u :. v)) := b Source #

(<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Identity :. (u :. (v :. w))) := a) -> (a -> b) -> (Identity :. (u :. (v :. w))) := b Source #

(.#..) :: (Identity ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: (Identity ~ v a, Identity ~ 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 #

(.#....) :: (Identity ~ v a, Identity ~ v b, Identity ~ 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 -> ((Identity :. u) := a) -> (Identity :. u) := b Source #

(<$$$) :: (Covariant u, Covariant v) => b -> ((Identity :. (u :. v)) := a) -> (Identity :. (u :. v)) := b Source #

(<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((Identity :. (u :. (v :. w))) := a) -> (Identity :. (u :. (v :. w))) := b Source #

($$>) :: Covariant u => ((Identity :. u) := a) -> b -> (Identity :. u) := b Source #

($$$>) :: (Covariant u, Covariant v) => ((Identity :. (u :. v)) := a) -> b -> (Identity :. (u :. v)) := b Source #

($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Identity :. (u :. (v :. w))) := a) -> b -> (Identity :. (u :. (v :. w))) := b Source #

Applicative Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

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

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

forever :: Identity a -> Identity b Source #

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

(<**>) :: Applicative u => ((Identity :. u) := (a -> b)) -> ((Identity :. u) := a) -> (Identity :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Identity :. (u :. v)) := (a -> b)) -> ((Identity :. (u :. v)) := a) -> (Identity :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Identity :. (u :. (v :. w))) := (a -> b)) -> ((Identity :. (u :. (v :. w))) := a) -> (Identity :. (u :. (v :. w))) := b Source #

Monad Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Representable Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Associated Types

type Representation Identity Source #

Adjoint Identity Identity ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

extract :: Identity a -> a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

point :: a -> Identity a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(<<-) :: (Covariant_ u (->) (->), Pointable u (->), Semimonoidal u (:*:) (->) (->)) => (a -> u b) -> Identity a -> u (Identity b) Source #

Category (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

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 #

type Representation Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

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) := (:*:))