category-0.2.4.0: Categorical types and classes

Safe HaskellNone
LanguageHaskell2010

Data.Functor.Trans.Identity

Documentation

newtype IdentityT f a Source #

Constructors

IdentityT 

Fields

Instances
Functor s ((->) :: Type -> Type -> Type) f => Functor (s :: k -> k -> Type) ((->) :: Type -> Type -> Type) (IdentityT f :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

map :: s a b -> IdentityT f a -> IdentityT f b Source #

(Functor s (Cokleisli ((->) :: Type -> Type -> Type) ɯ) f, Endofunctor ((->) :: Type -> Type -> Type) ɯ) => Functor (s :: k -> k -> Type) (Cokleisli ((->) :: Type -> Type -> Type) ɯ :: Type -> Type -> Type) (IdentityT f :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

map :: s a b -> Cokleisli (->) ɯ (IdentityT f a) (IdentityT f b) Source #

(Functor s (Kleisli ((->) :: Type -> Type -> Type) m) f, Endofunctor ((->) :: Type -> Type -> Type) m) => Functor (s :: k -> k -> Type) (Kleisli ((->) :: Type -> Type -> Type) m :: Type -> Type -> Type) (IdentityT f :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

map :: s a b -> Kleisli (->) m (IdentityT f a) (IdentityT f b) Source #

Comonad ((->) :: Type -> Type -> Type) f => Comonad ((->) :: Type -> Type -> Type) (IdentityT f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

counit :: IdentityT f a -> a Source #

cut :: IdentityT f a -> IdentityT f (IdentityT f a) Source #

cobind :: (IdentityT f a -> b) -> IdentityT f a -> IdentityT f b Source #

Monad ((->) :: Type -> Type -> Type) f => Monad ((->) :: Type -> Type -> Type) (IdentityT f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

unit :: a -> IdentityT f a Source #

join :: IdentityT f (IdentityT f a) -> IdentityT f a Source #

bind :: (a -> IdentityT f b) -> IdentityT f a -> IdentityT f b Source #

Comonad ((->) :: Type -> Type -> Type) ɯ => Functor (NT (Cokleisli ((->) :: Type -> Type -> Type) ɯ) :: (k -> Type) -> (k -> Type) -> Type) (NT (Cokleisli ((->) :: Type -> Type -> Type) ɯ) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

map :: NT (Cokleisli (->) ɯ) a b -> NT (Cokleisli (->) ɯ) (IdentityT a) (IdentityT b) Source #

Monad ((->) :: Type -> Type -> Type) m => Functor (NT (Kleisli ((->) :: Type -> Type -> Type) m) :: (k -> Type) -> (k -> Type) -> Type) (NT (Kleisli ((->) :: Type -> Type -> Type) m) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

map :: NT (Kleisli (->) m) a b -> NT (Kleisli (->) m) (IdentityT a) (IdentityT b) Source #

Functor (NT ((->) :: Type -> Type -> Type) :: (k -> Type) -> (k -> Type) -> Type) (NT ((->) :: Type -> Type -> Type) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

map :: NT (->) a b -> NT (->) (IdentityT a) (IdentityT b) Source #

Monad ((->) :: Type -> Type -> Type) m => Comonad (NT (Kleisli ((->) :: Type -> Type -> Type) m) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

counit :: NT (Kleisli (->) m) (IdentityT a) a Source #

cut :: NT (Kleisli (->) m) (IdentityT a) (IdentityT (IdentityT a)) Source #

cobind :: NT (Kleisli (->) m) (IdentityT a) b -> NT (Kleisli (->) m) (IdentityT a) (IdentityT b) Source #

Comonad ((->) :: Type -> Type -> Type) ɯ => Comonad (NT (Cokleisli ((->) :: Type -> Type -> Type) ɯ) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

counit :: NT (Cokleisli (->) ɯ) (IdentityT a) a Source #

cut :: NT (Cokleisli (->) ɯ) (IdentityT a) (IdentityT (IdentityT a)) Source #

cobind :: NT (Cokleisli (->) ɯ) (IdentityT a) b -> NT (Cokleisli (->) ɯ) (IdentityT a) (IdentityT b) Source #

Comonad (NT ((->) :: Type -> Type -> Type) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

counit :: NT (->) (IdentityT a) a Source #

cut :: NT (->) (IdentityT a) (IdentityT (IdentityT a)) Source #

cobind :: NT (->) (IdentityT a) b -> NT (->) (IdentityT a) (IdentityT b) Source #

Comonad ((->) :: Type -> Type -> Type) ɯ => Monad (NT (Cokleisli ((->) :: Type -> Type -> Type) ɯ) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

unit :: NT (Cokleisli (->) ɯ) a (IdentityT a) Source #

join :: NT (Cokleisli (->) ɯ) (IdentityT (IdentityT a)) (IdentityT a) Source #

bind :: NT (Cokleisli (->) ɯ) a (IdentityT b) -> NT (Cokleisli (->) ɯ) (IdentityT a) (IdentityT b) Source #

Monad ((->) :: Type -> Type -> Type) m => Monad (NT (Kleisli ((->) :: Type -> Type -> Type) m) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

unit :: NT (Kleisli (->) m) a (IdentityT a) Source #

join :: NT (Kleisli (->) m) (IdentityT (IdentityT a)) (IdentityT a) Source #

bind :: NT (Kleisli (->) m) a (IdentityT b) -> NT (Kleisli (->) m) (IdentityT a) (IdentityT b) Source #

Monad (NT ((->) :: Type -> Type -> Type) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Functor.Trans.Identity

Methods

unit :: NT (->) a (IdentityT a) Source #

join :: NT (->) (IdentityT (IdentityT a)) (IdentityT a) Source #

bind :: NT (->) a (IdentityT b) -> NT (->) (IdentityT a) (IdentityT b) Source #