[Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Bas van Dijk
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
...

The reason I ask is that I want to do something similar for
monad-control's MonadControlIO type class. But I'm not sure if I don't
introduce any undecidability in the type-checker.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Antoine Latter
On Fri, Oct 28, 2011 at 9:11 AM, Bas van Dijk v.dijk@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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Paterson, Ross
Bas van Dijk writes:
 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
 ...

It's done that way in transformers to keep the package portable.
As for doing it elsewhere, although this catch-all instance requires
UndecidableInstances, I don't think it introduces non-termination.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Bas van Dijk
On 28 October 2011 16:23, Antoine Latter aslat...@gmail.com wrote:
 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 actually have never seen a MonadIO instance for a `t m` where 't' is
not a MonadTrans instance.

On 28 October 2011 16:24, Paterson, Ross r.pater...@city.ac.uk wrote:
 It's done that way in transformers to keep the package portable.
 As for doing it elsewhere, although this catch-all instance requires
 UndecidableInstances, I don't think it introduces non-termination.

I understand, portability is important for transformers. For
monad-control it's less of an issue because I already use other
language extensions (incl. RankNTypes).

So I think I go ahead and add a catch-all instance for MonadControlIO
to monad-control.

Thanks for your responses,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Ertugrul Soeylemez
Bas van Dijk v.dijk@gmail.com wrote:

 I understand, portability is important for transformers. For
 monad-control it's less of an issue because I already use other
 language extensions (incl. RankNTypes).

 So I think I go ahead and add a catch-all instance for MonadControlIO
 to monad-control.

I'm not sure whether this will work well.  You will get overlapping
instances, and I don't see a way to hide instances when importing.
Perhaps the OverlappingInstances extension could help here.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Bas van Dijk
On 28 October 2011 16:59, Ertugrul Soeylemez e...@ertes.de wrote:
 I'm not sure whether this will work well.  You will get overlapping
 instances, and I don't see a way to hide instances when importing.
 Perhaps the OverlappingInstances extension could help here.

You're right.

I didn't get an overlapping instances error when building transformers
with this change (Note I didn't remove the custom MonadIO instances).

However when *using* liftIO I did get it:

 runReaderT (liftIO $ putStrLn Hello World!) (10 :: Int)

interactive:0:13:
Overlapping instances for MonadIO (ReaderT Int m0)
  arising from a use of `liftIO'
Matching instances:
  instance MonadIO m = MonadIO (ReaderT r m)
-- Defined at Control/Monad/Trans/Reader.hs:128:10-45
  instance (MonadTrans t, Monad (t m), MonadIO m) = MonadIO (t m)
-- Defined at Control/Monad/IO/Class.hs:43:10-64

Enabling the OverlappingInstances extension does fix it. However I
don't want to force users to use it so I keep the custom instances.

Thanks,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe