[Haskell-cafe] A catch-all MonadIO instance

Antoine Latter aslatter at gmail.com
Fri Oct 28 16:23:09 CEST 2011


On Fri, Oct 28, 2011 at 9:11 AM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> Hello,
>
> Is it unsafe to add the following catch-all MonadIO instance to
> transformers' Control.Monad.IO.Class module?
>
> {-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
>
> instance (MonadTrans t, Monad (t m), MonadIO m) => MonadIO (t m) where
>    liftIO = lift . liftIO
>
> It could get rid of all the similarly looking instances:
>
> instance (MonadIO m) => MonadIO (ReaderT r m) where
>    liftIO = lift . liftIO
> instance (MonadIO m) => MonadIO (StateT s m) where
>    liftIO = lift . liftIO
> instance (Monoid w, MonadIO m) => MonadIO (WriterT w m) where
>    liftIO = lift . liftIO
> ...
>

I would then need OverlappingInstances to declare a MonadIO instance
for any similar looking instance head (that is `t m`) where 't' was
not a proper MonadTrans instance, which sounds like a common enough
things to do.

I usually don't bother writing a MonadTrans instance in my own apps,
and I try to avoid using OverlappingInstances unless there's no other
way to do something.

Although I don't have a better solution to offer for the exploding
instance problem with mtl-like libraries.

Antoine



More information about the Haskell-Cafe mailing list