Adding IdentityT to mtl

I wanted an IdentityT today, for extending xmonad. (The idea is to allower user-defined monad transformers, so users can plug in their own semantics easily). By default it would use IdentityT, which I note is not in mtl! Here's roughly what it would be: ----------------------------------------------------------------------------- -- | -- Module : Identity.hs -- License : BSD3-style (see LICENSE) -- module IdentityT where import Control.Monad.Trans -- -- IdentityT , a parameterisable identity monad, with an inner monad -- The user's default monad transformer -- newtype IdentityT m a = IdentityT { runIdentityT :: m a } instance (Functor m, Monad m) => Functor (IdentityT m) where fmap f = IdentityT . fmap f . runIdentityT instance (Monad m) => Monad (IdentityT m) where return = IdentityT . return m >>= k = IdentityT $ runIdentityT . k =<< runIdentityT m fail msg = IdentityT $ fail msg instance (MonadIO m) => MonadIO (IdentityT m) where liftIO = IdentityT . liftIO Any reasons why this shouldn't be in mtl? -- Don

Hi,
Just curious, could you say a bit more about what you plan to use this for?
By the way, if IdentityT is added, then it should have instances for
all the classes---Reader,Writer,etc. Also the Functor instance does
not need the Monad constraint on "m".
-Iavor
On 5/31/07, Donald Bruce Stewart
I wanted an IdentityT today, for extending xmonad. (The idea is to allower user-defined monad transformers, so users can plug in their own semantics easily).
By default it would use IdentityT, which I note is not in mtl!
Here's roughly what it would be:
----------------------------------------------------------------------------- -- | -- Module : Identity.hs -- License : BSD3-style (see LICENSE) -- module IdentityT where
import Control.Monad.Trans
-- -- IdentityT , a parameterisable identity monad, with an inner monad -- The user's default monad transformer --
newtype IdentityT m a = IdentityT { runIdentityT :: m a }
instance (Functor m, Monad m) => Functor (IdentityT m) where fmap f = IdentityT . fmap f . runIdentityT
instance (Monad m) => Monad (IdentityT m) where return = IdentityT . return m >>= k = IdentityT $ runIdentityT . k =<< runIdentityT m fail msg = IdentityT $ fail msg
instance (MonadIO m) => MonadIO (IdentityT m) where liftIO = IdentityT . liftIO
Any reasons why this shouldn't be in mtl?
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

iavor.diatchki:
Hi,
Just curious, could you say a bit more about what you plan to use this for?
Yes, in Xmonad, we're considering a flexible way for users to extend the application. One way would be to provide their own monad transformer (so they could thread state, or add new effects and so on). The ticket for this is here: http://www.haskell.org/pipermail/xmonad/2007-June/000476.html Current xmonad runs in: newtype X a = X (ReaderT XConf (StateT XState IO) a) but we'd allow user-specified state, or logging , or so on with, newtype X a = X (ReaderT XConf (StateT XState (UserT IO)) a) by default though, UserT would be: type UserT = IdentityT runUserT :: Monad m => UserT m a -> m a but could be, say, type UserT = StateT UserState
By the way, if IdentityT is added, then it should have instances for all the classes---Reader,Writer,etc. Also the Functor instance does not need the Monad constraint on "m".
Yes, that's just a quick draft. It would need the other instances. Seems useful? -- Don

Whatever happened to the suggestion of extending mtl with IdentityT? I
think it's reasonable, especially since we have a documented use case.
/Josef
On 6/1/07, Donald Bruce Stewart
I wanted an IdentityT today, for extending xmonad. (The idea is to allower user-defined monad transformers, so users can plug in their own semantics easily).
By default it would use IdentityT, which I note is not in mtl!
Here's roughly what it would be:
----------------------------------------------------------------------------- -- | -- Module : Identity.hs -- License : BSD3-style (see LICENSE) -- module IdentityT where
import Control.Monad.Trans
-- -- IdentityT , a parameterisable identity monad, with an inner monad -- The user's default monad transformer --
newtype IdentityT m a = IdentityT { runIdentityT :: m a }
instance (Functor m, Monad m) => Functor (IdentityT m) where fmap f = IdentityT . fmap f . runIdentityT
instance (Monad m) => Monad (IdentityT m) where return = IdentityT . return m >>= k = IdentityT $ runIdentityT . k =<< runIdentityT m fail msg = IdentityT $ fail msg
instance (MonadIO m) => MonadIO (IdentityT m) where liftIO = IdentityT . liftIO
Any reasons why this shouldn't be in mtl?
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi,
I comlpletely forgot about this. I have added two new transformers to
monadLib: IdT and LiftT, the second one using a strict bind. These
changes are available in the darcs repository. When I get around to
playing around with them a bit more I will make a new package and put
it on hackage.
-Iavor
On 8/28/07, Josef Svenningsson
Whatever happened to the suggestion of extending mtl with IdentityT? I think it's reasonable, especially since we have a documented use case.
/Josef
On 6/1/07, Donald Bruce Stewart
wrote: I wanted an IdentityT today, for extending xmonad. (The idea is to allower user-defined monad transformers, so users can plug in their own semantics easily).
By default it would use IdentityT, which I note is not in mtl!
Here's roughly what it would be:
----------------------------------------------------------------------------- -- | -- Module : Identity.hs -- License : BSD3-style (see LICENSE) -- module IdentityT where
import Control.Monad.Trans
-- -- IdentityT , a parameterisable identity monad, with an inner monad -- The user's default monad transformer --
newtype IdentityT m a = IdentityT { runIdentityT :: m a }
instance (Functor m, Monad m) => Functor (IdentityT m) where fmap f = IdentityT . fmap f . runIdentityT
instance (Monad m) => Monad (IdentityT m) where return = IdentityT . return m >>= k = IdentityT $ runIdentityT . k =<< runIdentityT m fail msg = IdentityT $ fail msg
instance (MonadIO m) => MonadIO (IdentityT m) where liftIO = IdentityT . liftIO
Any reasons why this shouldn't be in mtl?
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Thanks Iavor! iavor.diatchki:
Hi, I comlpletely forgot about this. I have added two new transformers to monadLib: IdT and LiftT, the second one using a strict bind. These changes are available in the darcs repository. When I get around to playing around with them a bit more I will make a new package and put it on hackage. -Iavor
On 8/28/07, Josef Svenningsson
wrote: Whatever happened to the suggestion of extending mtl with IdentityT? I think it's reasonable, especially since we have a documented use case.
/Josef
On 6/1/07, Donald Bruce Stewart
wrote: I wanted an IdentityT today, for extending xmonad. (The idea is to allower user-defined monad transformers, so users can plug in their own semantics easily).
By default it would use IdentityT, which I note is not in mtl!
Here's roughly what it would be:
----------------------------------------------------------------------------- -- | -- Module : Identity.hs -- License : BSD3-style (see LICENSE) -- module IdentityT where
import Control.Monad.Trans
-- -- IdentityT , a parameterisable identity monad, with an inner monad -- The user's default monad transformer --
newtype IdentityT m a = IdentityT { runIdentityT :: m a }
instance (Functor m, Monad m) => Functor (IdentityT m) where fmap f = IdentityT . fmap f . runIdentityT
instance (Monad m) => Monad (IdentityT m) where return = IdentityT . return m >>= k = IdentityT $ runIdentityT . k =<< runIdentityT m fail msg = IdentityT $ fail msg
instance (MonadIO m) => MonadIO (IdentityT m) where liftIO = IdentityT . liftIO
Any reasons why this shouldn't be in mtl?
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (3)
-
dons@cse.unsw.edu.au
-
Iavor Diatchki
-
Josef Svenningsson