Re: [Haskell-cafe] State monad strictness - how?

2007-01-12 Thread Chris Kuklewicz
John Meacham wrote:
 incidentally, I made a very strict and unboxed version of the RWS monad,
 since it is a darn useful one in jhc. right now, it only implements the
 things I needed, but it might be useful to include somewhere common and
 expanded on
 
 http://repetae.net/dw/darcsweb.cgi?r=jhc;a=headblob;f=/Util/RWS.hs
 
 John


I have copied your email and the code to the wiki at

http://haskell.org/haskellwiki/New_monads/UnboxedRWS

and linked to it from the page that collects such items:

http://haskell.org/haskellwiki/New_monads

Everyone who is discussing variants of State might consider posting useful
implementations on the wiki under New_monads.

For example, some time ago I posted a LazyWriterT that added the '~' to the
tuple matching in (=) and mfix.

-- 
Chris

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Yitzchak Gale

Iavor Diatchki wrote:

The state transformer inherits its behavior from
the underlying monad.


Ross Paterson wrote:

This (like StateT) gives you strictness in the pair, but doesn't give
the strictness in the state that the original poster wanted.


I think it does - if you run his program with State Int
replaced by StateT Int Identity, it now runs in constant memory.


Once we have this kind of strictness, then the programmer
has control over the state.


That is true for MTL as well.

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Yitzchak Gale wrote:
 You're right, it is not in the docs. I don't think anyone would
 have planned it that way. StateT is strict only because there
 happens to be a line in a do-expression that looks like:
   (a, s') - runStateT m s
 The tuple pattern-match causes the strictness.
 That appears accidental, so it seems to be just an honest bug.

I agree that this is an accident, but the bug is in lazy State, for
three reasons:

- Being strict in the (result,state) pair does not for the evaluation of
  either result or state.  Not being strict could only ever be useful
  for a following action that made no use of either state or result, and
  I have a hard time imagining why you'd ever want to write such a
  beast, let alone in monadic style.  In fact, an unboxed tuple would be
  even better.

- Assuming that the State monad is lazy in the tuple, and you need to be
  strict in the state component, you are hosed.  No amount of 'seq' will
  help you.  On the other hand, were it strict and you needed it to be
  lazy, you could achieve that by manually boxing the data involved.

- (=) should also be head strict in the state component.  Again, if
  this is wrong, you can repair it.  If laziness turns out wrong, you
  can't.  Moreover, for most data types that you want to build lazily,
  especially lists, head strictness doesn't make a difference, as long
  as the tail is lazily evaluated.  For data where you need strictness,
  such as integers or tuples of them, having strictness available make
  all the difference.

I'd be fine with laziness being configurable, of course, but if it
isn't, I want strict state.  Come to think of it, it's probably just a
bad idea that _|_ and (_|_,_|_) are different things.


-Udo
-- 
The Seventh Commandments for Technicians:
Work thou not on energized equipment, for if thou dost, thy
fellow workers will surely buy beers for thy widow and console
her in other ways.


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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Ross Paterson wrote:
 This (like StateT) gives you strictness in the pair, but doesn't give
 the strictness in the state that the original poster wanted.

I think the OP wanted both.  If State is lazy in the pair, a long chain
of the form (a = (b = (c = ... = z))) gets build up and blows
the stack if it finally turns out that yes, all these steps are needed.
Worse than that, there's no way to correct this without changing the
definition of (=).

Laziness in the state component is annoying at times, but not as bad.
You can recover strictness by writing

put $! x
get = (put $!) . f

instead of

put x
modify f

provided that (=) is already strict in the pair.  (It gets even more
ugly if the state is a Data.Map that needs to be updated strictly, in
which Data.Map.update also doesn't work, even combined with the above
modifications.)


-Udo
-- 
The only problem with seeing too much is that it makes you insane.
-- Phaedrus


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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread John Meacham
incidentally, I made a very strict and unboxed version of the RWS monad,
since it is a darn useful one in jhc. right now, it only implements the
things I needed, but it might be useful to include somewhere common and
expanded on

http://repetae.net/dw/darcsweb.cgi?r=jhc;a=headblob;f=/Util/RWS.hs

John
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale

Dean Herington wrote:

I can't seem to figure out how to achieve strictness
in the context of the State monad.


Unfortunately, the current situation is that State is only
available as a lazy monad, and StateT is only available
as a strict monad.

It seems to me that this should clearly be considered
a serious bug in the library. It has been reported on
numerous occasions over the years, but it has still
not been fixed.

At the very least, the two should be consistent. I
would much prefer for them both to be lazy.
I have written a lot of code that depends on that;
it is the natural assumption in Haskell that everything
is lazy by default, except seq, IO, and their friends.

The obvious solution would be to have available
both a lazy and a strict version of each monad: State,
State', StateT, and State'T (or some such), with functions to
convert between them. It is trivial to implement that in
the current library.

If someone can come up with a more elegant solution
right away, that would be great. (Iavor - do you have
a solution?)

Otherwise, I think we have waited long enough. Let's
implement the simple fix. This bug is a major
inconvenience to users of this library.


(try 100) overflows the stack.


In the current situation, you can use


  where final = runIdentity $ execStateT prog (0::Int)

...

tick :: (Num a, MonadState a m) = m a

...

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Iavor Diatchki

Hello,


Unfortunately, the current situation is that State is only
available as a lazy monad, and StateT is only available
as a strict monad.


There is no such distinction in monadLib.  The state transformer
inherits its behavior from the underlying monad. For example: StateT
Int IO is strict, but StatT Int Id is lazy.   One way to get a strict
state monad with monadLib is like this:

import MonadLib

data Lift a = Lift { runLift :: a }

instance Monad Lift where
 return x  = Lift x
 Lift x = f  = f x


strict = runLift $ runStateT 2 $
do undefined
   return 5

lazy   = runId $ runStateT 2 $
do undefined
   return 5

The difference between those two is that strict == undefined, while
lazy = (5,undefined).
Unfortunately the monad Lift is not part of monadLib at the moment
so you have to define it on your own, like I did above, but I think
that this is a good example of when it is useful, so I will probably
add it to the next release.

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale

Wow! Now we are talking!

Josef Svenningsson wrote:

So instead of:
newtype State s a = State { runState :: (s - (a, s)) }
we have:
newtype StateP p s a = StateP { runStateP :: (s - p a s) }
Now, instantiating this with different pair types with different
strictness properties will give us total control over strictness for
state and value.


Beautiful!

Iavor Diatchki wrote:

The state transformer inherits its behavior from the underlying
monad. For example: StateT Int IO is strict, but StateT Int Id
is lazy.


Fantastic!

I'm drooling. When can we get stuff like this into MTL?
And maybe it is finally time for me to bite the bullet and
try out monadLib again (is it still CPS? gulp).

Now let's attack Data.* libraries...

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Dean Herington

At 11:02 AM +0200 1/10/07, Yitzchak Gale wrote:


Unfortunately, the current situation is that State is only
available as a lazy monad, and StateT is only available
as a strict monad.


[...]


The obvious solution would be to have available
both a lazy and a strict version of each monad: State,
State', StateT, and State'T (or some such), with functions to
convert between them. It is trivial to implement that in
the current library.


First, thanks for the very helpful reply explaining the situation.

Second, how would one know that State is lazy and StateT is strict? 
I don't see that in the Haddock documentation.


Third, isn't it a continuum rather than a binary choice between lazy 
and strict?  In my example, I used ($!) in the definition of (=), 
but that's just one flavor of strictness that was appropriate to my 
example.  Is there some way to parameterize this degree of strictness?


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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Chris Kuklewicz
Dean Herington wrote:

 Third, isn't it a continuum rather than a binary choice between lazy and
 strict?  In my example, I used ($!) in the definition of (=), but
 that's just one flavor of strictness that was appropriate to my
 example.  Is there some way to parameterize this degree of strictness?
 
 Dean

The r0 and rwhnf and rnf from
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Parallel-Strategies.html
parameterize strictness.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Iavor Diatchki

hi,


I'm drooling. When can we get stuff like this into MTL?
And maybe it is finally time for me to bite the bullet and
try out monadLib again (is it still CPS? gulp).


version 3 (the current version) implements the transformers in the
usual way (e.g., as in mtl) so no cps (except, of course, for the
continuation transformer).  as usual, feedback is welcome.

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale

...how would one know that State is lazy and StateT is strict?
I don't see that in the Haddock documentation.


You're right, it is not in the docs. I don't think anyone would
have planned it that way. StateT is strict only because there
happens to be a line in a do-expression that looks like:
(a, s') - runStateT m s
The tuple pattern-match causes the strictness.
That appears accidental, so it seems to be just an honest bug.

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Ross Paterson
On Wed, Jan 10, 2007 at 10:02:36AM -0800, Iavor Diatchki wrote:
 [Yitzchak Gale:]
 Unfortunately, the current situation is that State is only
 available as a lazy monad, and StateT is only available
 as a strict monad.
 
 There is no such distinction in monadLib.  The state transformer
 inherits its behavior from the underlying monad. For example: StateT
 Int IO is strict, but StatT Int Id is lazy.   One way to get a strict
 state monad with monadLib is like this:
 [strict pseudo-monad]

This (like StateT) gives you strictness in the pair, but doesn't give
the strictness in the state that the original poster wanted.

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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Steve Downey

haskell is the standard lazy functional language, so strictness ought
to be called out. e.g. StateStrict rather than StateLazy.
The traction that haskell is starting to get (and why I'm spending
time learning it and following haskell-cafe) is not because its
semantics are unsurprising to newbies. They are surprising and
surprisingly powerful. A haskell that did no more than scheme would
not be as interesting.
I may be subject to selection bias, but I haven't seen so many
references to a language in unexpected contexts since smalltalk in the
mid 80's.  I don't think that's because it's a language that behaves
the way someone coming from another language expects.

On 1/10/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Hello Yitzchak,

Wednesday, January 10, 2007, 12:02:25 PM, you wrote:

 Unfortunately, the current situation is that State is only
 available as a lazy monad, and StateT is only available
 as a strict monad.

 At the very least, the two should be consistent. I
 would much prefer for them both to be lazy.

imho, lazy monads (as any other lazy things) is a source of beginner's
confusion. therefore it may be better to provide default monads as strict
and lazy ones - for one who knows what he wants - with a Lazy prefix, e.g.
LazyST, LazyState...

--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Iavor Diatchki

Hello,

On 1/10/07, Ross Paterson [EMAIL PROTECTED] wrote:

 There is no such distinction in monadLib.  The state transformer
 inherits its behavior from the underlying monad. For example: StateT
 Int IO is strict, but StatT Int Id is lazy.   One way to get a strict
 state monad with monadLib is like this:
 [strict pseudo-monad]

This (like StateT) gives you strictness in the pair, but doesn't give
the strictness in the state that the original poster wanted.


Once we have this kind of strictness, then the programmer has control
over the state.
For example, they can define:

setStrict x = seq x (set x)
ex3 = runLift $ runState 2 $ setStrict undefined  return 5
ex4 = runId $ runState 2 $ setStrict undefined  return 5

In these examples ex3 == undefined but ex4 = (5,undefined).

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