On Tue, Jan 10, 2006 at 04:44:33PM +0000, Ian Lynagh wrote:
> 
> readChunks :: FirstMonad String
> readChunks = do xs <- get
>                 if null xs then return []
>                            else do let (ys, zs) = foo xs
>                                    put zs
>                                    rest <- readChunks
>                                    return (ys ++ rest)

It looks like changing this let to a case fixes this example, but at the
time I'd experimented with that there must have been other issues
clouding the effect, such as the following.

Foo1 (attached) uses large amounts of memory whereas Foo2 (also
attached) runs in a little constant space. The difference is only
changing this:

    else do chunk <- case foo xs of
                         (ys, zs) ->
                             do put zs
                                return ys
            chunks <- readChunks
            return (chunk ++ chunks)

to this:

    else case foo xs of
             (ys, zs) ->
                 do put zs
                    chunks <- readChunks
                    return (ys ++ chunks)

but I don't have a good feeling for why this should be the case given
I'd expect chunk to be forced, and thus the case evaluated, at the same
point in Foo1 as the case is evaluated in Foo2.

Is this just a case of GHC's optimiser's behaviour depending on subtle
source changes, or am I missing something?


Thanks
Ian

module Main (main) where

import Control.Monad (liftM)
import Control.Monad.State (State, runState, evalState, get, put)

main :: IO ()
main = do xs <- readFile "data"
          ys <- readFile "data"
          print (evalState readChunks xs == ys)

---

type FirstMonad = State String

readChunks :: FirstMonad String
readChunks = do xs <- get
                if null xs then return []
                           else do chunk <- case foo xs of
                                                (ys, zs) ->
                                                    do put zs
                                                       return ys
                                   chunks <- readChunks
                                   return (chunk ++ chunks)

---

type SecondMonad = State String

foo :: String -> (String, String)
foo = runState bar

bar :: SecondMonad String
bar = do inp <- get
         case inp of
             [] -> return []
             x:xs -> do put xs
                        liftM (x:) bar

module Main (main) where

import Control.Monad (liftM)
import Control.Monad.State (State, runState, evalState, get, put)

main :: IO ()
main = do xs <- readFile "data"
          ys <- readFile "data"
          print (evalState readChunks xs == ys)

---

type FirstMonad = State String

readChunks :: FirstMonad String
readChunks = do xs <- get
                if null xs then return []
                           else case foo xs of
                                    (ys, zs) ->
                                        do put zs
                                           chunks <- readChunks
                                           return (ys ++ chunks)

---

type SecondMonad = State String

foo :: String -> (String, String)
foo = runState bar

bar :: SecondMonad String
bar = do inp <- get
         case inp of
             [] -> return []
             x:xs -> do put xs
                        liftM (x:) bar

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

Reply via email to