Re: [Haskell-cafe] Improving MTL instances

2008-10-15 Thread Antoine Latter
On Wed, Oct 15, 2008 at 5:55 PM, wren ng thornton <[EMAIL PROTECTED]> wrote:
>
> Doing it that way removes the polymorphism that MonadState, MonadReader, etc
> offer to clients. For example, the backwards-state monad[1] is a MonadState
> but not a StateT (without extra plumbing). There are other examples which
> don't even change the semantics. It seems a shame to force these
> implementations to give different names for "the same" functions. Are MPTCs
> onerous? They'll be in haskell-prime afterall. Of course, the fundeps are
> another matter entirely...
>


Slightly off topic - if you do make your backwards-state monad an
instance on MonadState be careful not to use
Control.Monad.State.Class.modify - executing this falls into a black
hole for the backwards-state monad.

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


Re: [Haskell-cafe] Improving MTL instances

2008-10-15 Thread wren ng thornton

Henning Thielemann wrote:

 I long thought that it is unnecessary use of type system extensions to
require multi-parameter type classes for simple monads and its
transformer versions. I thought it would be enough to have atomar monads
like ST, IO and Identity, and monads like State, Reader, Writer,
Continuation can be offered exclusively in the transforming variant.
(State s a) would have to be defined as (StateT s Identity a) instead.
This way MonadState, MonadReader and the other classes become
unnecessary. However, 'lift' remains important with this design.


Doing it that way removes the polymorphism that MonadState, MonadReader, 
etc offer to clients. For example, the backwards-state monad[1] is a 
MonadState but not a StateT (without extra plumbing). There are other 
examples which don't even change the semantics. It seems a shame to 
force these implementations to give different names for "the same" 
functions. Are MPTCs onerous? They'll be in haskell-prime afterall. Of 
course, the fundeps are another matter entirely...


[1] 
http://luqui.org/blog/archives/2008/08/10/mindfuck-the-reverse-state-monad/


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-15 Thread Henning Thielemann
Ryan Ingram schrieb:
> On Mon, Oct 13, 2008 at 2:04 AM, J. Garrett Morris
> <[EMAIL PROTECTED]> wrote:
>> Indeed - MTL seems to have been rewritten at some point in the past to
>> prefer exhaustive enumeration to overlap.
> 
> Indeed, and I actually think this is a weakness of the current
> implementation.  Anyone who comes up with a new transformer that
> provides different functionality than what is there needs to
> explicitly provide all the relevant instances, instead of letting
> MonadTrans do its thing.

 I long thought that it is unnecessary use of type system extensions to
require multi-parameter type classes for simple monads and its
transformer versions. I thought it would be enough to have atomar monads
like ST, IO and Identity, and monads like State, Reader, Writer,
Continuation can be offered exclusively in the transforming variant.
(State s a) would have to be defined as (StateT s Identity a) instead.
This way MonadState, MonadReader and the other classes become
unnecessary. However, 'lift' remains important with this design.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-13 Thread Luke Palmer
On Mon, Oct 13, 2008 at 1:29 AM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> Of course, the point of this message isn't just to complain.  The
> overlap implementation was abhorrent and it *is* better now than it
> was before.  But perhaps there is an abstraction we are missing that
> would allow for better interoperability.  For example, the
> type-compose library documentation at
> http://haskell.org/haskellwiki/TypeCompose mentions that (f :. g) is
> an applicative functor if both f and g are applicative functors, which
> means there is a generic "transformer" for all applicative functors!
> The presense of >>=/join for monads make this more difficult, although
> there is the "product" definition:
>
>> newtype Product m n a = Prod { runProd :: m (Either a (Product n m a)) }
>
> which handles nesting joins by just nesting the monads recursively.
> But in this case it is up to the user to figure out how to untangle
> the spaghetti created, so that's no good.
>
> So, does anyone have any good ideas for improving the interoperability of MTL?

http://sneezy.cs.nott.ac.uk/fplunch/weblog/?p=111

This was on planet haskell a little over a month ago.  It describes
how any monad whose operations look like f (m a) -> m a for some
functor f can be automatically lifted.   If it's possible to phrase a
basis for operations on some transformer this way and then provide
"adapters" for ease of use, that would be one excellent way to improve
interoperability.  Some caveats are mentioned in the post...

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


Re: [Haskell-cafe] Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-13 Thread Stephen Hicks
On Mon, Oct 13, 2008 at 3:29 AM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> On Mon, Oct 13, 2008 at 2:04 AM, J. Garrett Morris
> <[EMAIL PROTECTED]> wrote:
>> Indeed - MTL seems to have been rewritten at some point in the past to
>> prefer exhaustive enumeration to overlap.
>
> Indeed, and I actually think this is a weakness of the current
> implementation.  Anyone who comes up with a new transformer that
> provides different functionality than what is there needs to
> explicitly provide all the relevant instances, instead of letting
> MonadTrans do its thing.

(First of all, sorry for the double reply.)  I'm certainly way out of
my depth here, but would something like associated classes help here?

I'm imagining something like this (I'm sure my syntax is all wrong, though):

> class TypedMonad m where
>   class MonadType m

> instance (MonadTrans m, TypedMonad n) => (MonadType n) (m n)

So then you could write something like

> instance Monad m => TypedMonad (ReaderT i m) where
>   class MonadType (ReaderT i m) = MonadReader

and likewise for Reader, Writer(T), State(T), IO, etc...  Then, for instance

> instance MonadWriter (StateT s (ReaderT r (WriterT w IO)))

is fully-automatic...  Or wouldn't this work, at least once associated
classes is implemented?

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


[Haskell-cafe] Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-13 Thread Ryan Ingram
On Mon, Oct 13, 2008 at 2:04 AM, J. Garrett Morris
<[EMAIL PROTECTED]> wrote:
> Indeed - MTL seems to have been rewritten at some point in the past to
> prefer exhaustive enumeration to overlap.

Indeed, and I actually think this is a weakness of the current
implementation.  Anyone who comes up with a new transformer that
provides different functionality than what is there needs to
explicitly provide all the relevant instances, instead of letting
MonadTrans do its thing.

Consider MonadPrompt (shameless plug, it's on hackage!)  In order to
be fully interoperable with the MTL I'd need to write instances for
MonadState, MonadReader, MonadWriter, MonadError, and MonadCont for
PromptT.  These are unavoidable, although for monads with a "simple
enough" interface, such as State, everything can be accomplished with
"lift".

But I also need to provide the same boilerplate instances for every
other monad transformer in the package to give them instances of
MonadPrompt.  And MonadPrompt *does* have a "simple enough" interface
that it could be accomplished trivially with "lift".

And this ignores interacting with any other transformer library!
Anyone who uses MonadPrompt along with another transformer (like
DatabaseT in the PostgreSQL library) needs to write any instances they
care about themselves, which adds to the difficulty in using the
libraries together.

Of course, the point of this message isn't just to complain.  The
overlap implementation was abhorrent and it *is* better now than it
was before.  But perhaps there is an abstraction we are missing that
would allow for better interoperability.  For example, the
type-compose library documentation at
http://haskell.org/haskellwiki/TypeCompose mentions that (f :. g) is
an applicative functor if both f and g are applicative functors, which
means there is a generic "transformer" for all applicative functors!
The presense of >>=/join for monads make this more difficult, although
there is the "product" definition:

> newtype Product m n a = Prod { runProd :: m (Either a (Product n m a)) }

which handles nesting joins by just nesting the monads recursively.
But in this case it is up to the user to figure out how to untangle
the spaghetti created, so that's no good.

So, does anyone have any good ideas for improving the interoperability of MTL?

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