Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Peter Verswyvelen
On Fri, Aug 21, 2009 at 5:03 AM, David Menendez d...@zednenem.com wrote:

 On Thu, Aug 20, 2009 at 6:57 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
 
  On Thu, Aug 20, 2009 at 11:23 PM, David Menendez d...@zednenem.com
 wrote:
 
  The important things to note are (1) getChar# depends on the token
  returned by putChar#, thus guaranteeing that putChar# gets executed
  first, and (2) putChar# and getChar# are impure and cannot normally be
  defined in Haskell.
 
  Ok, that I understand. But if getChar# and putChar# would be pure
 functions
  that just generate some output string / consume some input string, then
 this
  realworld token passing would not work when used with interact, since
  neither the output or input string really depends on the dummy token,
 unless
  using a seq again (or strictness annotation, which was explained to be
 just
  syntactic sugar for seq)?

 I'm not sure I understand your question, but I think it's possible to
 use interact in the way you want. For example, this code behaves
 correctly for me:

foo i =
let i1 = lines i
in Enter your name:  ++
(case i1 of
[] - error EOF
name:i2 - Welcome  ++ name ++ \n)

 Prelude interact foo
 Enter your name: Bob
 Welcome Bob


Yes but this also enforce strictness, since you're pattern matching against
the input, forcing it to be evaluated. If for example the empty string would
be valid input, this wouldn't work, and seq would be needed again no?


 Note the dependencies here. When you call interact foo, the prompt can
 be immediately output without reading any of the input. However,
 Welcome cannot be printed until one line of the input has been read
 (or EOF reached) because it's inside the pattern match on i1.


  But how would we then make a pure monad that can
  be used as in my example together with interact? I see no reason why to
 put
  everything in IO when it just comes to converting a stream of inputs to a
  stream of outputs? So interact really is useless, unless you just fmap
  something over the input or when the output is independent from the
 input?

 Not necessarily. Your situation reminds me of Haskell's I/O system
 before the IO monad was introduced. (See section 7 of A History of
 Haskell: Being Lazy With Class for details.
 
 http://research.microsoft.com/en-us/um/people/simonpj/papers/history-of-haskell/history.pdf
 )

 In it, they describe how older versions of Haskell could be defined in
 terms of lazy request and response streams, how you can use
 continuation-passing to build the streams in a more localized way, and
 then how you could define the IO monad in terms of that.

 This works for me:

 import Control.Monad.Cont

 type Behavior = [String] - String
 type MyIO = Cont Behavior

 putLine :: String - MyIO ()
 putLine s = Cont $ \k ss - s ++ k () ss

 getLine :: MyIO String
 getLine = Cont $ \k (s:ss) - k s ss

 run :: MyIO () - Behavior
 run m = runCont m (\_ _ - [])

 foo = do
putLine Enter name: 
name - getLine
putLine (Welcome  ++ name ++ \n)

 Prelude Control.Monad.Cont interact (run foo . lines)
 Enter name: Dave
 Welcome Dave

 It may be instructive to manually expand run foo.


This suffers from the same strictness problem on the input, e.g. when making
getLine less strict, as in:

import Prelude hiding (getLine)
import Control.Monad.Cont

type Behavior = [String] - String
type MyIO = Cont Behavior

putLine :: String - MyIO ()
putLine s = Cont $ \k ss - s ++ k () ss

getLine :: MyIO String
-- Was: getLine = Cont $ \k *(s:ss) - k s ss*
*getLine = Cont $ \k ss - k (head ss) (tail ss)*

run :: MyIO () - Behavior
run m = runCont m (\_ _ - [])

foo = do
   putLine Enter name: 
   name - getLine
   putLine (Welcome  ++ name ++ \n)

main = interact (run foo . lines)

You get the Welcome before the name again.

To be honest I don't fully understand why this is a horrible hack. From a
pure point of view, the behavior is the same, weither or not the input is
made strict. When side effects are present (interactive input/output from
the user), it does matter, but aren't all space/time leaks to be considered
as some sort of operational effects? In a pure mathematical world, space
and time leaks would not really matter?

I do understand much more now, thanks. The best solution for making this IO
pure remains MonadPrompt I guess.

Too bad that something extremely simple like console text IO doesn't seem to
be a good start for introducing FRP, or maybe seen from another angle (using
Reactive) it might still be, dono



 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Lennart Augustsson
Internally GHC does have to enforce the ordering on IO operations somehow.
If there actually was a RealWorld value being passed around you could
use some version of seq the guarantees sequential evaluation.
But GHC doesn't even pass a RealWorld around, the sequencing is
enforced by different means.

It's uninteresting for this discussion how GHC enforces the sequencing
internally, the important part is that it is part the sequencing is
part of the IO monad semantics and this is what should be used to
guarantee the sequencing of IO operations in a program.

  -- Lennart

On Thu, Aug 20, 2009 at 10:41 PM, Peter Verswyvelenbugf...@gmail.com wrote:
 But how does GHC implement the RealWorld internally? I guess this can't be
 done using standard Haskell stuff? It feels to me that if I would implement
 it, I would need seq again, or a strict field, or some incrementing time
 value that is a strict argument of each of the IO primitives. In any case, I
 would need strictness to control the dependencies no? I might be wrong
 (again) but this is all very interesting ;-)

 On Thu, Aug 20, 2009 at 10:25 PM, David Menendez d...@zednenem.com wrote:

 On Thu, Aug 20, 2009 at 3:43 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
 
  Also doesn't Haskell's IO system uses a hidden RealWorld type that has
  no
  value but which is passed from between monadics binds in a strict way to
  make the ordering work?

 Haskell only describes how the IO monad behaves. GHC's implementation
 uses a RealWorld type, but other implementations are possible.

 A quick sketch of an alternative implementation,

 data Trace = Done | Get (Char - Trace) | Put Char Trace

 newtype IO a = IO { unIO :: (a - Trace) - Trace }

 instance Monad IO where
    return a = IO (\k - k a)
    m = f = IO (\k - unIO m (\a - unIO (f a) k))

 getChar :: IO Char
 getChar = IO Get

 putChar :: Char - IO ()
 putChar c = IO (\k - Put c (k ()))

 The run-time system is responsible for interpreting the Trace and
 inputting/outputting characters as needed. All of IO can be
 implemented in this manner.

  So IO in Haskell is a horrible hack then? :-) If it
  would be done nicely, in the FRP way, then RealWorld IO would need time
  stamps to get rid of the hack?

 Again, no. GHC's IO type uses the RealWorld value to create data
 dependencies. For example, putChar 'x'  getChar, the getChar depends
 on the RealWorld returned by putChar 'x'.

 This is why it's dangerous to open up GHC's IO type unless you know
 what you're doing. If you aren't careful, you may accidentally
 duplicate or destroy the RealWorld, at which point you risk losing
 purity and referential transparency.

 I suppose you could consider the fact that GHC's IO is implemented
 using impure primitive operations a hack, but the whole point of the
 IO monad is to hide that impurity from the rest of the program.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/


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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread David Menendez
On Fri, Aug 21, 2009 at 4:37 AM, Peter Verswyvelenbugf...@gmail.com wrote:
 On Fri, Aug 21, 2009 at 5:03 AM, David Menendez d...@zednenem.com wrote:

 I'm not sure I understand your question, but I think it's possible to
 use interact in the way you want. For example, this code behaves
 correctly for me:

    foo i =
        let i1 = lines i
        in Enter your name:  ++
            (case i1 of
                [] - error EOF
                name:i2 - Welcome  ++ name ++ \n)

 Prelude interact foo
 Enter your name: Bob
 Welcome Bob

 Yes but this also enforce strictness, since you're pattern matching against
 the input, forcing it to be evaluated. If for example the empty string would
 be valid input, this wouldn't work, and seq would be needed again no?

You would still need to determine whether you've reached EOF or not,
which forces the input to be determined up to the first line-break or
EOF.

 This suffers from the same strictness problem on the input, e.g. when making
 getLine less strict, as in:
 import Prelude hiding (getLine)
 import Control.Monad.Cont
 type Behavior = [String] - String
 type MyIO = Cont Behavior
 putLine :: String - MyIO ()
 putLine s = Cont $ \k ss - s ++ k () ss
 getLine :: MyIO String
 -- Was: getLine = Cont $ \k (s:ss) - k s ss
 getLine = Cont $ \k ss - k (head ss) (tail ss)

Technically, these are both wrong, because they don't allow for EOF.
getLine should be more like this:

getLine = Cont $ \k ss - if null ss then error EOF else k (head ss) (tail ss)

 run :: MyIO () - Behavior
 run m = runCont m (\_ _ - [])
 foo = do
    putLine Enter name: 
    name - getLine
    putLine (Welcome  ++ name ++ \n)
 main = interact (run foo . lines)
 You get the Welcome before the name again.
 To be honest I don't fully understand why this is a horrible hack.

It isn't. Some people dislike seq because it lets you force strictness
in cases where pattern matching cannot (like function arguments), but
hardly anyone objects to pattern matching.

(I just read a paper arguing that pattern matching is bad because it
introduces interpretation. The proposed solution, Church encoding
everything, seemed impractical.)

 I do understand much more now, thanks. The best solution for making this IO
 pure remains MonadPrompt I guess.

Or the trace technique I mentioned earlier. I believe they're
equivalent in expressive power.

 Too bad that something extremely simple like console text IO doesn't seem to
 be a good start for introducing FRP, or maybe seen from another angle (using
 Reactive) it might still be, dono

Are you writing an introduction to using FRP, or an introduction to
implementing FRP? Every Haskell FRP implementation I'm aware of uses
the IO monad internally.

If you want to be able to run in an entirely pure manner, you might
investigate IOSpec.

http://hackage.haskell.org/package/IOSpec

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Peter Verswyvelen
On Fri, Aug 21, 2009 at 6:53 PM, David Menendez d...@zednenem.com wrote:

 You would still need to determine whether you've reached EOF or not,
 which forces the input to be determined up to the first line-break or
 EOF.


Good point!  I actually had it on my TODO list, but that settles it then :)

 run :: MyIO () - Behavior

 run m = runCont m (\_ _ - [])
  foo = do
 putLine Enter name: 
 name - getLine
 putLine (Welcome  ++ name ++ \n)
  main = interact (run foo . lines)
  You get the Welcome before the name again.
  To be honest I don't fully understand why this is a horrible hack.

 It isn't. Some people dislike seq because it lets you force strictness
 in cases where pattern matching cannot (like function arguments), but
 hardly anyone objects to pattern matching.


Ah so it's subjective. Okay, it's sometimes hard for a newbie to find the
truth when several experts contradict eachother. Because often when people
claim something here, they have very good reasons for it, reasons that are
not obvious at all to your average newbie!


  Too bad that something extremely simple like console text IO doesn't seem
 to
  be a good start for introducing FRP, or maybe seen from another angle
 (using
  Reactive) it might still be, dono

 Are you writing an introduction to using FRP, or an introduction to
 implementing FRP? Every Haskell FRP implementation I'm aware of uses
 the IO monad internally.


Both really. I think to start with I just want to start a blog to write down
random pieces (like this interesting conversation), and then see where this
will lead me. I'm mainly interested in doing a survey of existing systems,
comparing pros/cons with clear examples (at least for myself ;), and also
making minimal implementations so I understand the essence of the various
techniques.

If you want to be able to run in an entirely pure manner, you might
 investigate IOSpec.

 http://hackage.haskell.org/package/IOSpec


Ah I didn't know that one yet, thanks




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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread David Menendez
On Fri, Aug 21, 2009 at 3:29 PM, Peter Verswyvelenbugf...@gmail.com wrote:
 On Fri, Aug 21, 2009 at 6:53 PM, David Menendez d...@zednenem.com wrote:

 Some people dislike seq because it lets you force strictness
 in cases where pattern matching cannot (like function arguments), but
 hardly anyone objects to pattern matching.

 Ah so it's subjective. Okay, it's sometimes hard for a newbie to find the
 truth when several experts contradict eachother. Because often when people
 claim something here, they have very good reasons for it, reasons that are
 not obvious at all to your average newbie!

You can make a pretty good argument that programs which rely on
strictness for correctness (as opposed to space/time issues) are
risky, because it's easy to get things wrong by accident. Internally,
the IO monad may rely on strictness to make sure things happen in the
proper sequence, but all of that is hidden so we don't have to worry
about things like output happening too early because we haven't
examined some input yet.

This is also why some people object to getContents.


For laughs, here's an example of IO code written using Haskell's old
stream-based IO system, taken from A History of Haskell:

main :: Behaviour
main ~(Success : ~((Str userInput) : ~(Success : ~(r4 : _
  = [ AppendChan stdout enter filename\n,
ReadChan stdin,
AppendChan stdout name,
ReadFile name,
AppendChan stdout
(case r4 of
  Str contents - contents
  Failure ioerr - can’t open file)
] where (name : _) = lines userInput


It has a certain elegant purity, but I'm glad I don't have to use it.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Peter Verswyvelen
The question is, in this case when the user gets to see a bit too much of
the output before he sees the input, if that really qualifies as an
incorrect program. It's a bit in the gray zone I guess. You could even
argue that it's a feature that input and output are not really synched, they
are lazy, input is only read when evaluated; if you want to sync them, use a
syncIO action ;-) no that's silly of course.
Oh well, thanks for all the input, this was very informative for me hacker.

On Fri, Aug 21, 2009 at 10:20 PM, David Menendez d...@zednenem.com wrote:

 On Fri, Aug 21, 2009 at 3:29 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  On Fri, Aug 21, 2009 at 6:53 PM, David Menendez d...@zednenem.com
 wrote:
 
  Some people dislike seq because it lets you force strictness
  in cases where pattern matching cannot (like function arguments), but
  hardly anyone objects to pattern matching.
 
  Ah so it's subjective. Okay, it's sometimes hard for a newbie to find the
  truth when several experts contradict eachother. Because often when
 people
  claim something here, they have very good reasons for it, reasons that
 are
  not obvious at all to your average newbie!

 You can make a pretty good argument that programs which rely on
 strictness for correctness (as opposed to space/time issues) are
 risky, because it's easy to get things wrong by accident. Internally,
 the IO monad may rely on strictness to make sure things happen in the
 proper sequence, but all of that is hidden so we don't have to worry
 about things like output happening too early because we haven't
 examined some input yet.

 This is also why some people object to getContents.


 For laughs, here's an example of IO code written using Haskell's old
 stream-based IO system, taken from A History of Haskell:

 main :: Behaviour
 main ~(Success : ~((Str userInput) : ~(Success : ~(r4 : _
  = [ AppendChan stdout enter filename\n,
ReadChan stdin,
AppendChan stdout name,
ReadFile name,
AppendChan stdout
(case r4 of
  Str contents - contents
  Failure ioerr - can’t open file)
] where (name : _) = lines userInput


 It has a certain elegant purity, but I'm glad I don't have to use it.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Peter Verswyvelen
typo, sees the input = must enter the input
On Fri, Aug 21, 2009 at 10:28 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 The question is, in this case when the user gets to see a bit too much of
 the output before he sees the input, if that really qualifies as an
 incorrect program. It's a bit in the gray zone I guess. You could even
 argue that it's a feature that input and output are not really synched, they
 are lazy, input is only read when evaluated; if you want to sync them, use a
 syncIO action ;-) no that's silly of course.
 Oh well, thanks for all the input, this was very informative for me hacker.

 On Fri, Aug 21, 2009 at 10:20 PM, David Menendez d...@zednenem.comwrote:

 On Fri, Aug 21, 2009 at 3:29 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  On Fri, Aug 21, 2009 at 6:53 PM, David Menendez d...@zednenem.com
 wrote:
 
  Some people dislike seq because it lets you force strictness
  in cases where pattern matching cannot (like function arguments), but
  hardly anyone objects to pattern matching.
 
  Ah so it's subjective. Okay, it's sometimes hard for a newbie to find
 the
  truth when several experts contradict eachother. Because often when
 people
  claim something here, they have very good reasons for it, reasons that
 are
  not obvious at all to your average newbie!

 You can make a pretty good argument that programs which rely on
 strictness for correctness (as opposed to space/time issues) are
 risky, because it's easy to get things wrong by accident. Internally,
 the IO monad may rely on strictness to make sure things happen in the
 proper sequence, but all of that is hidden so we don't have to worry
 about things like output happening too early because we haven't
 examined some input yet.

 This is also why some people object to getContents.


 For laughs, here's an example of IO code written using Haskell's old
 stream-based IO system, taken from A History of Haskell:

 main :: Behaviour
 main ~(Success : ~((Str userInput) : ~(Success : ~(r4 : _
  = [ AppendChan stdout enter filename\n,
ReadChan stdin,
AppendChan stdout name,
ReadFile name,
AppendChan stdout
(case r4 of
  Str contents - contents
  Failure ioerr - can’t open file)
] where (name : _) = lines userInput


 It has a certain elegant purity, but I'm glad I don't have to use it.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/



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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ryan Ingram
On Wed, Aug 19, 2009 at 1:20 PM, Peter Verswyvelenbugf...@gmail.com wrote:
 Well I really wrote this code as an exercise, and it was a good one. Now I
 (or someone) needs to explain why it works.

There's a bit of trickiness, but it's not that hard when you break it down.

Lets look at a simplified version of test:

test = do
x - inp
out hello
out x
test

Desugaring a bit:

test
= inp = \x - out hello  out x  test
= S (\(i:is) - (is, empty, i))
   = \x - S (\is - (is, singleton hello, ()))
   = \_ - S (\is - (is, singleton x, ()))
   = \_ - test

Now, inlining = and simplifying, we get:

test = S (\i0 - let
   (i1, o1, x) = (\(i:is) - (is, empty, i)) i0
   (i2, o2, _) = (i1, singleton hello, ())
   (i3, o3, _) = (i2, singleton x, ())
   (i4, o4, res) = step test i3
   outputs = o1 `mappend` o2 `mappend` o3 `mappend` o4
  in (i4, outputs, res))

The first thing to notice is that when we run test by giving it some
input, we *immediately* get a triple back:
(i4, outputs, res)
with the values in the triple being unevaluated thunks.

res is _|_; trying to evaluate it will infinite loop.  Similarily
for i4.  But fortunately we never do; getOutput throws them both away.
So the only thing we care about is outputs.

outputs is infinite as well, but we have hope!  As long as `mappend`
is lazy in its second argument, we might be able to get some data out!

Lets simplify Data.DList a bit:

mappend = (.)
singleton = (:)
empty = id
fromList = (++)
toList = ($ [])

Now lets try to evaluate (toList outputs):

toList outputs
= ($ []) (o1 . o2 . o3 . o4)
= o1 . o2 . o3 . o4 $ []
= o1 (o2 (o3 (o4 [])))

We need to evaluate o1 in order to call it.  There is a possibility
that it is _|_ :
(i1, o1, x) = (\(i:is) - (is, empty, i)) i0

Therefore
   o1 = case i0 of
   (i:is) - empty
   [] - error pattern match failure
i1 = case i0 of
   (i:is) - is
   [] - error pattern match failure
x = case i0 of
(i:is) - i
[] - error pattern match failure

So as long as you type a line, o1 will be empty (= id).  But we
don't know that you necessarily will type an input line, so the code
*has* to wait for the line of input from the user, and can't print any
later values.  (This is where you get into some of the craziness of
lazy I/O)

Once you type a line, i0 gets bound to (whatever you type : some lazy
thunk representing the rest of the input) and o1 gets evaluated to id.

toList outputs
= o1 (o2 (o3 (o4 [])))
= id (o2 (o3 (o4 [])))
= o2 (o3 (o4 []))

o2 and o3 are easy:
   (i2, o2, _) = (i1, singleton hello, ())
   (i3, o3, _) = (i2, singleton x, ())
therefore
o2 = (hello :)
o3 = (x :)

toList outputs
= o2 (o3 (o4 []))
= (hello:) ( (x:) (o4 []) )
= hello : x : (o4 [])

Now we have some data!  We can output these two elements without
evaluating o4 at all!

So we do, and then we need to evaluate o4.  But that just is starting
over; o4 = getOutputs (step test i3).  We do have a different input
(i3 vs. i0), but the rest of the logic is the same, and we keep going
until we get to the end of the input list, at which point the pattern
match failure in inp hits us.

 But is this monad really useful? I mean it would be straightforward to write
 this using the ST monad I guess?

It's kind of useful.  I don't think I'd use ST, though.  It's isomorphic to
StateT [String] (Writer (DList String))

 Anyway, the reason why I want this pure code is that even with a console
 based game, I don't want IO in it, since recording the input and replaying
 it is vital to reproduce the actions the user did, and if things go wrong
 (they always do), the log of all input can be used to restore the exact game
 play. Of course you can do the same using imperative techniques and IO
 redirection (which I did for my old games), but with this pure code you
 don't have to worry about other places where IO could be used.

For logging/testing/whatever, I suggest building your monad based off
of MonadPrompt; it guarantees that all impure actions go through a
datatype which you can then log.  Check it out!
http://hackage.haskell.org/package/MonadPrompt

You can then change the implementation of what does this impure
action do without changing any of the logging or gameplay code.  For
example, you could have a object agent monad which each character
runs under, that is able to observe parts of the gamestate, and then
write an interpreter that allows the user to play the game (through an
impure I/O interface that draws to the screen) and another interpreter
which runs an AI (through a pure functional or memory-state-based
interface).

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
This is very very informative, thanks.
One thing I still struggle with (because I haven't practiced much I guess)
is writing down the desugaring/evaluation/expansion/reduction (how do you
call it?). I know how to do it more or less (tried it for a fix fac, since
fix feels like magic for an imperative programmer). This is unfortunate,
because the claim that Haskell is easier to reason with together with
controlling space/time only works I guess if you (1) developed an
intuition about how the evaluation exactly works and/or (2) are trained in
this algebraic rewriting (which I was 20 years ago ;-) If I do the
rewriting, I often get it wrong (too lazy, too strict) and this it is rather
useless. And many of the examples I've seem seem to skim many obvious
rewriting steps that don't feel that obvious to me.

But you gave a good exercise here :-)

This is typical for when I see Haskell code from experts: how do they make
it so compact? Often the code is unreadable then, but in the case of your
cleanup, I had to feeling why didn't write it like that in the first place?
It seems so obvious ;-) This also has an intimidating effect sometimes,
since as a newbie (and it feels that I'm still a newbie after a year) it's
hard to show code without looking like a fool. Luckily Haskell people are
very friendly and helpful!

On Thu, Aug 20, 2009 at 10:18 AM, Ryan Ingram ryani.s...@gmail.com wrote:

 On Wed, Aug 19, 2009 at 1:20 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  Well I really wrote this code as an exercise, and it was a good one. Now
 I
  (or someone) needs to explain why it works.

 There's a bit of trickiness, but it's not that hard when you break it down.

 Lets look at a simplified version of test:

 test = do
x - inp
out hello
out x
test

 Desugaring a bit:

 test
 = inp = \x - out hello  out x  test
 = S (\(i:is) - (is, empty, i))
   = \x - S (\is - (is, singleton hello, ()))
   = \_ - S (\is - (is, singleton x, ()))
   = \_ - test

 Now, inlining = and simplifying, we get:

 test = S (\i0 - let
   (i1, o1, x) = (\(i:is) - (is, empty, i)) i0
   (i2, o2, _) = (i1, singleton hello, ())
   (i3, o3, _) = (i2, singleton x, ())
   (i4, o4, res) = step test i3
   outputs = o1 `mappend` o2 `mappend` o3 `mappend` o4
  in (i4, outputs, res))

 The first thing to notice is that when we run test by giving it some
 input, we *immediately* get a triple back:
(i4, outputs, res)
 with the values in the triple being unevaluated thunks.

 res is _|_; trying to evaluate it will infinite loop.  Similarily
 for i4.  But fortunately we never do; getOutput throws them both away.
 So the only thing we care about is outputs.

 outputs is infinite as well, but we have hope!  As long as `mappend`
 is lazy in its second argument, we might be able to get some data out!

 Lets simplify Data.DList a bit:

 mappend = (.)
 singleton = (:)
 empty = id
 fromList = (++)
 toList = ($ [])

 Now lets try to evaluate (toList outputs):

 toList outputs
 = ($ []) (o1 . o2 . o3 . o4)
 = o1 . o2 . o3 . o4 $ []
 = o1 (o2 (o3 (o4 [])))

 We need to evaluate o1 in order to call it.  There is a possibility
 that it is _|_ :
(i1, o1, x) = (\(i:is) - (is, empty, i)) i0

 Therefore
   o1 = case i0 of
   (i:is) - empty
   [] - error pattern match failure
i1 = case i0 of
   (i:is) - is
   [] - error pattern match failure
x = case i0 of
(i:is) - i
[] - error pattern match failure

 So as long as you type a line, o1 will be empty (= id).  But we
 don't know that you necessarily will type an input line, so the code
 *has* to wait for the line of input from the user, and can't print any
 later values.  (This is where you get into some of the craziness of
 lazy I/O)

 Once you type a line, i0 gets bound to (whatever you type : some lazy
 thunk representing the rest of the input) and o1 gets evaluated to id.

 toList outputs
 = o1 (o2 (o3 (o4 [])))
 = id (o2 (o3 (o4 [])))
 = o2 (o3 (o4 []))

 o2 and o3 are easy:
   (i2, o2, _) = (i1, singleton hello, ())
   (i3, o3, _) = (i2, singleton x, ())
 therefore
o2 = (hello :)
o3 = (x :)

 toList outputs
 = o2 (o3 (o4 []))
 = (hello:) ( (x:) (o4 []) )
 = hello : x : (o4 [])

 Now we have some data!  We can output these two elements without
 evaluating o4 at all!

 So we do, and then we need to evaluate o4.  But that just is starting
 over; o4 = getOutputs (step test i3).  We do have a different input
 (i3 vs. i0), but the rest of the logic is the same, and we keep going
 until we get to the end of the input list, at which point the pattern
 match failure in inp hits us.

  But is this monad really useful? I mean it would be straightforward to
 write
  this using the ST monad I guess?

 It's kind of useful.  I don't think I'd use ST, though.  It's isomorphic to
 StateT [String] (Writer (DList String))

  Anyway, the reason why I want this pure code is that even with a console
  based game, I 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Jules Bean

Peter Verswyvelen wrote:

Not at all, use it for whatever you want to :-)

I'm writing this code because I'm preparing to write a bunch of 
tutorials on FRP, and I first wanted to start with simple console based 
FRP, e.g. making a little text adventure game, where the input/choices 
of the user might be parsed ala parsec, using monadic style, applicative 
style, and arrows, and then doing the same with FRP frameworks like 



This is a really bad place to start a FRP tutorial IMO.

The interface for 'interact' does not make any promises about the 
relative evaluation order of the input list / production order of the 
output list.


That's why you are having to play horrible tricks with seq to try to 
force the order to be what you want.


I don't think this is the basis of a robust system or a sensible tutorial.

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
I don't fully understand.
interact gives you a stream of input characters that the user types, and
produces a stream of output characters that are displayed back (with
buffering set to NoBuffering). it should behave predictable no?

and since the input that the user gives depends on the output on the screen
(it represents the user - machine dialog loop), we must make sure that
laziness does not go wild and strictness is needed to respect this
dependency. But as Ryan showed, seq is not really needed (but pattern
matching is), and his code is super elegant and simple. I also remember from
the Haskell School of Expression that putting lazy pattern matches (in
switch if I recall correctly) here and there is needed to avoid blocking or
inf loops. Also in Reactive this was important. In Yampa you need to mark
the outputs strict to avoid delayed computations from building up  (like sum
and foldl does). So it seems finding a good balance between strictness and
laziness is really important in FRP, at least for the engine, and in the
case of Yampa, also for the end user.

E.g in Ryans cleanup, if you replace inp  by

inp :: S String
inp = S $ \i - (tail i, D.empty, head i)

then the ordering of input to output is incorrect, too much output is
printed before the input is requested. it clearly demonstrates the effect of
laziness to me really, in a much easier to observe way than stack overflows
or infinite loops no?

how is interact different from a graphical user interface system or game
simulation, in which the input is a stream of events (or behaviors, samples,
whatever) from mouse, keyboard, timers, etc, and the output is a list of
pictures or geometry?

The tutorial I would like to make is exactly for this kind of feedback from
domain experts, so maybe tutorial is not the correct word, more a
discussion or journey.

Anyway I don't think I'm qualified to make a tutorial since I'm still
learning the basics, but with feedback from you guys (I already have
interest from Hai (Paul) Liu (Yampa) and Patai Gergely (Elerea) it might
still become a valuable resource?

On Thu, Aug 20, 2009 at 11:52 AM, Jules Bean ju...@jellybean.co.uk wrote:

 Peter Verswyvelen wrote:

 Not at all, use it for whatever you want to :-)

 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like



 This is a really bad place to start a FRP tutorial IMO.

 The interface for 'interact' does not make any promises about the relative
 evaluation order of the input list / production order of the output list.

 That's why you are having to play horrible tricks with seq to try to force
 the order to be what you want.

 I don't think this is the basis of a robust system or a sensible tutorial.

 Just my 2c.

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
It seems that with Ryan's approach, DList is not needed, simple concat works
fine.
It also seems to run in constant space. Now I must do the exercise of
rewriting it to see why concat works, since = is infixl and ++ is infixr,
this seems odd :) But again, my mind might be thinking too strict (bad
imperative habits?)

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8357
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Leimbach
On Thu, Aug 20, 2009 at 2:52 AM, Jules Bean ju...@jellybean.co.uk wrote:

 Peter Verswyvelen wrote:

 Not at all, use it for whatever you want to :-)

 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like



 This is a really bad place to start a FRP tutorial IMO.

 The interface for 'interact' does not make any promises about the relative
 evaluation order of the input list / production order of the output list.

 That's why you are having to play horrible tricks with seq to try to force
 the order to be what you want.

 I don't think this is the basis of a robust system or a sensible tutorial.

 Just my 2c.


Interesting feedback, but I don't get the reason really.  How is using seq a
horrible trick?  It's there for strict evaluation when you need it, and in
this case it was warranted.

And as far as saying it's not a good basis for a robust system, I'm also not
sure I agree, but a sensible tutorial, that I could believe as I think
it's actually quite difficult to explain these topics to people in a way
they're going to understand right away.

Could we perhaps bother you to suggest an alternative along with your
criticism?  It would feel a little more constructive at least (not that I
think you were being terribly harsh)

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Leimbach


 and since the input that the user gives depends on the output on the screen
 (it represents the user - machine dialog loop), we must make sure that
 laziness does not go wild and strictness is needed to respect this
 dependency. But as Ryan showed, seq is not really needed (but pattern
 matching is), and his code is super elegant and simple. I


I'm pretty certain that forcing a pattern match via case is what disallows
the laziness to get out of hand.  The case statement, when evaluated, must
choose a matched pattern branch, even if it's the only possibility, which
ends up boiling down to seq anyway doesn't it?

Or is it that case doesn't have to go through as deep an evaluation as seq
does in some cases?  Does that even make any sense?  :-)

Dave




 On Thu, Aug 20, 2009 at 11:52 AM, Jules Bean ju...@jellybean.co.ukwrote:

 Peter Verswyvelen wrote:

 Not at all, use it for whatever you want to :-)

 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like



 This is a really bad place to start a FRP tutorial IMO.

 The interface for 'interact' does not make any promises about the relative
 evaluation order of the input list / production order of the output list.

 That's why you are having to play horrible tricks with seq to try to force
 the order to be what you want.

 I don't think this is the basis of a robust system or a sensible tutorial.

 Just my 2c.



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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ryan Ingram
On Thu, Aug 20, 2009 at 7:37 AM, David Leimbachleim...@gmail.com wrote:
 I'm pretty certain that forcing a pattern match via case is what disallows
 the laziness to get out of hand.  The case statement, when evaluated, must
 choose a matched pattern branch, even if it's the only possibility, which
 ends up boiling down to seq anyway doesn't it?

Yep, it's basically the same, just prettier, and, in my opinion, more
clearly specifies what it is you are trying to do.

Compare these identical code fragments:

(a) \xs - (tail xs, xs `seq` empty, head xs)
(b) \(x:xs) - (xs, empty, x)

Here are the possibilities for input:

(1) input is _|_
   (a) (_|_, _|_, _|_)
   (b) _|_
(2) input is []
   (a) (_|_, empty, _|_)
   (b) _|_
(3) input is (x:xs)
   (a) (xs, empty, x)
   (b) (xs, empty, x)

In the case of lazy I/O, you can sort-of-imagine the _|_ input case as
a value that means don't know yet; the computation is incrementally
updated as the input becomes more defined.  It's complicated because
now you have to differentiate don't know _|_ with erroneous _|_
such as the results of case (2).

If it helps you twist your head around it, think of the input to
interact as coming from a big but slow pure function that is computing
the behavior of every atom in the universe and returning what keys on
a keyboard are getting pressed.  So when you pattern match against
that input, you have to wait for the computation to happen; someone
who doesn't type anything is like that function going into an infinite
loop _|_.  But you can't know if it might decide to return a value
(halting problem!) so you keep running it anyways.

 Or is it that case doesn't have to go through as deep an evaluation as seq
 does in some cases?  Does that even make any sense?  :-)

It's the same as seq; both reduce the argument to WHNF which means
that the constructor type ([] vs. (:) is known.

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ryan Ingram
On Thu, Aug 20, 2009 at 9:56 AM, Ryan Ingramryani.s...@gmail.com wrote:
 Compare these identical code fragments:

Er, strike identical.  Oops!  Comparing identical fragments would be boring.

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Lennart Augustsson
Using seq to control a program's semantics (as in, input-output
behaviour) is a horrible hack.
The seq operation there to control space and time aspects of your program.
(The specification of seq doesn't even say that the first argument is
evaluated before the second one.)
You should use data dependencies to control your program's semantics.

On Thu, Aug 20, 2009 at 4:34 PM, David Leimbachleim...@gmail.com wrote:


 On Thu, Aug 20, 2009 at 2:52 AM, Jules Bean ju...@jellybean.co.uk wrote:

 Peter Verswyvelen wrote:

 Not at all, use it for whatever you want to :-)

 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like


 This is a really bad place to start a FRP tutorial IMO.

 The interface for 'interact' does not make any promises about the relative
 evaluation order of the input list / production order of the output list.

 That's why you are having to play horrible tricks with seq to try to force
 the order to be what you want.

 I don't think this is the basis of a robust system or a sensible tutorial.

 Just my 2c.

 Interesting feedback, but I don't get the reason really.  How is using seq a
 horrible trick?  It's there for strict evaluation when you need it, and in
 this case it was warranted.
 And as far as saying it's not a good basis for a robust system, I'm also not
 sure I agree, but a sensible tutorial, that I could believe as I think
 it's actually quite difficult to explain these topics to people in a way
 they're going to understand right away.
 Could we perhaps bother you to suggest an alternative along with your
 criticism?  It would feel a little more constructive at least (not that I
 think you were being terribly harsh)
 Dave
 ___
 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] Re: Where do I put the seq?

2009-08-20 Thread Ketil Malde
David Leimbach leim...@gmail.com writes:

 I'm pretty certain that forcing a pattern match via case is what disallows
 the laziness to get out of hand.  The case statement, when evaluated, must
 choose a matched pattern branch, even if it's the only possibility, which
 ends up boiling down to seq anyway doesn't it?

Prelude case undefined of x - ()
()

So I think you are incorrect: the 'undefined' here isn't evaluated by
the case. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Antoine Latter
On Thu, Aug 20, 2009 at 1:02 PM, Ketil Maldeke...@malde.org wrote:
 David Leimbach leim...@gmail.com writes:

 I'm pretty certain that forcing a pattern match via case is what disallows
 the laziness to get out of hand.  The case statement, when evaluated, must
 choose a matched pattern branch, even if it's the only possibility, which
 ends up boiling down to seq anyway doesn't it?

    Prelude case undefined of x - ()
    ()

 So I think you are incorrect: the 'undefined' here isn't evaluated by
 the case.


It's doing a case on a pattern match that forces evaluation.  Try:

 case undefined of (x:xs) - ()

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
I totally agree that data dependencies are the best way to do that. And I'm
beginning to see why interact might not be suitable for demonstrating FRP.
On the other hand, when you say data dependencies, you mean that the value
of expression A depends on the value of expression B, but what if that value
is not really needed?

For example, suppose you want a program that asks the name of the user and
then outputs What a nice name or What a weird name depending on some
random value. Even though the input value from the user is not used, we
still can't output the text before the input is entered. Again the hidden
dependency is time itself I guess, so we should do it the real FRP way, even
with dumb console text IO.

Also doesn't Haskell's IO system uses a hidden RealWorld type that has no
value but which is passed from between monadics binds in a strict way to
make the ordering work? So IO in Haskell is a horrible hack then? :-) If it
would be done nicely, in the FRP way, then RealWorld IO would need time
stamps to get rid of the hack?

So to do console IO the FRP way (say like in Reactive), the input lines
 from the user would be Event String, and the output also Event String. Each
event occurrence has a time stamp, and when merged, they would be ordered.
It would be nice to show this example in Reactive. Too bad Reactive doesn't
work (and it's not sure it ever will according to the comment of some
users), but for a simple example like this, I'm sure it works. In Yampa, I'm
not sure how console based IO would work, I guess it would need to generate
event non-occurrences (Nothing) when the user did not type anything, and we
would need non-blocking IO, so 100% CPU load, since it's pull based, not
sure, to be investigated. I haven't worked with Elerea nor Grapefruit yet,
but I'm not sure if I should treat the former as a real FRP system since it
is not referentially transparent (it would be nice to know which combinators
break it).

On the other hand, in this simple example, I could use a strict field in an
ADT to enforce the input-output dependency, but I guess this is just the
same big hack? (see http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8367
)

This silly example is causing lots of feedback, cool :-)

On Thu, Aug 20, 2009 at 7:12 PM, Lennart Augustsson
lenn...@augustsson.netwrote:

 Using seq to control a program's semantics (as in, input-output
 behaviour) is a horrible hack.
 The seq operation there to control space and time aspects of your program.
 (The specification of seq doesn't even say that the first argument is
 evaluated before the second one.)
 You should use data dependencies to control your program's semantics.

 On Thu, Aug 20, 2009 at 4:34 PM, David Leimbachleim...@gmail.com wrote:
 
 
  On Thu, Aug 20, 2009 at 2:52 AM, Jules Bean ju...@jellybean.co.uk
 wrote:
 
  Peter Verswyvelen wrote:
 
  Not at all, use it for whatever you want to :-)
 
  I'm writing this code because I'm preparing to write a bunch of
 tutorials
  on FRP, and I first wanted to start with simple console based FRP, e.g.
  making a little text adventure game, where the input/choices of the
 user
  might be parsed ala parsec, using monadic style, applicative style, and
  arrows, and then doing the same with FRP frameworks like
 
 
  This is a really bad place to start a FRP tutorial IMO.
 
  The interface for 'interact' does not make any promises about the
 relative
  evaluation order of the input list / production order of the output
 list.
 
  That's why you are having to play horrible tricks with seq to try to
 force
  the order to be what you want.
 
  I don't think this is the basis of a robust system or a sensible
 tutorial.
 
  Just my 2c.
 
  Interesting feedback, but I don't get the reason really.  How is using
 seq a
  horrible trick?  It's there for strict evaluation when you need it, and
 in
  this case it was warranted.
  And as far as saying it's not a good basis for a robust system, I'm also
 not
  sure I agree, but a sensible tutorial, that I could believe as I think
  it's actually quite difficult to explain these topics to people in a way
  they're going to understand right away.
  Could we perhaps bother you to suggest an alternative along with your
  criticism?  It would feel a little more constructive at least (not that I
  think you were being terribly harsh)
  Dave
  ___
  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

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Dan Weston

Peter,

I think you are right that there is no way in general to prevent a valid 
graph rewrite to remove a vacuous dependency. That is why seq is there.


The funny business is visible right in the type signature of seq:

seq :: forall a t. a - t - t

If seq had nonstrict semantics, this would be isomorphic to t - t, 
which is inhabited only by id. So, if seq is going to have any useful 
effect, it must be strict. Since Haskell is nonstrict by default (absent 
some deconstruction, which requires knowledge of the value 
constructors), you need an extra-language primitive to do this. Don't 
look to case to do this.


And other strictifying syntax constructs like ! are just syntactic 
sugar, so they don't count.


Dan

Peter Verswyvelen wrote:
I totally agree that data dependencies are the best way to do that. And 
I'm beginning to see why interact might not be suitable for 
demonstrating FRP. 

On the other hand, when you say data dependencies, you mean that the 
value of expression A depends on the value of expression B, but what if 
that value is not really needed? 

For example, suppose you want a program that asks the name of the user 
and then outputs What a nice name or What a weird name depending on 
some random value. Even though the input value from the user is not 
used, we still can't output the text before the input is entered. Again 
the hidden dependency is time itself I guess, so we should do it the 
real FRP way, even with dumb console text IO.


Also doesn't Haskell's IO system uses a hidden RealWorld type that has 
no value but which is passed from between monadics binds in a strict way 
to make the ordering work? So IO in Haskell is a horrible hack then? :-) 
If it would be done nicely, in the FRP way, then RealWorld IO would need 
time stamps to get rid of the hack?
  
So to do console IO the FRP way (say like in Reactive), the input lines 
 from the user would be Event String, and the output also Event String. 
Each event occurrence has a time stamp, and when merged, they would be 
ordered. It would be nice to show this example in Reactive. Too bad 
Reactive doesn't work (and it's not sure it ever will according to the 
comment of some users), but for a simple example like this, I'm sure it 
works. In Yampa, I'm not sure how console based IO would work, I guess 
it would need to generate event non-occurrences (Nothing) when the user 
did not type anything, and we would need non-blocking IO, so 100% CPU 
load, since it's pull based, not sure, to be investigated. I haven't 
worked with Elerea nor Grapefruit yet, but I'm not sure if I should 
treat the former as a real FRP system since it is not referentially 
transparent (it would be nice to know which combinators break it).
 
On the other hand, in this simple example, I could use a strict field in 
an ADT to enforce the input-output dependency, but I guess this is just 
the same big hack? 
(see http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8367)


This silly example is causing lots of feedback, cool :-)

On Thu, Aug 20, 2009 at 7:12 PM, Lennart Augustsson 
lenn...@augustsson.net mailto:lenn...@augustsson.net wrote:


Using seq to control a program's semantics (as in, input-output
behaviour) is a horrible hack.
The seq operation there to control space and time aspects of your
program.
(The specification of seq doesn't even say that the first argument is
evaluated before the second one.)
You should use data dependencies to control your program's semantics.

On Thu, Aug 20, 2009 at 4:34 PM, David Leimbachleim...@gmail.com
mailto:leim...@gmail.com wrote:
 
 
  On Thu, Aug 20, 2009 at 2:52 AM, Jules Bean
ju...@jellybean.co.uk mailto:ju...@jellybean.co.uk wrote:
 
  Peter Verswyvelen wrote:
 
  Not at all, use it for whatever you want to :-)
 
  I'm writing this code because I'm preparing to write a bunch of
tutorials
  on FRP, and I first wanted to start with simple console based
FRP, e.g.
  making a little text adventure game, where the input/choices of
the user
  might be parsed ala parsec, using monadic style, applicative
style, and
  arrows, and then doing the same with FRP frameworks like
 
 
  This is a really bad place to start a FRP tutorial IMO.
 
  The interface for 'interact' does not make any promises about
the relative
  evaluation order of the input list / production order of the
output list.
 
  That's why you are having to play horrible tricks with seq to
try to force
  the order to be what you want.
 
  I don't think this is the basis of a robust system or a sensible
tutorial.
 
  Just my 2c.
 
  Interesting feedback, but I don't get the reason really.  How is
using seq a
  horrible trick?  It's there for strict evaluation when you need
it, and in
  this case it was warranted.
  And as far as saying it's not a good 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 3:43 PM, Peter Verswyvelenbugf...@gmail.com wrote:

 Also doesn't Haskell's IO system uses a hidden RealWorld type that has no
 value but which is passed from between monadics binds in a strict way to
 make the ordering work?

Haskell only describes how the IO monad behaves. GHC's implementation
uses a RealWorld type, but other implementations are possible.

A quick sketch of an alternative implementation,

data Trace = Done | Get (Char - Trace) | Put Char Trace

newtype IO a = IO { unIO :: (a - Trace) - Trace }

instance Monad IO where
return a = IO (\k - k a)
m = f = IO (\k - unIO m (\a - unIO (f a) k))

getChar :: IO Char
getChar = IO Get

putChar :: Char - IO ()
putChar c = IO (\k - Put c (k ()))

The run-time system is responsible for interpreting the Trace and
inputting/outputting characters as needed. All of IO can be
implemented in this manner.

 So IO in Haskell is a horrible hack then? :-) If it
 would be done nicely, in the FRP way, then RealWorld IO would need time
 stamps to get rid of the hack?

Again, no. GHC's IO type uses the RealWorld value to create data
dependencies. For example, putChar 'x'  getChar, the getChar depends
on the RealWorld returned by putChar 'x'.

This is why it's dangerous to open up GHC's IO type unless you know
what you're doing. If you aren't careful, you may accidentally
duplicate or destroy the RealWorld, at which point you risk losing
purity and referential transparency.

I suppose you could consider the fact that GHC's IO is implemented
using impure primitive operations a hack, but the whole point of the
IO monad is to hide that impurity from the rest of the program.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
But how does GHC implement the RealWorld internally? I guess this can't be
done using standard Haskell stuff? It feels to me that if I would implement
it, I would need seq again, or a strict field, or some incrementing time
value that is a strict argument of each of the IO primitives. In any case, I
would need strictness to control the dependencies no? I might be wrong
(again) but this is all very interesting ;-)


On Thu, Aug 20, 2009 at 10:25 PM, David Menendez d...@zednenem.com wrote:

 On Thu, Aug 20, 2009 at 3:43 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
 
  Also doesn't Haskell's IO system uses a hidden RealWorld type that has no
  value but which is passed from between monadics binds in a strict way to
  make the ordering work?

 Haskell only describes how the IO monad behaves. GHC's implementation
 uses a RealWorld type, but other implementations are possible.

 A quick sketch of an alternative implementation,

 data Trace = Done | Get (Char - Trace) | Put Char Trace

 newtype IO a = IO { unIO :: (a - Trace) - Trace }

 instance Monad IO where
return a = IO (\k - k a)
m = f = IO (\k - unIO m (\a - unIO (f a) k))

 getChar :: IO Char
 getChar = IO Get

 putChar :: Char - IO ()
 putChar c = IO (\k - Put c (k ()))

 The run-time system is responsible for interpreting the Trace and
 inputting/outputting characters as needed. All of IO can be
 implemented in this manner.

  So IO in Haskell is a horrible hack then? :-) If it
  would be done nicely, in the FRP way, then RealWorld IO would need time
  stamps to get rid of the hack?

 Again, no. GHC's IO type uses the RealWorld value to create data
 dependencies. For example, putChar 'x'  getChar, the getChar depends
 on the RealWorld returned by putChar 'x'.

 This is why it's dangerous to open up GHC's IO type unless you know
 what you're doing. If you aren't careful, you may accidentally
 duplicate or destroy the RealWorld, at which point you risk losing
 purity and referential transparency.

 I suppose you could consider the fact that GHC's IO is implemented
 using impure primitive operations a hack, but the whole point of the
 IO monad is to hide that impurity from the rest of the program.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 4:41 PM, Peter Verswyvelenbugf...@gmail.com wrote:
 But how does GHC implement the RealWorld internally? I guess this can't be
 done using standard Haskell stuff? It feels to me that if I would implement
 it, I would need seq again, or a strict field, or some incrementing time
 value that is a strict argument of each of the IO primitives. In any case, I
 would need strictness to control the dependencies no? I might be wrong
 (again) but this is all very interesting ;-)

The RealWorld is just a token that GHC uses to force IO computations
to have the correct data dependencies. If you look at code like
putChar 'x'  getChar, there's no obvious data dependency that
would prevent executing getChar before putChar, so internally the IO
monad passes around the RealWorld token to guarantee the ordering.

I don't know the exact details of GHC's IO internals, but I'd expect
putChar 'x'  getChar to translate into something like this,

\rw0 - let ((), rw1) = putChar# 'x' rw0 in getChar# rw1

The important things to note are (1) getChar# depends on the token
returned by putChar#, thus guaranteeing that putChar# gets executed
first, and (2) putChar# and getChar# are impure and cannot normally be
defined in Haskell.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
On Thu, Aug 20, 2009 at 11:23 PM, David Menendez d...@zednenem.com wrote:

 The important things to note are (1) getChar# depends on the token
 returned by putChar#, thus guaranteeing that putChar# gets executed
 first, and (2) putChar# and getChar# are impure and cannot normally be
 defined in Haskell.


Ok, that I understand. But if getChar# and putChar# would be pure functions
that just generate some output string / consume some input string, then this
realworld token passing would not work when used with interact, since
neither the output or input string really depends on the dummy token, unless
using a seq again (or strictness annotation, which was explained to be just
syntactic sugar for seq)? But how would we then make a pure monad that can
be used as in my example together with interact? I see no reason why to put
everything in IO when it just comes to converting a stream of inputs to a
stream of outputs? So interact really is useless, unless you just fmap
something over the input or when the output is independent from the input?

As Ryan said, I could use his MonadPrompt for this, but that's a different
approach (and maybe the only correct one)

I'm still curious to see how an FRP solution would look for simple console
based IO though :-) Probably a good exercise to do.



 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 6:57 PM, Peter Verswyvelenbugf...@gmail.com wrote:

 On Thu, Aug 20, 2009 at 11:23 PM, David Menendez d...@zednenem.com wrote:

 The important things to note are (1) getChar# depends on the token
 returned by putChar#, thus guaranteeing that putChar# gets executed
 first, and (2) putChar# and getChar# are impure and cannot normally be
 defined in Haskell.

 Ok, that I understand. But if getChar# and putChar# would be pure functions
 that just generate some output string / consume some input string, then this
 realworld token passing would not work when used with interact, since
 neither the output or input string really depends on the dummy token, unless
 using a seq again (or strictness annotation, which was explained to be just
 syntactic sugar for seq)?

I'm not sure I understand your question, but I think it's possible to
use interact in the way you want. For example, this code behaves
correctly for me:

foo i =
let i1 = lines i
in Enter your name:  ++
(case i1 of
[] - error EOF
name:i2 - Welcome  ++ name ++ \n)

Prelude interact foo
Enter your name: Bob
Welcome Bob

Note the dependencies here. When you call interact foo, the prompt can
be immediately output without reading any of the input. However,
Welcome cannot be printed until one line of the input has been read
(or EOF reached) because it's inside the pattern match on i1.


 But how would we then make a pure monad that can
 be used as in my example together with interact? I see no reason why to put
 everything in IO when it just comes to converting a stream of inputs to a
 stream of outputs? So interact really is useless, unless you just fmap
 something over the input or when the output is independent from the input?

Not necessarily. Your situation reminds me of Haskell's I/O system
before the IO monad was introduced. (See section 7 of A History of
Haskell: Being Lazy With Class for details.
http://research.microsoft.com/en-us/um/people/simonpj/papers/history-of-haskell/history.pdf)

In it, they describe how older versions of Haskell could be defined in
terms of lazy request and response streams, how you can use
continuation-passing to build the streams in a more localized way, and
then how you could define the IO monad in terms of that.

This works for me:

import Control.Monad.Cont

type Behavior = [String] - String
type MyIO = Cont Behavior

putLine :: String - MyIO ()
putLine s = Cont $ \k ss - s ++ k () ss

getLine :: MyIO String
getLine = Cont $ \k (s:ss) - k s ss

run :: MyIO () - Behavior
run m = runCont m (\_ _ - [])

foo = do
putLine Enter name: 
name - getLine
putLine (Welcome  ++ name ++ \n)

Prelude Control.Monad.Cont interact (run foo . lines)
Enter name: Dave
Welcome Dave

It may be instructive to manually expand run foo.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Try LineBuffering.
I do linewise stuff with interact a lot.  You'll find stuff like

unlines . lines

may help too.  In fact I just wrote a blog post about this.

http://leimy9.blogspot.com

I'm trying to write some interactive code to automate working with serial
console controlled power strips, so I need to either use Expect (yuck) or do
my own thing.

Dave

On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Apparently this particular example happens to work on Mac and Linux because
 of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin NoBuffering  
 test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not sure.

 I would like to use a graphical tool to show the graph reduction step by
 step, to get a better understanding of the laziness  strictness. Does such
 a tool exist? I know people often say this is not usable because the amount
 of information is too much, but I used to be an assembly language programmer
 so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 In an attempt to get a deeper understanding of several monads (State, ST,
 IO, ...) I skimmed over some of the research papers (but didn't understand
 all of it, I lack the required education) and decided to write a little
 program myself without using any prefab monad instances that should mimic
 the following:
 main = do
   putStrLn Enter your name:
   x - getLine
   putStr Welcome 
   putStrLn x
   putStrLn Goodbye!

 But instead of using IO, I wanted to make my own pure monad that gets
 evaluated with interact, and does the same.

 However, I get the following output:

 Enter your name:
 Welcome ..

 So the Welcome is printed too soon.

 This is obvious since my monad is lazy, so I tried to put a seq at some
 strategic places to get the same behavior as IO. But I completely failed
 doing so, either the program doesn't print anything and asks input first, or
 it still prints too much output.

 Of course I could just use ST, State, transformers, etc, but this is
 purely an exercise I'm doing.

 So, I could re-read all papers and look in detail at all the code, but
 maybe someone could help me out where to put the seq or what to do :-)

 The code is at http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316

 Oh btw, the usage of DList here might not be needed; intuitively it felt
 like the correct thing to do, but when it comes to Haskell, my intuition is
 usually wrong ;-)

 Thanks a lot,
 Peter Verswyvelen



 ___
 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] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
Thanks, but that doesn't really matter in my example, my code is just buggy,
and I'm not sure why. For example if I change my test function so that it
outputs lines only, then it still prints Welcome first before asking for
input.
See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.com wrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with serial
 console controlled power strips, so I need to either use Expect (yuck) or do
 my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin NoBuffering 
  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not sure.

 I would like to use a graphical tool to show the graph reduction step by
 step, to get a better understanding of the laziness  strictness. Does such
 a tool exist? I know people often say this is not usable because the amount
 of information is too much, but I used to be an assembly language programmer
 so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 In an attempt to get a deeper understanding of several monads (State, ST,
 IO, ...) I skimmed over some of the research papers (but didn't understand
 all of it, I lack the required education) and decided to write a little
 program myself without using any prefab monad instances that should mimic
 the following:
 main = do
   putStrLn Enter your name:
   x - getLine
   putStr Welcome 
   putStrLn x
   putStrLn Goodbye!

 But instead of using IO, I wanted to make my own pure monad that gets
 evaluated with interact, and does the same.

 However, I get the following output:

 Enter your name:
 Welcome ..

 So the Welcome is printed too soon.

 This is obvious since my monad is lazy, so I tried to put a seq at some
 strategic places to get the same behavior as IO. But I completely failed
 doing so, either the program doesn't print anything and asks input first, or
 it still prints too much output.

 Of course I could just use ST, State, transformers, etc, but this is
 purely an exercise I'm doing.

 So, I could re-read all papers and look in detail at all the code, but
 maybe someone could help me out where to put the seq or what to do :-)

 The code is at http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316

 Oh btw, the usage of DList here might not be needed; intuitively it felt
 like the correct thing to do, but when it comes to Haskell, my intuition is
 usually wrong ;-)

 Thanks a lot,
 Peter Verswyvelen



 ___
 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] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
On Wed, Aug 19, 2009 at 8:12 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before asking
 for input.



Ah I see, I misunderstood. Sorry for the noise!  ;-)  I thought perhaps
you'd hit something I ran into last night.


Dave


 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.com wrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with serial
 console controlled power strips, so I need to either use Expect (yuck) or do
 my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not sure.

 I would like to use a graphical tool to show the graph reduction step by
 step, to get a better understanding of the laziness  strictness. Does such
 a tool exist? I know people often say this is not usable because the amount
 of information is too much, but I used to be an assembly language programmer
 so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 In an attempt to get a deeper understanding of several monads (State,
 ST, IO, ...) I skimmed over some of the research papers (but didn't
 understand all of it, I lack the required education) and decided to write a
 little program myself without using any prefab monad instances that should
 mimic the following:
 main = do
   putStrLn Enter your name:
   x - getLine
   putStr Welcome 
   putStrLn x
   putStrLn Goodbye!

 But instead of using IO, I wanted to make my own pure monad that gets
 evaluated with interact, and does the same.

 However, I get the following output:

 Enter your name:
 Welcome ..

 So the Welcome is printed too soon.

 This is obvious since my monad is lazy, so I tried to put a seq at some
 strategic places to get the same behavior as IO. But I completely failed
 doing so, either the program doesn't print anything and asks input first, 
 or
 it still prints too much output.

 Of course I could just use ST, State, transformers, etc, but this is
 purely an exercise I'm doing.

 So, I could re-read all papers and look in detail at all the code, but
 maybe someone could help me out where to put the seq or what to do :-)

 The code is at http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316

 Oh btw, the usage of DList here might not be needed; intuitively it felt
 like the correct thing to do, but when it comes to Haskell, my intuition is
 usually wrong ;-)

 Thanks a lot,
 Peter Verswyvelen



 ___
 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] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
I fixed it myself but it's really tricky :-)
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea is, that
when the input is requested, the output that is then generated must be in
sync with the input.

inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i**
**`**seq**`** **D**.**empty**)*, head i) in (tail i, r)


I first had

inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


But that was too eager, since i syncs the input not with the output, but
with the function that will generate the output.

Okay, now I can sleep again :-)




On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before asking
 for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.com wrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with serial
 console controlled power strips, so I need to either use Expect (yuck) or do
 my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not sure.

 I would like to use a graphical tool to show the graph reduction step by
 step, to get a better understanding of the laziness  strictness. Does such
 a tool exist? I know people often say this is not usable because the amount
 of information is too much, but I used to be an assembly language programmer
 so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 In an attempt to get a deeper understanding of several monads (State,
 ST, IO, ...) I skimmed over some of the research papers (but didn't
 understand all of it, I lack the required education) and decided to write a
 little program myself without using any prefab monad instances that should
 mimic the following:
 main = do
   putStrLn Enter your name:
   x - getLine
   putStr Welcome 
   putStrLn x
   putStrLn Goodbye!

 But instead of using IO, I wanted to make my own pure monad that gets
 evaluated with interact, and does the same.

 However, I get the following output:

 Enter your name:
 Welcome ..

 So the Welcome is printed too soon.

 This is obvious since my monad is lazy, so I tried to put a seq at some
 strategic places to get the same behavior as IO. But I completely failed
 doing so, either the program doesn't print anything and asks input first, 
 or
 it still prints too much output.

 Of course I could just use ST, State, transformers, etc, but this is
 purely an exercise I'm doing.

 So, I could re-read all papers and look in detail at all the code, but
 maybe someone could help me out where to put the seq or what to do :-)

 The code is at http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316

 Oh btw, the usage of DList here might not be needed; intuitively it felt
 like the correct thing to do, but when it comes to Haskell, my intuition is
 usually wrong ;-)

 Thanks a lot,
 Peter Verswyvelen



 ___
 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] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
This doesn't seem to be working for me interactively though on a Mac.  I
still get Welcome before I've entered text.

On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea is,
 that when the input is requested, the output that is then generated must be
 in sync with the input.

 inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i** **`**seq**`** 
 **D**.**empty**)*, head i) in (tail i, r)



 I first had

 inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


 But that was too eager, since i syncs the input not with the output, but
 with the function that will generate the output.

 Okay, now I can sleep again :-)




 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before asking
 for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.comwrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with serial
 console controlled power strips, so I need to either use Expect (yuck) or do
 my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not sure.

 I would like to use a graphical tool to show the graph reduction step by
 step, to get a better understanding of the laziness  strictness. Does such
 a tool exist? I know people often say this is not usable because the amount
 of information is too much, but I used to be an assembly language 
 programmer
 so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 In an attempt to get a deeper understanding of several monads (State,
 ST, IO, ...) I skimmed over some of the research papers (but didn't
 understand all of it, I lack the required education) and decided to write 
 a
 little program myself without using any prefab monad instances that should
 mimic the following:
 main = do
   putStrLn Enter your name:
   x - getLine
   putStr Welcome 
   putStrLn x
   putStrLn Goodbye!

 But instead of using IO, I wanted to make my own pure monad that gets
 evaluated with interact, and does the same.

 However, I get the following output:

 Enter your name:
 Welcome ..

 So the Welcome is printed too soon.

 This is obvious since my monad is lazy, so I tried to put a seq at some
 strategic places to get the same behavior as IO. But I completely failed
 doing so, either the program doesn't print anything and asks input first, 
 or
 it still prints too much output.

 Of course I could just use ST, State, transformers, etc, but this is
 purely an exercise I'm doing.

 So, I could re-read all papers and look in detail at all the code, but
 maybe someone could help me out where to put the seq or what to do :-)

 The code is at http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316

 Oh btw, the usage of DList here might not be needed; intuitively it
 felt like the correct thing to do, but when it comes to Haskell, my
 intuition is usually wrong ;-)

 Thanks a lot,
 Peter Verswyvelen



 ___
 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] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Argh... I too have been up too late :-).  I edited THE WRONG FILE!  No
wonder your change didn't take effect!  :-/
Time for coffee I suppose.

On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.com wrote:

 This doesn't seem to be working for me interactively though on a Mac.  I
 still get Welcome before I've entered text.


 On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea is,
 that when the input is requested, the output that is then generated must be
 in sync with the input.

 inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i** 
 **`**seq**`** **D**.**empty**)*, head i) in (tail i, r)



 I first had

 inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


 But that was too eager, since i syncs the input not with the output, but
 with the function that will generate the output.

 Okay, now I can sleep again :-)




 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before asking
 for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.comwrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with
 serial console controlled power strips, so I need to either use Expect
 (yuck) or do my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not sure.

 I would like to use a graphical tool to show the graph reduction step
 by step, to get a better understanding of the laziness  strictness. Does
 such a tool exist? I know people often say this is not usable because the
 amount of information is too much, but I used to be an assembly language
 programmer so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 In an attempt to get a deeper understanding of several monads (State,
 ST, IO, ...) I skimmed over some of the research papers (but didn't
 understand all of it, I lack the required education) and decided to 
 write a
 little program myself without using any prefab monad instances that 
 should
 mimic the following:
 main = do
   putStrLn Enter your name:
   x - getLine
   putStr Welcome 
   putStrLn x
   putStrLn Goodbye!

 But instead of using IO, I wanted to make my own pure monad that gets
 evaluated with interact, and does the same.

 However, I get the following output:

 Enter your name:
 Welcome ..

 So the Welcome is printed too soon.

 This is obvious since my monad is lazy, so I tried to put a seq at
 some strategic places to get the same behavior as IO. But I completely
 failed doing so, either the program doesn't print anything and asks input
 first, or it still prints too much output.

 Of course I could just use ST, State, transformers, etc, but this is
 purely an exercise I'm doing.

 So, I could re-read all papers and look in detail at all the code, but
 maybe someone could help me out where to put the seq or what to do :-)

 The code is at http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316

 Oh btw, the usage of DList here might not be needed; intuitively it
 felt like the correct thing to do, but when it comes to Haskell, my
 intuition is usually wrong ;-)

 Thanks a lot,
 Peter Verswyvelen



 ___
 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] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
Not at all, use it for whatever you want to :-)
I'm writing this code because I'm preparing to write a bunch of tutorials on
FRP, and I first wanted to start with simple console based FRP, e.g. making
a little text adventure game, where the input/choices of the user might be
parsed ala parsec, using monadic style, applicative style, and arrows, and
then doing the same with FRP frameworks like Yampa, Elera, Reactive, etc...

After that I would start writing tutorials that use OpenGL, making some very
simple games, again with the above approaches, and ending with a conversion
of a very old game of mine (Zarathrusta written in assembler from 1991,
which was based on Thrust
http://www.bytecellar.com/archives/000106.phpfrom 1986, converted by
myself in C++ to PocketPC as
G-Podhttp://www.handango.com/catalog/ProductDetails.jsp?productId=16574platformId=30,
and so I would like to make a version in Haskell that runs on the iPhone :-)

This of course is a lot of work, and I would like to put this on the Haskell
wiki or a blog or something, so others can contribute and comment. I would
like to show real examples that explain the shortcomings of the FRP
approaches, because now this is still a bit blurry to me.



On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com wrote:

 This Monad you've created is quite excellent.  I was trying to do something
 like this about a year ago, to make the input and output handling of an
 interactive bowling score card work nicely.  I kept running into issues, and
 did not believe that seq was going to do the trick.  Nice work!
 This is a very useful monad I think, it could be called Prompter or
 something to that effect.

 Do you mind if I use it in some of my code?

 Dave


 On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 LOL. Maybe we should have that coffee together ;-) at least virtually!

 On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.comwrote:

 Argh... I too have been up too late :-).  I edited THE WRONG FILE!  No
 wonder your change didn't take effect!  :-/
 Time for coffee I suppose.


 On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.comwrote:

 This doesn't seem to be working for me interactively though on a Mac.  I
 still get Welcome before I've entered text.


 On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea is,
 that when the input is requested, the output that is then generated must 
 be
 in sync with the input.

 inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i** 
 **`**seq**`** **D**.**empty**)*, head i) in (tail i, r)



 I first had

 inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


 But that was too eager, since i syncs the input not with the output,
 but with the function that will generate the output.

 Okay, now I can sleep again :-)




 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before 
 asking
 for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.comwrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with
 serial console controlled power strips, so I need to either use Expect
 (yuck) or do my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen 
 bugf...@gmail.com wrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should
 be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not
 sure.

 I would like to use a graphical tool to show the graph reduction
 step by step, to get a better understanding of the laziness  
 strictness.
 Does such a tool exist? I know people often say this is not usable 
 because
 the amount of information is too much, but I used to be an assembly 
 language
 programmer so I still would like to give it a try :-)



 On Wed, Aug 19, 2009 at 1:07 PM, Peter Verswyvelen 
 bugf...@gmail.com wrote:

 In an attempt to get a deeper understanding of several monads
 (State, ST, IO, ...) I skimmed over some of the research papers (but 
 didn't
 understand all of it, I lack the required 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
Expect more bugs with this though :-) Just found out that looping does not
work, it hangs, e.g.

test = do  out Enter your first name:  fstName - inp  out Enter
your second name:  sndName - inp  out (Welcome ++fstName++
++sndName)  out Goodbye!*  **test*

Doesn't seem to work :-) Back to the drawing board.


On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Not at all, use it for whatever you want to :-)
 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like Yampa, Elera,
 Reactive, etc...

 After that I would start writing tutorials that use OpenGL, making some
 very simple games, again with the above approaches, and ending with a
 conversion of a very old game of mine (Zarathrusta written in assembler from
 1991, which was based on 
 Thrusthttp://www.bytecellar.com/archives/000106.phpfrom 1986, converted by 
 myself in C++ to PocketPC as
 G-Podhttp://www.handango.com/catalog/ProductDetails.jsp?productId=16574platformId=30,
 and so I would like to make a version in Haskell that runs on the iPhone :-)

 This of course is a lot of work, and I would like to put this on the
 Haskell wiki or a blog or something, so others can contribute and comment. I
 would like to show real examples that explain the shortcomings of the FRP
 approaches, because now this is still a bit blurry to me.



 On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com wrote:

 This Monad you've created is quite excellent.  I was trying to do
 something like this about a year ago, to make the input and output handling
 of an interactive bowling score card work nicely.  I kept running into
 issues, and did not believe that seq was going to do the trick.  Nice work!
 This is a very useful monad I think, it could be called Prompter or
 something to that effect.

 Do you mind if I use it in some of my code?

 Dave


 On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 LOL. Maybe we should have that coffee together ;-) at least virtually!

 On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.comwrote:

 Argh... I too have been up too late :-).  I edited THE WRONG FILE!  No
 wonder your change didn't take effect!  :-/
 Time for coffee I suppose.


 On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.comwrote:

 This doesn't seem to be working for me interactively though on a Mac.
  I still get Welcome before I've entered text.


 On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea
 is, that when the input is requested, the output that is then generated 
 must
 be in sync with the input.

 inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i** 
 **`**seq**`** **D**.**empty**)*, head i) in (tail i, r)



 I first had

 inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


 But that was too eager, since i syncs the input not with the output,
 but with the function that will generate the output.

 Okay, now I can sleep again :-)




 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen bugf...@gmail.com
  wrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before 
 asking
 for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach 
 leim...@gmail.comwrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with
 serial console controlled power strips, so I need to either use Expect
 (yuck) or do my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen 
 bugf...@gmail.com wrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should
 be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix systems.

 I guess the way I'm concatenating the strings is not correct, not
 sure.

 I would like to use a graphical tool to show the graph reduction
 step by step, to get a better understanding of the laziness  
 strictness.
 Does such a tool exist? I know people often say this is not usable 
 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Have you spoken to Conal Elliott about this stuff?  He might be interested.
 He was looking for doing this sort of thing on iPhones for a bit.
Also, I was wondering if you thought this Monad might be useful as a way to
automate tasks in an Expect like fashion.  I've been struggling with a good
way to do this stuff in Haskell for a while.

One challenge is that input is not always line oriented, for example the
Password:  token that we get when we use ssh interactively.  My first
thought was to try to avoid seq, and use words and unwords.

However, I'm thinking now that I'm going to need new Monad Operations like
inp, but for different token sizes and possibly different matches of
characters.

Dave

On Wed, Aug 19, 2009 at 8:55 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Not at all, use it for whatever you want to :-)
 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like Yampa, Elera,
 Reactive, etc...

 After that I would start writing tutorials that use OpenGL, making some
 very simple games, again with the above approaches, and ending with a
 conversion of a very old game of mine (Zarathrusta written in assembler from
 1991, which was based on 
 Thrusthttp://www.bytecellar.com/archives/000106.phpfrom 1986, converted by 
 myself in C++ to PocketPC as
 G-Podhttp://www.handango.com/catalog/ProductDetails.jsp?productId=16574platformId=30,
 and so I would like to make a version in Haskell that runs on the iPhone :-)

 This of course is a lot of work, and I would like to put this on the
 Haskell wiki or a blog or something, so others can contribute and comment. I
 would like to show real examples that explain the shortcomings of the FRP
 approaches, because now this is still a bit blurry to me.



 On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com wrote:

 This Monad you've created is quite excellent.  I was trying to do
 something like this about a year ago, to make the input and output handling
 of an interactive bowling score card work nicely.  I kept running into
 issues, and did not believe that seq was going to do the trick.  Nice work!
 This is a very useful monad I think, it could be called Prompter or
 something to that effect.

 Do you mind if I use it in some of my code?

 Dave


 On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 LOL. Maybe we should have that coffee together ;-) at least virtually!

 On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.comwrote:

 Argh... I too have been up too late :-).  I edited THE WRONG FILE!  No
 wonder your change didn't take effect!  :-/
 Time for coffee I suppose.


 On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.comwrote:

 This doesn't seem to be working for me interactively though on a Mac.
  I still get Welcome before I've entered text.


 On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen 
 bugf...@gmail.comwrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea
 is, that when the input is requested, the output that is then generated 
 must
 be in sync with the input.

 inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i** 
 **`**seq**`** **D**.**empty**)*, head i) in (tail i, r)



 I first had

 inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


 But that was too eager, since i syncs the input not with the output,
 but with the function that will generate the output.

 Okay, now I can sleep again :-)




 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen bugf...@gmail.com
  wrote:

 Thanks, but that doesn't really matter in my example, my code is just
 buggy, and I'm not sure why. For example if I change my test function so
 that it outputs lines only, then it still prints Welcome first before 
 asking
 for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach 
 leim...@gmail.comwrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with
 serial console controlled power strips, so I need to either use Expect
 (yuck) or do my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen 
 bugf...@gmail.com wrote:

 Apparently this particular example happens to work on Mac and Linux
 because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should
 be:

 main = do  hSetBuffering stdout 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Yet this does work
interact $ run test9

test9 = replicateM 9 test

Will run test 9 times.  I suppose if one constructed an infinite list you
could loop as you wanted to.

Yet, that might not be what you want.

Dave

On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Expect more bugs with this though :-) Just found out that looping does not
 work, it hangs, e.g.

 test = do  out Enter your first name:  fstName - inp  out Enter your 
 second name:  sndName - inp  out (Welcome ++fstName++ ++sndName)  out 
 Goodbye!*  **test*

 Doesn't seem to work :-) Back to the drawing board.


 On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Not at all, use it for whatever you want to :-)
 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like Yampa, Elera,
 Reactive, etc...

 After that I would start writing tutorials that use OpenGL, making some
 very simple games, again with the above approaches, and ending with a
 conversion of a very old game of mine (Zarathrusta written in assembler from
 1991, which was based on 
 Thrusthttp://www.bytecellar.com/archives/000106.phpfrom 1986, converted by 
 myself in C++ to PocketPC as
 G-Podhttp://www.handango.com/catalog/ProductDetails.jsp?productId=16574platformId=30,
 and so I would like to make a version in Haskell that runs on the iPhone :-)

 This of course is a lot of work, and I would like to put this on the
 Haskell wiki or a blog or something, so others can contribute and comment. I
 would like to show real examples that explain the shortcomings of the FRP
 approaches, because now this is still a bit blurry to me.



 On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.comwrote:

 This Monad you've created is quite excellent.  I was trying to do
 something like this about a year ago, to make the input and output handling
 of an interactive bowling score card work nicely.  I kept running into
 issues, and did not believe that seq was going to do the trick.  Nice work!
 This is a very useful monad I think, it could be called Prompter or
 something to that effect.

 Do you mind if I use it in some of my code?

 Dave


 On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 LOL. Maybe we should have that coffee together ;-) at least virtually!

 On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.comwrote:

 Argh... I too have been up too late :-).  I edited THE WRONG FILE!  No
 wonder your change didn't take effect!  :-/
 Time for coffee I suppose.


 On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.comwrote:

 This doesn't seem to be working for me interactively though on a Mac.
  I still get Welcome before I've entered text.


 On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen bugf...@gmail.com
  wrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330The idea
 is, that when the input is requested, the output that is then generated 
 must
 be in sync with the input.

 inp = S $ \s i - let r = (*s** **`**D**.**append**`** **(**i** 
 **`**seq**`** **D**.**empty**)*, head i) in (tail i, r)



 I first had

 inp = S $ \s i - let r = (i `seq` *s*, head i) in (tail i, r)


 But that was too eager, since i syncs the input not with the output,
 but with the function that will generate the output.

 Okay, now I can sleep again :-)




 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen 
 bugf...@gmail.com wrote:

 Thanks, but that doesn't really matter in my example, my code is
 just buggy, and I'm not sure why. For example if I change my test 
 function
 so that it outputs lines only, then it still prints Welcome first 
 before
 asking for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328

 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach 
 leim...@gmail.comwrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like

 unlines . lines

 may help too.  In fact I just wrote a blog post about this.

 http://leimy9.blogspot.com

 I'm trying to write some interactive code to automate working with
 serial console controlled power strips, so I need to either use Expect
 (yuck) or do my own thing.

 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen 
 bugf...@gmail.com wrote:

 Apparently this particular example happens to work on Mac and
 Linux because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should
 be:

 main = do  hSetBuffering stdout NoBuffering  hSetBuffering stdin 
 NoBuffering  test

 Now I think it should also be *incorrect* on Unix 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread Ryan Ingram
I posted a reply to your paste with a stricter version of S and some cleanup.

Untested, though I believe it should work without seq.

case provides all the strictness you need, I think!

  -- ryan

On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com wrote:
 Expect more bugs with this though :-) Just found out that looping does not
 work, it hangs, e.g.

 test = do
   out Enter your first name:
   fstName - inp
   out Enter your second name:
   sndName - inp
   out (Welcome ++fstName++ ++sndName)
   out Goodbye!
   test

 Doesn't seem to work :-) Back to the drawing board.

 On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.com
 wrote:

 Not at all, use it for whatever you want to :-)
 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like Yampa, Elera,
 Reactive, etc...
 After that I would start writing tutorials that use OpenGL, making some
 very simple games, again with the above approaches, and ending with a
 conversion of a very old game of mine (Zarathrusta written in assembler from
 1991, which was based on Thrust from 1986, converted by myself in C++ to
 PocketPC as G-Pod, and so I would like to make a version in Haskell that
 runs on the iPhone :-)
 This of course is a lot of work, and I would like to put this on the
 Haskell wiki or a blog or something, so others can contribute and comment. I
 would like to show real examples that explain the shortcomings of the FRP
 approaches, because now this is still a bit blurry to me.

 On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com wrote:

 This Monad you've created is quite excellent.  I was trying to do
 something like this about a year ago, to make the input and output handling
 of an interactive bowling score card work nicely.  I kept running into
 issues, and did not believe that seq was going to do the trick.  Nice work!
 This is a very useful monad I think, it could be called Prompter or
 something to that effect.
 Do you mind if I use it in some of my code?
 Dave

 On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.com
 wrote:

 LOL. Maybe we should have that coffee together ;-) at least virtually!
 On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.com
 wrote:

 Argh... I too have been up too late :-).  I edited THE WRONG FILE!  No
 wonder your change didn't take effect!  :-/
 Time for coffee I suppose.

 On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.com
 wrote:

 This doesn't seem to be working for me interactively though on a Mac.
  I still get Welcome before I've entered text.

 On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen bugf...@gmail.com
 wrote:

 I fixed it myself but it's really tricky :-)
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330
 The idea is, that when the input is requested, the output that is
 then generated must be in sync with the input.

 inp = S $ \s i - let r = (s `D.append` (i `seq` D.empty), head i) in
 (tail i, r)


 I first had

 inp = S $ \s i - let r = (i `seq` s, head i) in (tail i, r)

 But that was too eager, since i syncs the input not with the output,
 but with the function that will generate the output.







 Okay, now I can sleep again :-)










 On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen
 bugf...@gmail.com wrote:

 Thanks, but that doesn't really matter in my example, my code is
 just buggy, and I'm not sure why. For example if I change my test 
 function
 so that it outputs lines only, then it still prints Welcome first 
 before
 asking for input.
 See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328
 On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach leim...@gmail.com
 wrote:

 Try LineBuffering.
 I do linewise stuff with interact a lot.  You'll find stuff like
 unlines . lines
 may help too.  In fact I just wrote a blog post about this.
 http://leimy9.blogspot.com
 I'm trying to write some interactive code to automate working with
 serial console controlled power strips, so I need to either use Expect
 (yuck) or do my own thing.
 Dave

 On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen
 bugf...@gmail.com wrote:

 Apparently this particular example happens to work on Mac and
 Linux because of different buffering (thanks Martijn for the help!)
 To make sure we have no buffering at all, the main function should
 be:

 main = do
   hSetBuffering stdout NoBuffering
   hSetBuffering stdin NoBuffering
   test

 Now I think it should also be incorrect on Unix systems.
 I guess the way I'm concatenating the strings is not correct, not
 sure.
 I would like to use a graphical tool to show the graph reduction
 step by step, to get a better understanding of the laziness  
 strictness.
 Does such a 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Doesn't seem to compile.
I nearly never use case statements in my code, so I'm not really sure what's
going on.

neat2.hs:14:39: parse error on input `='

Dave

On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.com wrote:

 I posted a reply to your paste with a stricter version of S and some
 cleanup.

 Untested, though I believe it should work without seq.

 case provides all the strictness you need, I think!

  -- ryan

 On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  Expect more bugs with this though :-) Just found out that looping does
 not
  work, it hangs, e.g.
 
  test = do
out Enter your first name:
fstName - inp
out Enter your second name:
sndName - inp
out (Welcome ++fstName++ ++sndName)
out Goodbye!
test
 
  Doesn't seem to work :-) Back to the drawing board.
 
  On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.com
  wrote:
 
  Not at all, use it for whatever you want to :-)
  I'm writing this code because I'm preparing to write a bunch of
 tutorials
  on FRP, and I first wanted to start with simple console based FRP, e.g.
  making a little text adventure game, where the input/choices of the user
  might be parsed ala parsec, using monadic style, applicative style, and
  arrows, and then doing the same with FRP frameworks like Yampa, Elera,
  Reactive, etc...
  After that I would start writing tutorials that use OpenGL, making some
  very simple games, again with the above approaches, and ending with a
  conversion of a very old game of mine (Zarathrusta written in assembler
 from
  1991, which was based on Thrust from 1986, converted by myself in C++ to
  PocketPC as G-Pod, and so I would like to make a version in Haskell that
  runs on the iPhone :-)
  This of course is a lot of work, and I would like to put this on the
  Haskell wiki or a blog or something, so others can contribute and
 comment. I
  would like to show real examples that explain the shortcomings of the
 FRP
  approaches, because now this is still a bit blurry to me.
 
  On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com
 wrote:
 
  This Monad you've created is quite excellent.  I was trying to do
  something like this about a year ago, to make the input and output
 handling
  of an interactive bowling score card work nicely.  I kept running into
  issues, and did not believe that seq was going to do the trick.  Nice
 work!
  This is a very useful monad I think, it could be called Prompter or
  something to that effect.
  Do you mind if I use it in some of my code?
  Dave
 
  On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.com
  wrote:
 
  LOL. Maybe we should have that coffee together ;-) at least virtually!
  On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.com
  wrote:
 
  Argh... I too have been up too late :-).  I edited THE WRONG FILE!
  No
  wonder your change didn't take effect!  :-/
  Time for coffee I suppose.
 
  On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.com
  wrote:
 
  This doesn't seem to be working for me interactively though on a
 Mac.
   I still get Welcome before I've entered text.
 
  On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen 
 bugf...@gmail.com
  wrote:
 
  I fixed it myself but it's really tricky :-)
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330
  The idea is, that when the input is requested, the output that is
  then generated must be in sync with the input.
 
  inp = S $ \s i - let r = (s `D.append` (i `seq` D.empty), head i)
 in
  (tail i, r)
 
 
  I first had
 
  inp = S $ \s i - let r = (i `seq` s, head i) in (tail i, r)
 
  But that was too eager, since i syncs the input not with the
 output,
  but with the function that will generate the output.
 
 
 
 
 
 
 
  Okay, now I can sleep again :-)
 
 
 
 
 
 
 
 
 
 
  On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen
  bugf...@gmail.com wrote:
 
  Thanks, but that doesn't really matter in my example, my code is
  just buggy, and I'm not sure why. For example if I change my test
 function
  so that it outputs lines only, then it still prints Welcome first
 before
  asking for input.
  See e.g. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328
  On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach 
 leim...@gmail.com
  wrote:
 
  Try LineBuffering.
  I do linewise stuff with interact a lot.  You'll find stuff like
  unlines . lines
  may help too.  In fact I just wrote a blog post about this.
  http://leimy9.blogspot.com
  I'm trying to write some interactive code to automate working
 with
  serial console controlled power strips, so I need to either use
 Expect
  (yuck) or do my own thing.
  Dave
 
  On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen
  bugf...@gmail.com wrote:
 
  Apparently this particular example happens to work on Mac and
  Linux because of different buffering (thanks Martijn for the
 help!)
  To make sure we have no buffering at all, the main function
 should

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
I've corrected it.  It still doesn't suffer looping.  :-)

On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.com wrote:

 Doesn't seem to compile.
 I nearly never use case statements in my code, so I'm not really sure
 what's going on.

 neat2.hs:14:39: parse error on input `='

 Dave

 On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.comwrote:

 I posted a reply to your paste with a stricter version of S and some
 cleanup.

 Untested, though I believe it should work without seq.

 case provides all the strictness you need, I think!

  -- ryan

 On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  Expect more bugs with this though :-) Just found out that looping does
 not
  work, it hangs, e.g.
 
  test = do
out Enter your first name:
fstName - inp
out Enter your second name:
sndName - inp
out (Welcome ++fstName++ ++sndName)
out Goodbye!
test
 
  Doesn't seem to work :-) Back to the drawing board.
 
  On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.com
  wrote:
 
  Not at all, use it for whatever you want to :-)
  I'm writing this code because I'm preparing to write a bunch of
 tutorials
  on FRP, and I first wanted to start with simple console based FRP, e.g.
  making a little text adventure game, where the input/choices of the
 user
  might be parsed ala parsec, using monadic style, applicative style, and
  arrows, and then doing the same with FRP frameworks like Yampa, Elera,
  Reactive, etc...
  After that I would start writing tutorials that use OpenGL, making some
  very simple games, again with the above approaches, and ending with a
  conversion of a very old game of mine (Zarathrusta written in assembler
 from
  1991, which was based on Thrust from 1986, converted by myself in C++
 to
  PocketPC as G-Pod, and so I would like to make a version in Haskell
 that
  runs on the iPhone :-)
  This of course is a lot of work, and I would like to put this on the
  Haskell wiki or a blog or something, so others can contribute and
 comment. I
  would like to show real examples that explain the shortcomings of the
 FRP
  approaches, because now this is still a bit blurry to me.
 
  On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com
 wrote:
 
  This Monad you've created is quite excellent.  I was trying to do
  something like this about a year ago, to make the input and output
 handling
  of an interactive bowling score card work nicely.  I kept running into
  issues, and did not believe that seq was going to do the trick.  Nice
 work!
  This is a very useful monad I think, it could be called Prompter or
  something to that effect.
  Do you mind if I use it in some of my code?
  Dave
 
  On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen bugf...@gmail.com
 
  wrote:
 
  LOL. Maybe we should have that coffee together ;-) at least
 virtually!
  On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.com
  wrote:
 
  Argh... I too have been up too late :-).  I edited THE WRONG FILE!
  No
  wonder your change didn't take effect!  :-/
  Time for coffee I suppose.
 
  On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.com
  wrote:
 
  This doesn't seem to be working for me interactively though on a
 Mac.
   I still get Welcome before I've entered text.
 
  On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen 
 bugf...@gmail.com
  wrote:
 
  I fixed it myself but it's really tricky :-)
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330
  The idea is, that when the input is requested, the output that is
  then generated must be in sync with the input.
 
  inp = S $ \s i - let r = (s `D.append` (i `seq` D.empty), head i)
 in
  (tail i, r)
 
 
  I first had
 
  inp = S $ \s i - let r = (i `seq` s, head i) in (tail i, r)
 
  But that was too eager, since i syncs the input not with the
 output,
  but with the function that will generate the output.
 
 
 
 
 
 
 
  Okay, now I can sleep again :-)
 
 
 
 
 
 
 
 
 
 
  On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen
  bugf...@gmail.com wrote:
 
  Thanks, but that doesn't really matter in my example, my code is
  just buggy, and I'm not sure why. For example if I change my test
 function
  so that it outputs lines only, then it still prints Welcome first
 before
  asking for input.
  See e.g.
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328
  On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach 
 leim...@gmail.com
  wrote:
 
  Try LineBuffering.
  I do linewise stuff with interact a lot.  You'll find stuff like
  unlines . lines
  may help too.  In fact I just wrote a blog post about this.
  http://leimy9.blogspot.com
  I'm trying to write some interactive code to automate working
 with
  serial console controlled power strips, so I need to either use
 Expect
  (yuck) or do my own thing.
  Dave
 
  On Wed, Aug 19, 2009 at 7:35 AM, Peter Verswyvelen
  bugf...@gmail.com wrote:
 
  Apparently this particular example happens to work on 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
The cleaned up code didn't seem to work for me, it printed everything before
asking input again.

But I added a patch that looks like it supports looping, but I don't
understand exactly what is going on :-)
I added the delay function which makes appending to the output less
strict.

Note that in this version I add a delay to each right argument of =, but
one could also do it manually

On Wed, Aug 19, 2009 at 7:37 PM, David Leimbach leim...@gmail.com wrote:

 I've corrected it.  It still doesn't suffer looping.  :-)


 On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.comwrote:

 Doesn't seem to compile.
 I nearly never use case statements in my code, so I'm not really sure
 what's going on.

 neat2.hs:14:39: parse error on input `='

 Dave

 On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.comwrote:

 I posted a reply to your paste with a stricter version of S and some
 cleanup.

 Untested, though I believe it should work without seq.

 case provides all the strictness you need, I think!

  -- ryan

 On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  Expect more bugs with this though :-) Just found out that looping does
 not
  work, it hangs, e.g.
 
  test = do
out Enter your first name:
fstName - inp
out Enter your second name:
sndName - inp
out (Welcome ++fstName++ ++sndName)
out Goodbye!
test
 
  Doesn't seem to work :-) Back to the drawing board.
 
  On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.com
  wrote:
 
  Not at all, use it for whatever you want to :-)
  I'm writing this code because I'm preparing to write a bunch of
 tutorials
  on FRP, and I first wanted to start with simple console based FRP,
 e.g.
  making a little text adventure game, where the input/choices of the
 user
  might be parsed ala parsec, using monadic style, applicative style,
 and
  arrows, and then doing the same with FRP frameworks like Yampa, Elera,
  Reactive, etc...
  After that I would start writing tutorials that use OpenGL, making
 some
  very simple games, again with the above approaches, and ending with a
  conversion of a very old game of mine (Zarathrusta written in
 assembler from
  1991, which was based on Thrust from 1986, converted by myself in C++
 to
  PocketPC as G-Pod, and so I would like to make a version in Haskell
 that
  runs on the iPhone :-)
  This of course is a lot of work, and I would like to put this on the
  Haskell wiki or a blog or something, so others can contribute and
 comment. I
  would like to show real examples that explain the shortcomings of the
 FRP
  approaches, because now this is still a bit blurry to me.
 
  On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com
 wrote:
 
  This Monad you've created is quite excellent.  I was trying to do
  something like this about a year ago, to make the input and output
 handling
  of an interactive bowling score card work nicely.  I kept running
 into
  issues, and did not believe that seq was going to do the trick.  Nice
 work!
  This is a very useful monad I think, it could be called Prompter or
  something to that effect.
  Do you mind if I use it in some of my code?
  Dave
 
  On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen 
 bugf...@gmail.com
  wrote:
 
  LOL. Maybe we should have that coffee together ;-) at least
 virtually!
  On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.com
  wrote:
 
  Argh... I too have been up too late :-).  I edited THE WRONG FILE!
  No
  wonder your change didn't take effect!  :-/
  Time for coffee I suppose.
 
  On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach leim...@gmail.com
 
  wrote:
 
  This doesn't seem to be working for me interactively though on a
 Mac.
   I still get Welcome before I've entered text.
 
  On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen 
 bugf...@gmail.com
  wrote:
 
  I fixed it myself but it's really tricky :-)
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330
  The idea is, that when the input is requested, the output that is
  then generated must be in sync with the input.
 
  inp = S $ \s i - let r = (s `D.append` (i `seq` D.empty), head
 i) in
  (tail i, r)
 
 
  I first had
 
  inp = S $ \s i - let r = (i `seq` s, head i) in (tail i, r)
 
  But that was too eager, since i syncs the input not with the
 output,
  but with the function that will generate the output.
 
 
 
 
 
 
 
  Okay, now I can sleep again :-)
 
 
 
 
 
 
 
 
 
 
  On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen
  bugf...@gmail.com wrote:
 
  Thanks, but that doesn't really matter in my example, my code is
  just buggy, and I'm not sure why. For example if I change my
 test function
  so that it outputs lines only, then it still prints Welcome
 first before
  asking for input.
  See e.g.
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8328
  On Wed, Aug 19, 2009 at 5:00 PM, David Leimbach 
 leim...@gmail.com
  wrote:
 
  Try LineBuffering.
  I do linewise stuff with 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread Ryan Ingram
Added a new version (tested, works with infinite loops, no early output, etc.)

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8343

I'll put up a short write-up after lunch.

  -- ryan

On Wed, Aug 19, 2009 at 11:28 AM, Peter Verswyvelenbugf...@gmail.com wrote:
 The cleaned up code didn't seem to work for me, it printed everything before
 asking input again.
 But I added a patch that looks like it supports looping, but I don't
 understand exactly what is going on :-)
 I added the delay function which makes appending to the output less
 strict.
 Note that in this version I add a delay to each right argument of =, but
 one could also do it manually
 On Wed, Aug 19, 2009 at 7:37 PM, David Leimbach leim...@gmail.com wrote:

 I've corrected it.  It still doesn't suffer looping.  :-)

 On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.com
 wrote:

 Doesn't seem to compile.
 I nearly never use case statements in my code, so I'm not really sure
 what's going on.
 neat2.hs:14:39: parse error on input `='
 Dave
 On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.com
 wrote:

 I posted a reply to your paste with a stricter version of S and some
 cleanup.

 Untested, though I believe it should work without seq.

 case provides all the strictness you need, I think!

  -- ryan

 On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  Expect more bugs with this though :-) Just found out that looping does
  not
  work, it hangs, e.g.
 
  test = do
    out Enter your first name:
    fstName - inp
    out Enter your second name:
    sndName - inp
    out (Welcome ++fstName++ ++sndName)
    out Goodbye!
    test
 
  Doesn't seem to work :-) Back to the drawing board.
 
  On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen bugf...@gmail.com
  wrote:
 
  Not at all, use it for whatever you want to :-)
  I'm writing this code because I'm preparing to write a bunch of
  tutorials
  on FRP, and I first wanted to start with simple console based FRP,
  e.g.
  making a little text adventure game, where the input/choices of the
  user
  might be parsed ala parsec, using monadic style, applicative style,
  and
  arrows, and then doing the same with FRP frameworks like Yampa,
  Elera,
  Reactive, etc...
  After that I would start writing tutorials that use OpenGL, making
  some
  very simple games, again with the above approaches, and ending with a
  conversion of a very old game of mine (Zarathrusta written in
  assembler from
  1991, which was based on Thrust from 1986, converted by myself in C++
  to
  PocketPC as G-Pod, and so I would like to make a version in Haskell
  that
  runs on the iPhone :-)
  This of course is a lot of work, and I would like to put this on the
  Haskell wiki or a blog or something, so others can contribute and
  comment. I
  would like to show real examples that explain the shortcomings of the
  FRP
  approaches, because now this is still a bit blurry to me.
 
  On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com
  wrote:
 
  This Monad you've created is quite excellent.  I was trying to do
  something like this about a year ago, to make the input and output
  handling
  of an interactive bowling score card work nicely.  I kept running
  into
  issues, and did not believe that seq was going to do the trick.
   Nice work!
  This is a very useful monad I think, it could be called Prompter
  or
  something to that effect.
  Do you mind if I use it in some of my code?
  Dave
 
  On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen
  bugf...@gmail.com
  wrote:
 
  LOL. Maybe we should have that coffee together ;-) at least
  virtually!
  On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach leim...@gmail.com
  wrote:
 
  Argh... I too have been up too late :-).  I edited THE WRONG FILE!
   No
  wonder your change didn't take effect!  :-/
  Time for coffee I suppose.
 
  On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach
  leim...@gmail.com
  wrote:
 
  This doesn't seem to be working for me interactively though on a
  Mac.
   I still get Welcome before I've entered text.
 
  On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen
  bugf...@gmail.com
  wrote:
 
  I fixed it myself but it's really tricky :-)
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330
  The idea is, that when the input is requested, the output that
  is
  then generated must be in sync with the input.
 
  inp = S $ \s i - let r = (s `D.append` (i `seq` D.empty), head
  i) in
  (tail i, r)
 
 
  I first had
 
  inp = S $ \s i - let r = (i `seq` s, head i) in (tail i, r)
 
  But that was too eager, since i syncs the input not with the
  output,
  but with the function that will generate the output.
 
 
 
 
 
 
 
  Okay, now I can sleep again :-)
 
 
 
 
 
 
 
 
 
 
  On Wed, Aug 19, 2009 at 5:12 PM, Peter Verswyvelen
  bugf...@gmail.com wrote:
 
  Thanks, but that doesn't really matter in my example, my code
  is
  just buggy, and I'm not sure why. For example if I change my
  test 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Very cool!
I am still wondering what the significance of the DList is with this though,
or why it was needed to begin with.

Dave

On Wed, Aug 19, 2009 at 12:28 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 Added a new version (tested, works with infinite loops, no early output,
 etc.)

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8343

 I'll put up a short write-up after lunch.

  -- ryan

 On Wed, Aug 19, 2009 at 11:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  The cleaned up code didn't seem to work for me, it printed everything
 before
  asking input again.
  But I added a patch that looks like it supports looping, but I don't
  understand exactly what is going on :-)
  I added the delay function which makes appending to the output less
  strict.
  Note that in this version I add a delay to each right argument of =,
 but
  one could also do it manually
  On Wed, Aug 19, 2009 at 7:37 PM, David Leimbach leim...@gmail.com
 wrote:
 
  I've corrected it.  It still doesn't suffer looping.  :-)
 
  On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.com
  wrote:
 
  Doesn't seem to compile.
  I nearly never use case statements in my code, so I'm not really sure
  what's going on.
  neat2.hs:14:39: parse error on input `='
  Dave
  On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.com
  wrote:
 
  I posted a reply to your paste with a stricter version of S and some
  cleanup.
 
  Untested, though I believe it should work without seq.
 
  case provides all the strictness you need, I think!
 
   -- ryan
 
  On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com
  wrote:
   Expect more bugs with this though :-) Just found out that looping
 does
   not
   work, it hangs, e.g.
  
   test = do
 out Enter your first name:
 fstName - inp
 out Enter your second name:
 sndName - inp
 out (Welcome ++fstName++ ++sndName)
 out Goodbye!
 test
  
   Doesn't seem to work :-) Back to the drawing board.
  
   On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen 
 bugf...@gmail.com
   wrote:
  
   Not at all, use it for whatever you want to :-)
   I'm writing this code because I'm preparing to write a bunch of
   tutorials
   on FRP, and I first wanted to start with simple console based FRP,
   e.g.
   making a little text adventure game, where the input/choices of the
   user
   might be parsed ala parsec, using monadic style, applicative style,
   and
   arrows, and then doing the same with FRP frameworks like Yampa,
   Elera,
   Reactive, etc...
   After that I would start writing tutorials that use OpenGL, making
   some
   very simple games, again with the above approaches, and ending with
 a
   conversion of a very old game of mine (Zarathrusta written in
   assembler from
   1991, which was based on Thrust from 1986, converted by myself in
 C++
   to
   PocketPC as G-Pod, and so I would like to make a version in Haskell
   that
   runs on the iPhone :-)
   This of course is a lot of work, and I would like to put this on
 the
   Haskell wiki or a blog or something, so others can contribute and
   comment. I
   would like to show real examples that explain the shortcomings of
 the
   FRP
   approaches, because now this is still a bit blurry to me.
  
   On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach leim...@gmail.com
 
   wrote:
  
   This Monad you've created is quite excellent.  I was trying to do
   something like this about a year ago, to make the input and output
   handling
   of an interactive bowling score card work nicely.  I kept running
   into
   issues, and did not believe that seq was going to do the trick.
Nice work!
   This is a very useful monad I think, it could be called Prompter
   or
   something to that effect.
   Do you mind if I use it in some of my code?
   Dave
  
   On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen
   bugf...@gmail.com
   wrote:
  
   LOL. Maybe we should have that coffee together ;-) at least
   virtually!
   On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach 
 leim...@gmail.com
   wrote:
  
   Argh... I too have been up too late :-).  I edited THE WRONG
 FILE!
No
   wonder your change didn't take effect!  :-/
   Time for coffee I suppose.
  
   On Wed, Aug 19, 2009 at 8:38 AM, David Leimbach
   leim...@gmail.com
   wrote:
  
   This doesn't seem to be working for me interactively though on
 a
   Mac.
I still get Welcome before I've entered text.
  
   On Wed, Aug 19, 2009 at 8:25 AM, Peter Verswyvelen
   bugf...@gmail.com
   wrote:
  
   I fixed it myself but it's really tricky :-)
   http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8330
   The idea is, that when the input is requested, the output that
   is
   then generated must be in sync with the input.
  
   inp = S $ \s i - let r = (s `D.append` (i `seq` D.empty),
 head
   i) in
   (tail i, r)
  
  
   I first had
  
   inp = S $ \s i - let r = (i `seq` s, head i) in (tail i, r)
  
   But that was too eager, since i syncs the input 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
Wow, very nice cleanup! That's really a good way for me to learn, thanks.
Well, my intuition told me that strings and ++ wouldn't work, since what we
want is an infinite list of output strings, and using ++ would result in
(((s1++s2)++s3)++s4)++s5... which is highly inefficient and I think it would
keep the complete output text in memory. Using difference lists results in
right associative concatenation of s1++(s2++(s3++(s4++... which is efficient
and can be garbage collected nicely. At least that's what I guess. I really
would like to get a deeper understanding of all this but that will take lots
of time and study, but if I'm lucky I still have 20 to 40 years to go, so I
won't be bored :-)




On Wed, Aug 19, 2009 at 9:46 PM, David Leimbach leim...@gmail.com wrote:

 Very cool!
 I am still wondering what the significance of the DList is with this
 though, or why it was needed to begin with.

 Dave


 On Wed, Aug 19, 2009 at 12:28 PM, Ryan Ingram ryani.s...@gmail.comwrote:

 Added a new version (tested, works with infinite loops, no early output,
 etc.)

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8343

 I'll put up a short write-up after lunch.

  -- ryan

 On Wed, Aug 19, 2009 at 11:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  The cleaned up code didn't seem to work for me, it printed everything
 before
  asking input again.
  But I added a patch that looks like it supports looping, but I don't
  understand exactly what is going on :-)
  I added the delay function which makes appending to the output less
  strict.
  Note that in this version I add a delay to each right argument of =,
 but
  one could also do it manually
  On Wed, Aug 19, 2009 at 7:37 PM, David Leimbach leim...@gmail.com
 wrote:
 
  I've corrected it.  It still doesn't suffer looping.  :-)
 
  On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.com
  wrote:
 
  Doesn't seem to compile.
  I nearly never use case statements in my code, so I'm not really sure
  what's going on.
  neat2.hs:14:39: parse error on input `='
  Dave
  On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.com
  wrote:
 
  I posted a reply to your paste with a stricter version of S and some
  cleanup.
 
  Untested, though I believe it should work without seq.
 
  case provides all the strictness you need, I think!
 
   -- ryan
 
  On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelenbugf...@gmail.com
 
  wrote:
   Expect more bugs with this though :-) Just found out that looping
 does
   not
   work, it hangs, e.g.
  
   test = do
 out Enter your first name:
 fstName - inp
 out Enter your second name:
 sndName - inp
 out (Welcome ++fstName++ ++sndName)
 out Goodbye!
 test
  
   Doesn't seem to work :-) Back to the drawing board.
  
   On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen 
 bugf...@gmail.com
   wrote:
  
   Not at all, use it for whatever you want to :-)
   I'm writing this code because I'm preparing to write a bunch of
   tutorials
   on FRP, and I first wanted to start with simple console based FRP,
   e.g.
   making a little text adventure game, where the input/choices of
 the
   user
   might be parsed ala parsec, using monadic style, applicative
 style,
   and
   arrows, and then doing the same with FRP frameworks like Yampa,
   Elera,
   Reactive, etc...
   After that I would start writing tutorials that use OpenGL, making
   some
   very simple games, again with the above approaches, and ending
 with a
   conversion of a very old game of mine (Zarathrusta written in
   assembler from
   1991, which was based on Thrust from 1986, converted by myself in
 C++
   to
   PocketPC as G-Pod, and so I would like to make a version in
 Haskell
   that
   runs on the iPhone :-)
   This of course is a lot of work, and I would like to put this on
 the
   Haskell wiki or a blog or something, so others can contribute and
   comment. I
   would like to show real examples that explain the shortcomings of
 the
   FRP
   approaches, because now this is still a bit blurry to me.
  
   On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach 
 leim...@gmail.com
   wrote:
  
   This Monad you've created is quite excellent.  I was trying to do
   something like this about a year ago, to make the input and
 output
   handling
   of an interactive bowling score card work nicely.  I kept running
   into
   issues, and did not believe that seq was going to do the trick.
Nice work!
   This is a very useful monad I think, it could be called
 Prompter
   or
   something to that effect.
   Do you mind if I use it in some of my code?
   Dave
  
   On Wed, Aug 19, 2009 at 8:42 AM, Peter Verswyvelen
   bugf...@gmail.com
   wrote:
  
   LOL. Maybe we should have that coffee together ;-) at least
   virtually!
   On Wed, Aug 19, 2009 at 5:39 PM, David Leimbach 
 leim...@gmail.com
   wrote:
  
   Argh... I too have been up too late :-).  I edited THE WRONG
 FILE!
No
   wonder your change didn't take effect!  :-/
   Time for 

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread David Leimbach
Hmmm very interesting thinking on this.  Perhaps ByteStrings would be a good
way to go for efficiency of composition.
I'd love to see some profiling of all of this as part of the lesson at some
point.  (Perhaps with vacuum visualization?)

This thread has tackled 3 major tricky issue areas with Haskell so far:

1. Lazy IO and seq
2. Roll-your-own-Monad
3. Data growth profiling.

It's been a good read anyway, and fun to play with the code.

Dave

On Wed, Aug 19, 2009 at 1:00 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Wow, very nice cleanup! That's really a good way for me to learn, thanks.
 Well, my intuition told me that strings and ++ wouldn't work, since what we
 want is an infinite list of output strings, and using ++ would result in
 (((s1++s2)++s3)++s4)++s5... which is highly inefficient and I think it would
 keep the complete output text in memory. Using difference lists results in
 right associative concatenation of s1++(s2++(s3++(s4++... which is efficient
 and can be garbage collected nicely. At least that's what I guess. I really
 would like to get a deeper understanding of all this but that will take lots
 of time and study, but if I'm lucky I still have 20 to 40 years to go, so I
 won't be bored :-)




 On Wed, Aug 19, 2009 at 9:46 PM, David Leimbach leim...@gmail.com wrote:

 Very cool!
 I am still wondering what the significance of the DList is with this
 though, or why it was needed to begin with.

 Dave


 On Wed, Aug 19, 2009 at 12:28 PM, Ryan Ingram ryani.s...@gmail.comwrote:

 Added a new version (tested, works with infinite loops, no early output,
 etc.)

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8343

 I'll put up a short write-up after lunch.

  -- ryan

 On Wed, Aug 19, 2009 at 11:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  The cleaned up code didn't seem to work for me, it printed everything
 before
  asking input again.
  But I added a patch that looks like it supports looping, but I don't
  understand exactly what is going on :-)
  I added the delay function which makes appending to the output less
  strict.
  Note that in this version I add a delay to each right argument of =,
 but
  one could also do it manually
  On Wed, Aug 19, 2009 at 7:37 PM, David Leimbach leim...@gmail.com
 wrote:
 
  I've corrected it.  It still doesn't suffer looping.  :-)
 
  On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.com
  wrote:
 
  Doesn't seem to compile.
  I nearly never use case statements in my code, so I'm not really sure
  what's going on.
  neat2.hs:14:39: parse error on input `='
  Dave
  On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.com
  wrote:
 
  I posted a reply to your paste with a stricter version of S and some
  cleanup.
 
  Untested, though I believe it should work without seq.
 
  case provides all the strictness you need, I think!
 
   -- ryan
 
  On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelen
 bugf...@gmail.com
  wrote:
   Expect more bugs with this though :-) Just found out that looping
 does
   not
   work, it hangs, e.g.
  
   test = do
 out Enter your first name:
 fstName - inp
 out Enter your second name:
 sndName - inp
 out (Welcome ++fstName++ ++sndName)
 out Goodbye!
 test
  
   Doesn't seem to work :-) Back to the drawing board.
  
   On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen 
 bugf...@gmail.com
   wrote:
  
   Not at all, use it for whatever you want to :-)
   I'm writing this code because I'm preparing to write a bunch of
   tutorials
   on FRP, and I first wanted to start with simple console based
 FRP,
   e.g.
   making a little text adventure game, where the input/choices of
 the
   user
   might be parsed ala parsec, using monadic style, applicative
 style,
   and
   arrows, and then doing the same with FRP frameworks like Yampa,
   Elera,
   Reactive, etc...
   After that I would start writing tutorials that use OpenGL,
 making
   some
   very simple games, again with the above approaches, and ending
 with a
   conversion of a very old game of mine (Zarathrusta written in
   assembler from
   1991, which was based on Thrust from 1986, converted by myself in
 C++
   to
   PocketPC as G-Pod, and so I would like to make a version in
 Haskell
   that
   runs on the iPhone :-)
   This of course is a lot of work, and I would like to put this on
 the
   Haskell wiki or a blog or something, so others can contribute and
   comment. I
   would like to show real examples that explain the shortcomings of
 the
   FRP
   approaches, because now this is still a bit blurry to me.
  
   On Wed, Aug 19, 2009 at 5:43 PM, David Leimbach 
 leim...@gmail.com
   wrote:
  
   This Monad you've created is quite excellent.  I was trying to
 do
   something like this about a year ago, to make the input and
 output
   handling
   of an interactive bowling score card work nicely.  I kept
 running
   into
   issues, and did not believe that seq was going to do the trick.
Nice work!
   

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-19 Thread Peter Verswyvelen
Well I really wrote this code as an exercise, and it was a good one. Now I
(or someone) needs to explain why it works.
But is this monad really useful? I mean it would be straightforward to write
this using the ST monad I guess?

Anyway, the reason why I want this pure code is that even with a console
based game, I don't want IO in it, since recording the input and replaying
it is vital to reproduce the actions the user did, and if things go wrong
(they always do), the log of all input can be used to restore the exact game
play. Of course you can do the same using imperative techniques and IO
redirection (which I did for my old games), but with this pure code you
don't have to worry about other places where IO could be used.

On Wed, Aug 19, 2009 at 10:06 PM, David Leimbach leim...@gmail.com wrote:

 Hmmm very interesting thinking on this.  Perhaps ByteStrings would be a
 good way to go for efficiency of composition.
 I'd love to see some profiling of all of this as part of the lesson at some
 point.  (Perhaps with vacuum visualization?)

 This thread has tackled 3 major tricky issue areas with Haskell so far:

 1. Lazy IO and seq
 2. Roll-your-own-Monad
 3. Data growth profiling.

 It's been a good read anyway, and fun to play with the code.

 Dave

 On Wed, Aug 19, 2009 at 1:00 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 Wow, very nice cleanup! That's really a good way for me to learn, thanks.
 Well, my intuition told me that strings and ++ wouldn't work, since what
 we want is an infinite list of output strings, and using ++ would result in
 (((s1++s2)++s3)++s4)++s5... which is highly inefficient and I think it would
 keep the complete output text in memory. Using difference lists results in
 right associative concatenation of s1++(s2++(s3++(s4++... which is efficient
 and can be garbage collected nicely. At least that's what I guess. I really
 would like to get a deeper understanding of all this but that will take lots
 of time and study, but if I'm lucky I still have 20 to 40 years to go, so I
 won't be bored :-)




 On Wed, Aug 19, 2009 at 9:46 PM, David Leimbach leim...@gmail.comwrote:

 Very cool!
 I am still wondering what the significance of the DList is with this
 though, or why it was needed to begin with.

 Dave


 On Wed, Aug 19, 2009 at 12:28 PM, Ryan Ingram ryani.s...@gmail.comwrote:

 Added a new version (tested, works with infinite loops, no early output,
 etc.)

 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8316#a8343

 I'll put up a short write-up after lunch.

  -- ryan

 On Wed, Aug 19, 2009 at 11:28 AM, Peter Verswyvelenbugf...@gmail.com
 wrote:
  The cleaned up code didn't seem to work for me, it printed everything
 before
  asking input again.
  But I added a patch that looks like it supports looping, but I don't
  understand exactly what is going on :-)
  I added the delay function which makes appending to the output less
  strict.
  Note that in this version I add a delay to each right argument of =,
 but
  one could also do it manually
  On Wed, Aug 19, 2009 at 7:37 PM, David Leimbach leim...@gmail.com
 wrote:
 
  I've corrected it.  It still doesn't suffer looping.  :-)
 
  On Wed, Aug 19, 2009 at 10:31 AM, David Leimbach leim...@gmail.com
  wrote:
 
  Doesn't seem to compile.
  I nearly never use case statements in my code, so I'm not really
 sure
  what's going on.
  neat2.hs:14:39: parse error on input `='
  Dave
  On Wed, Aug 19, 2009 at 10:23 AM, Ryan Ingram ryani.s...@gmail.com
 
  wrote:
 
  I posted a reply to your paste with a stricter version of S and
 some
  cleanup.
 
  Untested, though I believe it should work without seq.
 
  case provides all the strictness you need, I think!
 
   -- ryan
 
  On Wed, Aug 19, 2009 at 9:28 AM, Peter Verswyvelen
 bugf...@gmail.com
  wrote:
   Expect more bugs with this though :-) Just found out that looping
 does
   not
   work, it hangs, e.g.
  
   test = do
 out Enter your first name:
 fstName - inp
 out Enter your second name:
 sndName - inp
 out (Welcome ++fstName++ ++sndName)
 out Goodbye!
 test
  
   Doesn't seem to work :-) Back to the drawing board.
  
   On Wed, Aug 19, 2009 at 5:55 PM, Peter Verswyvelen 
 bugf...@gmail.com
   wrote:
  
   Not at all, use it for whatever you want to :-)
   I'm writing this code because I'm preparing to write a bunch of
   tutorials
   on FRP, and I first wanted to start with simple console based
 FRP,
   e.g.
   making a little text adventure game, where the input/choices of
 the
   user
   might be parsed ala parsec, using monadic style, applicative
 style,
   and
   arrows, and then doing the same with FRP frameworks like Yampa,
   Elera,
   Reactive, etc...
   After that I would start writing tutorials that use OpenGL,
 making
   some
   very simple games, again with the above approaches, and ending
 with a
   conversion of a very old game of mine (Zarathrusta written in
   assembler from
   1991, which was based on Thrust from 1986, converted by myself