
Hello! I have a program that is using ST.Strict, which works fine. However, the program needs to be extended, and to do that, lazy evaluation is needed. As a result of that, I have switched to ST.Lazy to be able to do stuff like foo y = do x <- something xs <- foo (y+1) return (x:xs) However, when running the program compiled with ST.Lazy, the following is outputted: [tobsi@wobsi]$ ./runnerLazy looper.hex runnerLazy: <<loop>> The very same program compiled with ST.Strict outputs: [tobsi@wobsi]$ ./runner looper.hex 83298556 The code that is actually computing stuff is this: loopSys :: Int -> CPU s Int loopSys cc = do instr <- fetch if instr == 0xEA --NOP then return cc else do c <- execute instr loopSys $! (cc+c) The CPU type looks as follows: type CPU s a = ReaderT (SysEnv s) (ST s) a The program is run like runReaderT (loopSys 0) which in turn is being runST'd and then printed Does anyone know why the program just outputs <<loop>> when compiled under ghc 6.10.2, and runs perfectly fine under ghc 6.8.2? The program is compiled with --make and -O2 Tobias Olausson tobsan@gmail.com

So, I don't know what is causing your problem, but foo will not do
what you want even with lazy ST.
foo y = do
x <- something
xs <- foo (y+1)
return (x:xs)
Desugaring:
foo y = something >>= \x -> foo (y+1) >>= \xs -> return (x:xs)
= something >>= \x -> something >>= \x2 -> foo (y+2) >>= \xs2 ->
return (x2:xs2) >>= \xs -> return (x:xs)
= something >>= \x -> something >>= \x2 -> foo (y+2) >>= \xs2 ->
return (x:x2:xs2)
You see that there is an infinite chain of "foo" calls; the lazy ST
still needs to thread the state through that chain; so in the case of
foo 0 >>= something_else, the state is _|_ for something_else and you
will fail if you use read/write/newSTRef after that point. In fact,
I'm not sure that lazy ST is very useful :)
My guess is that you want one of
(1) mdo, when the effects in 'something' only matter once, or
(2) unsafeInterleaveST, if you just want to be able to traverse the
(x:xs) list lazily and the references it uses are dead after calling
foo.
-- ryan
On Sun, May 3, 2009 at 10:27 AM, Tobias Olausson
Hello! I have a program that is using ST.Strict, which works fine. However, the program needs to be extended, and to do that, lazy evaluation is needed. As a result of that, I have switched to ST.Lazy to be able to do stuff like
foo y = do x <- something xs <- foo (y+1) return (x:xs)
However, when running the program compiled with ST.Lazy, the following is outputted: [tobsi@wobsi]$ ./runnerLazy looper.hex runnerLazy: <<loop>>
The very same program compiled with ST.Strict outputs: [tobsi@wobsi]$ ./runner looper.hex 83298556
The code that is actually computing stuff is this: loopSys :: Int -> CPU s Int loopSys cc = do instr <- fetch if instr == 0xEA --NOP then return cc else do c <- execute instr loopSys $! (cc+c)
The CPU type looks as follows: type CPU s a = ReaderT (SysEnv s) (ST s) a
The program is run like runReaderT (loopSys 0) which in turn is being runST'd and then printed
Does anyone know why the program just outputs <<loop>> when compiled under ghc 6.10.2, and runs perfectly fine under ghc 6.8.2? The program is compiled with --make and -O2
Tobias Olausson tobsan@gmail.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Would unsafeInterleaveST work just as unsafeInterleaveIO in the manner
that it returns immediately, and then is computed lazily?
The idea in the complete program is that one part representing
the CPU will produce a list lazily, which will then be consumed
lazily by another part of the program, which in turn will produce
a lazy list fed to the CPU.
I might add that there was a base case for foo. It turns out i omitted
that for "simplicity". Even stranger, if one adds the following
foo y = do
if something then return y
else do
val <- foo (y+1)
fail "this is a fail"
Will make the program fail with "this is a fail". Without the fail, that
does not return the computed y. How come?
//Tobias
2009/5/4 Ryan Ingram
So, I don't know what is causing your problem, but foo will not do what you want even with lazy ST.
foo y = do x <- something xs <- foo (y+1) return (x:xs)
Desugaring:
foo y = something >>= \x -> foo (y+1) >>= \xs -> return (x:xs) = something >>= \x -> something >>= \x2 -> foo (y+2) >>= \xs2 -> return (x2:xs2) >>= \xs -> return (x:xs) = something >>= \x -> something >>= \x2 -> foo (y+2) >>= \xs2 -> return (x:x2:xs2)
You see that there is an infinite chain of "foo" calls; the lazy ST still needs to thread the state through that chain; so in the case of foo 0 >>= something_else, the state is _|_ for something_else and you will fail if you use read/write/newSTRef after that point. In fact, I'm not sure that lazy ST is very useful :)
My guess is that you want one of (1) mdo, when the effects in 'something' only matter once, or (2) unsafeInterleaveST, if you just want to be able to traverse the (x:xs) list lazily and the references it uses are dead after calling foo.
-- ryan
On Sun, May 3, 2009 at 10:27 AM, Tobias Olausson
wrote: Hello! I have a program that is using ST.Strict, which works fine. However, the program needs to be extended, and to do that, lazy evaluation is needed. As a result of that, I have switched to ST.Lazy to be able to do stuff like
foo y = do x <- something xs <- foo (y+1) return (x:xs)
However, when running the program compiled with ST.Lazy, the following is outputted: [tobsi@wobsi]$ ./runnerLazy looper.hex runnerLazy: <<loop>>
The very same program compiled with ST.Strict outputs: [tobsi@wobsi]$ ./runner looper.hex 83298556
The code that is actually computing stuff is this: loopSys :: Int -> CPU s Int loopSys cc = do instr <- fetch if instr == 0xEA --NOP then return cc else do c <- execute instr loopSys $! (cc+c)
The CPU type looks as follows: type CPU s a = ReaderT (SysEnv s) (ST s) a
The program is run like runReaderT (loopSys 0) which in turn is being runST'd and then printed
Does anyone know why the program just outputs <<loop>> when compiled under ghc 6.10.2, and runs perfectly fine under ghc 6.8.2? The program is compiled with --make and -O2
Tobias Olausson tobsan@gmail.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tobias Olausson tobsan@gmail.com

On Sun, May 3, 2009 at 7:54 PM, Tobias Olausson
Would unsafeInterleaveST work just as unsafeInterleaveIO in the manner that it returns immediately, and then is computed lazily? The idea in the complete program is that one part representing the CPU will produce a list lazily, which will then be consumed lazily by another part of the program, which in turn will produce a lazy list fed to the CPU.
Like co-routines? It might be possible to do this with non-strict ST, but it feels like it would be tricky to get right. How are you feeding the lists from the two computations together? Are they computed in the same ST thread?
I might add that there was a base case for foo. It turns out i omitted that for "simplicity". Even stranger, if one adds the following
foo y = do if something then return y else do val <- foo (y+1) fail "this is a fail"
Will make the program fail with "this is a fail". Without the fail, that does not return the computed y. How come?
In the non-strict ST monad, the recursive call to foo does not get
evaluated until forced by an evaluation of val. That particular
version would work identically if you replaced the recursive call to
foo with "undefined".
--
Dave Menendez

This simple implementation of CPU does not behave as expected in the latest version of ghc using ST.Lazy since it updates the `pc` in the wrong order. When we use ghc-6.8 the code works as expected both with lazy and strict ST. How is that? How do we fix this so we can use ghc-6.10. -- ------------------------------------------------------------------ module Main where import Control.Monad.Reader import Control.Monad.ST.Lazy import Data.STRef.Lazy import Data.Array.ST import Int data Refs s = Refs { memory :: STArray s Int8 Int8 , pc :: STRef s Int8 } type CPU s a = ReaderT (Refs s) (ST s) a type Address = Int8 type OPCode = Int8 alterVar v f = asks v >>= lift . flip modifySTRef f getVar v = asks v >>= lift . readSTRef setVar v a = asks v >>= lift . flip writeSTRef a readMem :: Int8 -> CPU s Int8 readMem addr = asks memory >>= lift . flip readArray addr writeMem :: Address -> Int8 -> CPU s () writeMem addr v = asks memory >>= \r -> lift $ writeArray r addr v fetch :: CPU s OPCode fetch = getVar pc >>= \v -> alterVar pc (+1) >> readMem v execute :: OPCode -> CPU s () execute op = case op of 0x4 -> alterVar pc (+100) -- should run this _ -> error "should never match this" initCPU :: ST s (Refs s) initCPU = do m <- newArray_ (0,30) p <- newSTRef 0 return (Refs m p) main :: IO () main = do print $ runST (initCPU >>= runReaderT m) where m = do writeMem 0 0x4 writeMem 1 0x10 op <- fetch execute op getVar pc

Am Dienstag 05 Mai 2009 21:42:00 schrieb Tobias Olausson:
This simple implementation of CPU does not behave as expected in the latest version of ghc using ST.Lazy since it updates the `pc` in the wrong order. When we use ghc-6.8 the code works as expected both with lazy and strict ST. How is that? How do we fix this so we can use ghc-6.10.
Fix 1: compile with optimisations. The sample code worked here with that. Fix 2: change fetch:
fetch :: CPU s OPCode fetch = getVar pc >>= \v -> alterVar pc (+1) >> readMem v
The lazy ST doesn't actually read the STRef before readMem v is called, so it reads the altered STRef and consequently the wrong memory address. Make sure that v is determined before the STRef is altered, e.g. by fetch = getVar pc >>= \v -> v `seq` (alterVar pc (+1) >> readMem v) or fetch = do v <- getVar pc w <- readMem v alterVar pc succ return w

On 05/05/2009 20:42, Tobias Olausson wrote:
This simple implementation of CPU does not behave as expected in the latest version of ghc using ST.Lazy since it updates the `pc` in the wrong order. When we use ghc-6.8 the code works as expected both with lazy and strict ST. How is that? How do we fix this so we can use ghc-6.10.
Looks like a real bug, I just created a ticket: http://hackage.haskell.org/trac/ghc/ticket/3207 Cheers, Simon

On Sun, May 3, 2009 at 6:11 PM, Ryan Ingram
So, I don't know what is causing your problem, but foo will not do what you want even with lazy ST.
That depends on what he wants to do. As long as nothing subsequent to the call to foo tries to read a reference, then foo is fine. For example, this works fine: bar r = do x <- readSTRef r writeSTRef $! x + 1 return x
take 10 $ runST (newSTRef 0 >>= \r -> sequence (repeat (bar r))) [0,1,2,3,4,5,6,7,8,9]
Does anyone know why the program just outputs <<loop>> when compiled under ghc 6.10.2, and runs perfectly fine under ghc 6.8.2? The program is compiled with --make and -O2
As I understand it, you get <<loop>> when the RTS detects a thunk
which depends on itself, which can happen if you're trying to do a
strict computation lazily.
I can't imagine why different versions of GHC would give different
results, though.
--
Dave Menendez

On Sun, May 3, 2009 at 11:27 AM, Tobias Olausson
Hello! I have a program that is using ST.Strict, which works fine. However, the program needs to be extended, and to do that, lazy evaluation is needed. As a result of that, I have switched to ST.Lazy to be able to do stuff like
foo y = do x <- something xs <- foo (y+1) return (x:xs)
As Ryan points out, this will not do what you want. But that is incidental, not essential: foo y = do x <- something fmap (x:) $ foo (y+1) Luke

On Tue, May 5, 2009 at 3:27 PM, Luke Palmer
On Sun, May 3, 2009 at 11:27 AM, Tobias Olausson
wrote: Hello! I have a program that is using ST.Strict, which works fine. However, the program needs to be extended, and to do that, lazy evaluation is needed. As a result of that, I have switched to ST.Lazy to be able to do stuff like
foo y = do x <- something xs <- foo (y+1) return (x:xs)
As Ryan points out, this will not do what you want. But that is incidental, not essential:
foo y = do x <- something fmap (x:) $ foo (y+1)
Questioning my own reasoning, I must apologize. I was wrong, these two programs are identical and both do what you want. Any references to the state *after* the infinite chain of foos will result in _|_, but as long as "something" is the only place that state calls occur, you will be fine. I also suspect that ST.Lazy should be no less defined than ST.Strict in all cases, modulo unsafe operations of course (you aren't doing those, are you?), so you have encountered a bug. Minimize the test case and submit a bug report :-) Luke
participants (6)
-
Daniel Fischer
-
David Menendez
-
Luke Palmer
-
Ryan Ingram
-
Simon Marlow
-
Tobias Olausson