category-0.2.5.0: Categorical types and classes

Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Trans.Identity

Synopsis

Documentation

newtype IdentityT (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #

The trivial monad transformer, which maps a monad to an equivalent monad.

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 Control.Categorical.Functor

Methods

map :: s a b -> 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 Control.Categorical.Monad

Methods

map :: s a b -> Kleisli (->) m (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 Control.Categorical.Monad

Methods

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

MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

lift :: Monad m => m a -> IdentityT m a #

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

Defined in Control.Categorical.Monad

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 Control.Categorical.Monad

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 #

Monad m => Monad (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

(>>=) :: IdentityT m a -> (a -> IdentityT m b) -> IdentityT m b #

(>>) :: IdentityT m a -> IdentityT m b -> IdentityT m b #

return :: a -> IdentityT m a #

fail :: String -> IdentityT m a #

Functor m => Functor (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

fmap :: (a -> b) -> IdentityT m a -> IdentityT m b #

(<$) :: a -> IdentityT m b -> IdentityT m a #

MonadFix m => MonadFix (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

mfix :: (a -> IdentityT m a) -> IdentityT m a #

MonadFail m => MonadFail (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

fail :: String -> IdentityT m a #

Applicative m => Applicative (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

pure :: a -> IdentityT m a #

(<*>) :: IdentityT m (a -> b) -> IdentityT m a -> IdentityT m b #

liftA2 :: (a -> b -> c) -> IdentityT m a -> IdentityT m b -> IdentityT m c #

(*>) :: IdentityT m a -> IdentityT m b -> IdentityT m b #

(<*) :: IdentityT m a -> IdentityT m b -> IdentityT m a #

Foldable f => Foldable (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

fold :: Monoid m => IdentityT f m -> m #

foldMap :: Monoid m => (a -> m) -> IdentityT f a -> m #

foldr :: (a -> b -> b) -> b -> IdentityT f a -> b #

foldr' :: (a -> b -> b) -> b -> IdentityT f a -> b #

foldl :: (b -> a -> b) -> b -> IdentityT f a -> b #

foldl' :: (b -> a -> b) -> b -> IdentityT f a -> b #

foldr1 :: (a -> a -> a) -> IdentityT f a -> a #

foldl1 :: (a -> a -> a) -> IdentityT f a -> a #

toList :: IdentityT f a -> [a] #

null :: IdentityT f a -> Bool #

length :: IdentityT f a -> Int #

elem :: Eq a => a -> IdentityT f a -> Bool #

maximum :: Ord a => IdentityT f a -> a #

minimum :: Ord a => IdentityT f a -> a #

sum :: Num a => IdentityT f a -> a #

product :: Num a => IdentityT f a -> a #

Traversable f => Traversable (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

traverse :: Applicative f0 => (a -> f0 b) -> IdentityT f a -> f0 (IdentityT f b) #

sequenceA :: Applicative f0 => IdentityT f (f0 a) -> f0 (IdentityT f a) #

mapM :: Monad m => (a -> m b) -> IdentityT f a -> m (IdentityT f b) #

sequence :: Monad m => IdentityT f (m a) -> m (IdentityT f a) #

Contravariant f => Contravariant (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

contramap :: (a -> b) -> IdentityT f b -> IdentityT f a #

(>$) :: b -> IdentityT f b -> IdentityT f a #

Eq1 f => Eq1 (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftEq :: (a -> b -> Bool) -> IdentityT f a -> IdentityT f b -> Bool #

Ord1 f => Ord1 (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftCompare :: (a -> b -> Ordering) -> IdentityT f a -> IdentityT f b -> Ordering #

Read1 f => Read1 (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (IdentityT f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [IdentityT f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (IdentityT f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [IdentityT f a] #

Show1 f => Show1 (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> IdentityT f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [IdentityT f a] -> ShowS #

MonadZip m => MonadZip (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

mzip :: IdentityT m a -> IdentityT m b -> IdentityT m (a, b) #

mzipWith :: (a -> b -> c) -> IdentityT m a -> IdentityT m b -> IdentityT m c #

munzip :: IdentityT m (a, b) -> (IdentityT m a, IdentityT m b) #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

Alternative m => Alternative (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

empty :: IdentityT m a #

(<|>) :: IdentityT m a -> IdentityT m a -> IdentityT m a #

some :: IdentityT m a -> IdentityT m [a] #

many :: IdentityT m a -> IdentityT m [a] #

MonadPlus m => MonadPlus (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

mzero :: IdentityT m a #

mplus :: IdentityT m a -> IdentityT m a -> IdentityT m a #

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 Control.Categorical.Functor

Methods

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

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

Defined in Control.Categorical.Monad

Methods

map :: NT (Kleisli (Dual (->)) m) a b -> NT (Kleisli (Dual (->)) m) (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 Control.Categorical.Monad

Methods

map :: NT (Kleisli (->) m) a b -> NT (Kleisli (->) m) (IdentityT a) (IdentityT 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 Control.Categorical.Monad

Methods

map :: NT (Cokleisli (->) ɯ) a b -> NT (Cokleisli (->) ɯ) (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 Control.Categorical.Monad

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 (NT ((->) :: Type -> Type -> Type) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Control.Categorical.Monad

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) ɯ => Comonad (NT (Cokleisli ((->) :: Type -> Type -> Type) ɯ) :: (k -> Type) -> (k -> Type) -> Type) (IdentityT :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Control.Categorical.Monad

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 #

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

Defined in Control.Categorical.Monad

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 #

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 Control.Categorical.Monad

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 #

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 Control.Categorical.Monad

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 #

(Eq1 f, Eq a) => Eq (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

(==) :: IdentityT f a -> IdentityT f a -> Bool #

(/=) :: IdentityT f a -> IdentityT f a -> Bool #

(Ord1 f, Ord a) => Ord (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

compare :: IdentityT f a -> IdentityT f a -> Ordering #

(<) :: IdentityT f a -> IdentityT f a -> Bool #

(<=) :: IdentityT f a -> IdentityT f a -> Bool #

(>) :: IdentityT f a -> IdentityT f a -> Bool #

(>=) :: IdentityT f a -> IdentityT f a -> Bool #

max :: IdentityT f a -> IdentityT f a -> IdentityT f a #

min :: IdentityT f a -> IdentityT f a -> IdentityT f a #

(Read1 f, Read a) => Read (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

(Show1 f, Show a) => Show (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

showsPrec :: Int -> IdentityT f a -> ShowS #

show :: IdentityT f a -> String #

showList :: [IdentityT f a] -> ShowS #