Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Jonathan Cast
On Mon, 2008-10-13 at 18:28 +0100, Andrew Coppin wrote:
 Reid Barton wrote:
  It's not difficult: the operation is called
 
  mplus :: MyMonad a - MyMonad a - MyMonad a
 
  and already exists (assuming the author of ListT has not forgotten to
  write a MonadPlus instance).

 
 I see... I was under the impression that mplus is just any arbitrary 
 binary operation over a given monad. How do you know what it does for a 
 specific monad?

Process of elimination.  Sometimes, this doesn't narrow things down to a
single operation, but it gives you a good idea of what you're supposed
to expect.

Firstly, mplus and mzero form a (natural) monoid, put together.  That
rules out a number of binary operations right there.

Secondly, mzero has a null law with (=):

  mzero = f = mzero

So, if you have

  a `mplus` b

and a calls mzero at some point (not inside another call to mplus ---
nice and informal, that description :), then you know b will be executed
instead.  (Maybe b will be executed *anyway*.  I didn't say anything
about that).

So mplus and mzero are basically suitable for three kinds of things:

* Exception handling
* Back-tracking
* Parallelism

Usually, when you see a MonadPlus instance, you expect one or more of
these.

That's in the general case.

ListT is a special case; the (somewhat idealized) specification of ListT
(what people want to happen when they use ListT) is that ListT m in some
sense `adds back-tracking' to m.  Where back-tracking choice is
implemented by mplus.

jcc


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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Andrew Coppin

Reid Barton wrote:

It's not difficult: the operation is called

mplus :: MyMonad a - MyMonad a - MyMonad a

and already exists (assuming the author of ListT has not forgotten to
write a MonadPlus instance).
  


I see... I was under the impression that mplus is just any arbitrary 
binary operation over a given monad. How do you know what it does for a 
specific monad?


Anyway, utilising this trick, I now have my function working quite well. 
Implementing negation is the only hard part; I need to unwind everything 
down to the list level, and check whether the list is empty, and do 
something different depending on whether it is or it isn't:


 foo = do
   ...
   let x = run_some_moadic_action
   if null x
 then ...
 else ...

This obviously fails since x isn't a list, it's a StateT MyState 
(ListT (ErrorT MyError Ideneity)) x. I can't see a nice way to handle 
this. I found a way that works, but it's quite ugly...


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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Andrew Coppin

Jonathan Cast wrote:
I see... I was under the impression that mplus is just any arbitrary 
binary operation over a given monad. How do you know what it does for a 
specific monad?



Process of elimination.  Sometimes, this doesn't narrow things down to a
single operation, but it gives you a good idea of what you're supposed
to expect.

Firstly, mplus and mzero form a (natural) monoid, put together.  That
rules out a number of binary operations right there.

Secondly, mzero has a null law with (=):

  mzero = f = mzero

So, if you have

  a `mplus` b

and a calls mzero at some point (not inside another call to mplus ---
nice and informal, that description :), then you know b will be executed
instead.  (Maybe b will be executed *anyway*.  I didn't say anything
about that).

So mplus and mzero are basically suitable for three kinds of things:

* Exception handling
* Back-tracking
* Parallelism

Usually, when you see a MonadPlus instance, you expect one or more of
these.

That's in the general case.

ListT is a special case; the (somewhat idealized) specification of ListT
(what people want to happen when they use ListT) is that ListT m in some
sense `adds back-tracking' to m.  Where back-tracking choice is
implemented by mplus.
  


Right. OK. So... isn't there a class somewhere called MonadChoice or 
similar, which defines (|)?


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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Jonathan Cast
On Mon, 2008-10-13 at 18:58 +0100, Andrew Coppin wrote:
 Jonathan Cast wrote:
  I see... I was under the impression that mplus is just any arbitrary 
  binary operation over a given monad. How do you know what it does for a 
  specific monad?
  
 
  Process of elimination.  Sometimes, this doesn't narrow things down to a
  single operation, but it gives you a good idea of what you're supposed
  to expect.
 
  Firstly, mplus and mzero form a (natural) monoid, put together.  That
  rules out a number of binary operations right there.
 
  Secondly, mzero has a null law with (=):
 
mzero = f = mzero
 
  So, if you have
 
a `mplus` b
 
  and a calls mzero at some point (not inside another call to mplus ---
  nice and informal, that description :), then you know b will be executed
  instead.  (Maybe b will be executed *anyway*.  I didn't say anything
  about that).
 
  So mplus and mzero are basically suitable for three kinds of things:
 
  * Exception handling
  * Back-tracking
  * Parallelism
 
  Usually, when you see a MonadPlus instance, you expect one or more of
  these.
 
  That's in the general case.
 
  ListT is a special case; the (somewhat idealized) specification of ListT
  (what people want to happen when they use ListT) is that ListT m in some
  sense `adds back-tracking' to m.  Where back-tracking choice is
  implemented by mplus.

 
 Right. OK. So... isn't there a class somewhere called MonadChoice or 
 similar, which defines (|)?

It's called Alternative:

class Applicative f = Alternative f where
  empty :: f a
  (|) :: f a - f a - fa 

It's basically MonadPlus, weakened to just applicative functions.  (I
think that the name (|) was probably found after mplus, which is why
MonadPlus doesn't use it.)  So you can expect, for an arbitrary monad,
that the good defintion(s) for mplus and the good definition(s) for (|
) will coincide.

jcc


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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Dino Morelli

On Mon, 13 Oct 2008, Andrew Coppin wrote:


Reid Barton wrote:

It's not difficult: the operation is called

mplus :: MyMonad a - MyMonad a - MyMonad a

and already exists (assuming the author of ListT has not forgotten to
write a MonadPlus instance).



I see... I was under the impression that mplus is just any arbitrary 
binary operation over a given monad. How do you know what it does for a 
specific monad?




I had imagined the definition of mplus to be similar in spirit to what
bind is for a specific monad.  i.e. it's part of that monad's strategy
for achieving what it does. As for knowing what it does, trial and error,
reading API docs and source. :)

Something similar to this discussion had come up recently for me, list
monad's MonadPlus implementation.

We found ourselves doing something like this to model 'use default value
if empty' for strings:

   let foo = case str of
   [] - default
   s  - s


Right away I was wishing I could do this:

   let foo = str `or-if-empty` default


If it was a Maybe, this works with mplus:

   (Just foo) `mplus` (Just bar) == Just foo
   Nothing  `mplus` (Just bar) == Just bar


But not so much for list, mplus just ain't defined that way, instead
doing concatination:

   foo `mplus` bar == foobar
   `mplus` bar == bar


I ended up writing a special mplus' for this (thanks to #haskell!):

   mplus' :: (MonadPlus m, Eq (m a)) = m a - m a - m a
   mplus' x y
  | x == mzero = y
  | otherwise  = x

   foo `mplus'` bar == foo
   `mplus'` bar == bar


--
Dino Morelli  email: [EMAIL PROTECTED]  web: http://ui3.info/d/  irc: dino-
pubkey: http://ui3.info/d/dino-4AA4F02D-pub.gpg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Arnar Birgisson
Hi Andrew,

On Mon, Oct 13, 2008 at 19:58, Andrew Coppin
[EMAIL PROTECTED] wrote:
 Right. OK. So... isn't there a class somewhere called MonadChoice or
 similar, which defines (|)?

Just to pitch in a helpful tip, Hoogle is excellent for these kind of
questions (which come up very often):

http://www.haskell.org/hoogle/?q=%3C|%3E

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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-13 Thread Tillmann Rendel
Dino Morelli wrote:
 I was wishing I could do this:

let foo = str `or-if-empty` default


 If it was a Maybe, this works with mplus:

(Just foo) `mplus` (Just bar) == Just foo
Nothing  `mplus` (Just bar) == Just bar


 But not so much for list, mplus just ain't defined that way, instead
 doing concatination:

foo `mplus` bar == foobar
`mplus` bar == bar

The difference between Maybe-style MonadPlus and List-style MonadPlus is
discussed on

   http://www.haskell.org/haskellwiki/MonadPlus_reform_proposal.

With that proposal, you could use morelse with both Maybe and lists.
Personally, I would like to call these beasts | (for Maybe-style
mplus) and + (for List-style mplus). One could even have

   a | b = a | pure b
   a + b = a + pure b
   a + b = pure a + b

in the style of * and *. Note that I assume Applicative as a
superclass of Monad, while I'm talking about a better world anyway.

That said, I would consider using something like the + sketched here
for Strings as a hack, because I do not see Strings as Chars under the
List functor, even if they technically may be exactly that. Since abc
does not represent multiple results, I don't think  should represent
failure.

Instead, I would wrap optional strings in Maybe, and then use fromMaybe
to handle the default values:

   fromMaybe bar (Just foo) = foo
   fromMaybe bar Nothing  = bar

Now, with the operators sketched above, fromMaybe = flip (|), so one
could use

   Just foo | bar = foo
   Nothing| bar = bar

which seems to closely correspond to what you want.

   Tillmann


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


[Haskell-cafe] Still stacking monad transformers

2008-10-12 Thread Andrew Coppin
I am becoming extremely frustrated now. The task I want to perform is 
simple, yet I simply cannot make Haskell do what I want.


I've given up hope of ever getting my program to handle infinite result 
sets. That means I can make do with just ListT. So I have the following 
monad:


 type MyMonad x = StateT MyState (ListT Identity) x

Now I'm trying to run two computations, starting from _the same state_, 
and combine the two resulting lists. The trouble is, I am literally 
losing the will to live trying to comprehend the whinings of the type 
checker. The operation I'm trying to perform is perfectly simple; I 
don't understand why this has to be so damned *difficult*! _


Any suggestions?

I found that by using the brief and easily memorable construction 
runIdentity $ runListT $ runStateT foo state I can get at the result 
set for each action, and combine them. But nothing in hell seems to 
transform this from [((), MyState)] back into MyMonad ().


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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-12 Thread Duncan Coutts
On Sun, 2008-10-12 at 18:08 +0100, Andrew Coppin wrote:
 I am becoming extremely frustrated now. The task I want to perform is 
 simple, yet I simply cannot make Haskell do what I want.
 
 I've given up hope of ever getting my program to handle infinite result 
 sets. That means I can make do with just ListT. So I have the following 
 monad:
 
   type MyMonad x = StateT MyState (ListT Identity) x
 
 Now I'm trying to run two computations, starting from _the same state_, 
 and combine the two resulting lists. The trouble is, I am literally 
 losing the will to live trying to comprehend the whinings of the type 
 checker. The operation I'm trying to perform is perfectly simple; I 
 don't understand why this has to be so damned *difficult*! _
 
 Any suggestions?

Have you tried pure lazy functional programming without stacked monads?

I've never been convinced that stacked monads is a good way to write
ordinary code. Monad transformers are great for building your own custom
monads but they should be wrapped in a newtype and made abstract. One
shouldn't have to see the multiple layers. If ordinary code is full of
'lift' then it would seem to me that one is doing something wrong.

Duncan

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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-12 Thread Miguel Mitrofanov


On 12 Oct 2008, at 21:08, Andrew Coppin wrote:

I found that by using the brief and easily memorable construction  
runIdentity $ runListT $ runStateT foo state I can get at the  
result set for each action, and combine them. But nothing in hell  
seems to transform this from [((), MyState)] back into MyMonad ().


Well, State monad (and StateT transformer) doesn't work with STATE,  
they work with STATE CHANGES. So, instead of [((), MyState], you  
should have something like (MyState - [((), MyState)]). And that can  
be transformed to MyMonad () quite easily:


Prelude Control.Monad.State Control.Monad.List  
Control.Monad.Identity :t \f - StateT $ ListT . Identity . f
\f - StateT $ ListT . Identity . f :: (s - [(a, s)]) - StateT s  
(ListT Identity) a


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


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-12 Thread David Menendez
On Sun, Oct 12, 2008 at 1:08 PM, Andrew Coppin
[EMAIL PROTECTED] wrote:
 I am becoming extremely frustrated now. The task I want to perform is
 simple, yet I simply cannot make Haskell do what I want.

 I've given up hope of ever getting my program to handle infinite result sets.

Did you miss this message?

http://article.gmane.org/gmane.comp.lang.haskell.cafe/45952/

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Still stacking monad transformers

2008-10-12 Thread wren ng thornton

David Menendez wrote:

On Sun, Oct 12, 2008 at 1:08 PM, Andrew Coppin
[EMAIL PROTECTED] wrote:

I am becoming extremely frustrated now. The task I want to perform is
simple, yet I simply cannot make Haskell do what I want.

I've given up hope of ever getting my program to handle infinite result sets.


Did you miss this message?

http://article.gmane.org/gmane.comp.lang.haskell.cafe/45952/


And if you don't like that one, there's also LogicT 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logict. The 
function you're looking for is called Control.Monad.Logic.interleave. I 
know LogicT and fair disjunction were brought up earlier, though I seem 
to have mislaid the post.


In case you don't like the efficient Logic or LogicT implementations of 
MonadLogic, defining your own only requires that you can define msplit 
:: m a - m (Maybe (a, m a)) which pulls the first content out of your 
monad without forcing the rest of it.



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