Re: [Haskell-cafe] (state) monad and CPS

2009-11-12 Thread jean-christophe mincke
Hello, Thank everybody for the answers. I must admit that I did not really emphasize the goal behind my initial question. Which is better expressed this way: 'walk' is written is CPS and is tail recursive. Unless I am wrong , if the continuation monad is used, the recursive calls to 'walk' are

Re: [Haskell-cafe] (state) monad and CPS

2009-11-12 Thread Nicolas Pouillard
Excerpts from wren ng thornton's message of Thu Nov 12 08:17:41 +0100 2009: Nicolas Pouillard wrote: Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009: do acc - get put (acc+1) ... Since this pattern occurs often 'modify' is a combination of

Re: [Haskell-cafe] (state) monad and CPS

2009-11-11 Thread Nicolas Pouillard
Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009: Hello, Hello, I would like to get some advice about state monad (or any other monad I guess) and CPS. Here is to remarks somewhat off topic: [...] walk Empty acc k = k acc walk (Leaf _) acc k = k (acc+1)

Re: [Haskell-cafe] (state) monad and CPS

2009-11-11 Thread wren ng thornton
Nicolas Pouillard wrote: Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009: do acc - get put (acc+1) ... Since this pattern occurs often 'modify' is a combination of get and put: do modify (+1) ... Though the caveat about laziness applies here as

[Haskell-cafe] (state) monad and CPS

2009-11-10 Thread jean-christophe mincke
Hello, I would like to get some advice about state monad (or any other monad I guess) and CPS. Let's take a simple exemple (see the code below) 'walk' is a function written in CPS that compute the number of nodes leaves in a tree. It use a counter which is explicitly passed through calls.

Re: [Haskell-cafe] (state) monad and CPS

2009-11-10 Thread Gregory Crosswhite
Yes; check out the module Control.Monad.Cont, which has a monad for continuation passing style. In particular, note that most of the monads in Control.Monad.* are stackable in that there is a version of the monad which you can stack on top of an existing monad. So for example, you could

Re: [Haskell-cafe] (state) monad and CPS

2009-11-10 Thread Ryan Ingram
Something like this should work: newtype ContState r s a = ContState { runCS :: s - (a - s - r) - r } instance Monad (ContState r s) where return a = ContState $ \s k - k a s m = f = ContState $ \s0 k - runCS m s $ \a s1 - runCS (f a) s1 k instance MonadState s (ContState r s) where

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-15 Thread Peter Verswyvelen
ouch, I was confusing the mtl and transformers package... so basically transformers is a better replacement for mtl? or does mtl offer things transformers does not? On Sun, Mar 15, 2009 at 12:04 AM, Henning Thielemann lemm...@henning-thielemann.de wrote: On Sat, 14 Mar 2009, Peter

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-15 Thread Henning Thielemann
Peter Verswyvelen schrieb: ouch, I was confusing the mtl and transformers package... so basically transformers is a better replacement for mtl? or does mtl offer things transformers does not? transformers and monad-fd are cleanly separated, transformers is Haskell 98 and monad-fd uses

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-14 Thread Peter Verswyvelen
I was using the transformers but still had to implement the Applicative instance of State This package contains an applicative instance for StateT but not for State On Sat, Mar 14, 2009 at 3:05 AM, Henning Thielemann lemm...@henning-thielemann.de wrote: On Thu, 12 Mar 2009, Peter Verswyvelen

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-14 Thread Henning Thielemann
On Sat, 14 Mar 2009, Peter Verswyvelen wrote: I was using the transformers but still had to implement the Applicative instance of State This package contains an applicative instance for StateT but not for State In 'transformers' State is a type synonym for StateT Identity and thus does not

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-13 Thread Wolfgang Jeltsch
Am Freitag, 13. März 2009 05:09 schrieb Denis Bueno: This works because every monad induces an Applicative instance in a way I've ingested just enough wine to forget. =] pure = return (*) = ap Best wishes, Wolfgang ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-13 Thread Henning Thielemann
On Thu, 12 Mar 2009, Peter Verswyvelen wrote: I think. Or is it defined in some other package? The 'transformers' package has those instances. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Peter Verswyvelen
I think. Or is it defined in some other package? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Matt Hellige
Looks like it may be defined in the package applicative-extras: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/applicative-extras But I'm not positive about that, and the docs are... sparse. Matt 2009/3/12 Peter Verswyvelen bugf...@gmail.com: I think. Or is it defined in some

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Bas van Dijk
2009/3/12 Peter Verswyvelen bugf...@gmail.com: I think. Or is it defined in some other package? There's an existing ticket about this: http://hackage.haskell.org/trac/ghc/ticket/2316 Note that the ticket links to some old threads on librar...@haskell.org about the issue. regards, Bas

Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Denis Bueno
2009/3/12 Peter Verswyvelen bugf...@gmail.com: I think. Or is it defined in some other package? Note that you can get an Applicative instance for free by using WrapMonad in Control.Applicative. For example, just today I was writing a quickcheck Arbitrary instance, and the Gen monad doesn't have

Re: [Haskell-cafe] State Monad - using the updated state

2009-01-08 Thread Kurt Hutchinson
Ryan gave some great advice about restructuring your program to do what you want, but I wanted to give a small explanation of why that's necessary. 2009/1/7 Phil pbeadl...@mail2web.com: I want to be able to do: Get_a_random_number a whole load of other stuff Get the next number as

Re: [Haskell-cafe] State Monad - using the updated state

2009-01-08 Thread Phil
I think I've got this now - thanks to you all for the superb advice! The reason I cannot increment state inside main is because main is not a State monad (it's an IO monad). Thus in order to use my State Monad, I have execute inside a State monad as that the state is encapsulated in there. I'll

Re: [Haskell-cafe] State Monad - using the updated state

2009-01-08 Thread Luke Palmer
On Thu, Jan 8, 2009 at 12:56 PM, Phil pbeadl...@mail2web.com wrote: One more question on this - the other concern I had with the recursive list approach was that although lazy evaluation prevents me generating numbers before I 'ask' for them, I figured that if I was going to be asking for say

[Haskell-cafe] State Monad - using the updated state

2009-01-07 Thread Phil
Hi, I¹m a newbie looking to get my head around using the State Monad for random number generation. I¹ve written non-monad code that achieves this no problem. When attempting to use the state monad I can get what I know to be the correct initial value and state, but can¹t figure out for the life

[Haskell-cafe] State Monad - using the updated state in an adhoc manner

2009-01-07 Thread Phil
Hi, I¹m a newbie looking to get my head around using the State Monad for random number generation. I¹ve written non-monad code that achieves this no problem. When attempting to use the state monad I can get what I know to be the correct initial value and state, but can¹t figure out for the life

Re: [Haskell-cafe] State Monad - using the updated state

2009-01-07 Thread Ryan Ingram
Hi Phil. First a quick style comment, then I'll get to the meat of your question. getRanq1 is correct; although quite verbose. A simpler definition is this: getRanq1 = State ranq1 This uses the State constructor from Control.Monad.State: State :: (s - (a,s)) - State s a What it sounds like

Re: [Haskell-cafe] State Monad - using the updated state in an adhoc manner

2009-01-07 Thread Brandon S. Allbery KF8NH
On 2009 Jan 7, at 20:58, Phil wrote: -- 124353542542 is just an arbitrary seed main :: IO() main = do let x = evalState getRanq1 (ranq1Init 124353542542) print (x) You're throwing away the state you want to keep by using evalState there. But you're also missing the point of

Re: [Haskell-cafe] state monad and continuation monads ...

2008-09-30 Thread minh thu
2008/9/30 Galchin, Vasili [EMAIL PROTECTED]: Hello, I would like to read 1) pedagogical examples of State monad and the Continuation monad 2) library usage of these monads Regarding 1), there is a lot to find on the web. Maybe start on haskell.org. In term of example, here

Re: [Haskell-cafe] state monad and continuation monads ...

2008-09-30 Thread Henning Thielemann
On Tue, 30 Sep 2008, Galchin, Vasili wrote: Hello, I would like to read 1) pedagogical examples of State monad and the Continuation monad 2) library usage of these monads For continuations I found the withCString example especially convincing:

Re: [Haskell-cafe] state monad and continuation monads ...

2008-09-30 Thread Albert Y. C. Lai
Galchin, Vasili wrote: 1) pedagogical examples of State monad and the Continuation monad Shameless plug: http://www.vex.net/~trebla/haskell/ContMonad.lhs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] state monad and continuation monads ...

2008-09-29 Thread Galchin, Vasili
Hello, I would like to read 1) pedagogical examples of State monad and the Continuation monad 2) library usage of these monads Regards, Vasili ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] State monad in the wikibood article

2007-03-01 Thread TJ
Matthew Brecknell: Note the lambda abstraction (\st - ...) at the beginning of the definition. This means that (container = fn) returns a *function* that maps an input state to the result of (container2 st2). It doesn't return the result of (container st2) directly. Ah. Silly me :D Thanks

[Haskell-cafe] State monad in the wikibood article

2007-02-28 Thread TJ
In the wikibook article here: http://en.wikibooks.org/wiki/Haskell/Understanding_monads, which really does an excellent job explaining things (nuclear waste woohoo!), I am stuck at the following code snippet: container = fn = \st - let (a, st2) = container st container2 = fn a

Re: [Haskell-cafe] State monad in the wikibood article

2007-02-28 Thread Matthew Brecknell
TJ [EMAIL PROTECTED] said: In the wikibook article here: http://en.wikibooks.org/wiki/Haskell/Understanding_monads, which really does an excellent job explaining things (nuclear waste woohoo!), I am stuck at the following code snippet: container = fn = \st - let (a, st2) = container st

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

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

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

2007-01-11 Thread Yitzchak Gale
Josef Svenningsson wrote: Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? ...both strict and lazy variants are useful. I wrote: Are those really needed? ...it wouldn't be very convenient, would it? Sometimes

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.

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

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

2007-01-11 Thread Josef Svenningsson
On 1/11/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Josef Svenningsson wrote: Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? ...both strict and lazy variants are useful. I wrote: Are those really needed?

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

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

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

2007-01-10 Thread Bulat Ziganshin
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

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

2007-01-10 Thread Yitzchak Gale
Hi Bulat, I wrote: [State and StateT] should be consistent. I would much prefer for them both to be lazy. Bulat Ziganshin wrote: 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 -

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

2007-01-10 Thread Josef Svenningsson
Yitzchak, I agree with you that both lazy and strict monads are important and that we should have both options in a monad library. But the fun doesn't end there. There are other strictness properties to consider. Take the state monad for example. Should it be strict or lazy in the state that it

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

2007-01-10 Thread Yitzchak Gale
Hi Josef, Josef Svenningsson wrote: ...the fun doesn't end there. There are other strictness properties to consider. Could be. But after using mtl heavily for a few years now, I find that in practice the only one where have felt the need for control over strictness is =, like Dean's example.

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

2007-01-10 Thread Josef Svenningsson
On 1/10/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Hi Josef, Josef Svenningsson wrote: ...the fun doesn't end there. There are other strictness properties to consider. Could be. But after using mtl heavily for a few years now, I find that in practice the only one where have felt the need for

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,

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

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,

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

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,

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:

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

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.

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

[Haskell-cafe] State monad strictness - how?

2007-01-09 Thread Dean Herington
I can't seem to figure out how to achieve strictness in the context of the State monad. Consider: import Control.Monad.State try count = print final where (_,final) = runState prog 0 prog = sequence_ (replicate count tick) tick :: State Int Int tick = do n - get

Re: [Haskell-cafe] State Monad

2005-03-04 Thread Mark Carroll
On Fri, 4 Mar 2005, Mark Carroll wrote: (snip) Enclosed is a programme that asks for two ints from standard input, adds (snip) Let me try again. (-: -- Markmodule StackMTest where import StackM import Control.Monad import Control.Monad.Trans import System.IO import System.Random add :: Num a =

[Haskell-cafe] State Monad

2005-03-04 Thread Derek Elkins
Thinking of stacks, I've often wondered if Haskell would be a good language for implementing a PostScript interpreter. I actually have the beginning of a PostScript interpreter somwhere... And the core of a Joy interpreter is extremely small. It's pretty much 'foldl compose . map

Re: [Haskell-cafe] State Monad

2005-03-03 Thread Sam G.
Thaks a lot for your contribution, this helps me a lot, I see what I've got to do. However, I understand the first version (Stack.hs), but I can't get what StateM.hs is. Is it the same version but using state transformers, so as to be able to do IO (which I would need)? In fact, could you give

[Haskell-cafe] State Monad

2005-03-02 Thread Sam G.
I need a Monad to represent an internal stack. I mean I've got a lot of functions which operates on lists and I would not like to pass the list as an argument everytime. Could you help me writing this monad? To start, I just need a + function which will return the sum of the 2 toppest elements

Re: [Haskell-cafe] State Monad

2005-03-02 Thread Sam
Hello again, in fact I wrote the following state monad: -- newtype State state value = State (state - (state, value)) instance Monad (State state) where return v = State $ \s - (s, v) State f = k = State $ \s - let (s0, v0) = f s State g = k v0

Re: [Haskell-cafe] State Monad

2005-03-02 Thread Bernard Pope
On Thu, 2005-03-03 at 02:03 +0100, Sam G. wrote: I need a Monad to represent an internal stack. I mean I've got a lot of functions which operates on lists and I would not like to pass the list as an argument everytime. Could you help me writing this monad? To start, I just need a +

Re: [Haskell-cafe] State Monad

2005-03-02 Thread Mark Carroll
On Thu, 3 Mar 2005, Sam G. wrote: I need a Monad to represent an internal stack. I mean I've got a lot of functions which operates on lists and I would not like to pass the list as an argument everytime. Could you help me writing this monad? To start, I just need a + function which will

[Haskell-cafe] State monad strictness (was: ... abysmal Language Shootout results)

2004-09-30 Thread Peter Simons
How can anyone stay away from such a deliciously pointless waste of time as implementing a wc(1) derivate? :-) Here is my attempt: import IO type Count = Int data CountingState = ST !Bool !Count !Count !Count deriving (Show) initCST = ST True 0 0 0

Re: [Haskell-cafe] State Monad

2004-03-04 Thread Georg Martius
Hi, thanks for your suggestion. The thing is, that I don't want to change the type of my transformation functions. To answer Iavor's question: I have basically two types of transformation functions. One StringTransformation (String - String) and one transformation with a string and something

[Haskell-cafe] State Monad

2004-03-03 Thread Georg Martius
Hi folks, I have a question to the State Monad or Monads in general - I'am not sure. Lets assume I have functions to transform strings. I can use the State Monad as follows: strTrans :: String - String strTrans s = s ++ s f :: State String () f = do put hallo modify strTrans

Re: [Haskell-cafe] State Monad

2004-03-03 Thread Wolfgang Jeltsch
Am Mittwoch, 3. Mrz 2004 14:44 schrieb Georg Martius: [...] Now I have also functions to map from (a, String) - (a,String). I could write: modifyT :: ((a, String) - (a, String)) - a - State String a modifyT trans a = do str - get let (a', str') = trans (a, str)

Re: [Haskell-cafe] State Monad

2004-03-03 Thread Iavor S. Diatchki
hi, Georg Martius wrote: Now I have also functions to map from (a, String) - (a,String). I could write: modifyT :: ((a, String) - (a, String)) - a - State String a modifyT trans a = do str - get let (a', str') = trans (a, str) put str' return a' f ::

Re: [Haskell-cafe] State Monad

2004-03-03 Thread Wolfgang Jeltsch
Am Mittwoch, 3. Mrz 2004 18:15 schrieb Georg Martius: Thanks for your answer. I got it now. It works with lift instead of liftM. Yes, of course. Georg Wolfgang ___ Haskell-Cafe mailing list [EMAIL PROTECTED]

Re: [Haskell-cafe] State Monad

2004-03-03 Thread Tom Pledger
Georg Martius wrote: [...] I could write: modifyT :: ((a, String) - (a, String)) - a - State String a modifyT trans a = do str - get let (a', str') = trans (a, str) put str' return a' f :: State String () f = do put hallo modify strTrans i -