[Haskell-cafe] memory, garbage collection and other newbie's issues

Andrea Rossato mailing_list at istitutocolli.org
Sun Oct 22 05:37:55 EDT 2006


Hello!

On Sun, Oct 22, 2006 at 12:27:05AM +0400, Bulat Ziganshin wrote:
> as Udo said, it should be better to evaluate thunks just when they are
> created, by using proper 'seq' calls.

While I understand why you and Udo are right, still it is difficult
for me to related this discussion to my code. So I wrote a small
example that reproduces my problem, with the hope that this will help
me understand your point.

This is my specific problem, I believe.

There is a StateT monad with a list of string as a state.
The list is populated with the lines of a file entered by the user.
The user may read some lines of this file or request another one:
- lFilename will load a file
- sNumber will show a line number.

The input file is evaluated at the very beginning (in my case that is
forced by the xml parser, as far as I understand) and stored as the
state.

Now, the state will not be entirely consumed/evaluated by the user,
and so it will not become garbage. Am I right?

Where should I force evaluation? 

Is it clear my confusion (sorry for this kind of nasty recursion...;-)?

Thanks for your kind attention.

Best regards,
Andrea

here's the code:

--------------
module Main where

import Control.Monad.State
import IO

data Mystate = Mystate {mystate :: [String]}

type SL = StateT Mystate IO

getState :: SL [String]
getState =
    do s <- get
       return $ mystate s

setState ns =
    modify (\s -> s {mystate = ns})

getFile :: String -> SL ()
getFile p =
    do f <- liftIO $ readFile p
       let lns = lines f
       -- forces evaluation of lns
       liftIO $ putStrLn $ "Number of lines: " ++ show (length lns)
       setState lns
       promptLoop

showLine :: Int -> SL ()
showLine nr =
    do s <- getState
       liftIO $ putStrLn $ s !! nr
       promptLoop

promptStr = "lFilename [load the file Filename] - sNr [show the line Nr of Filename] - q to quit"

promptLoop :: SL ()
promptLoop = 
    do liftIO $ putStrLn promptStr
       str <- liftIO getLine
       case str of
         ('l':ss) -> getFile ss
         ('s':nr) -> showLine (read nr)
         ('q':[]) -> liftIO $ return ()
         _ -> promptLoop

main =
    evalStateT promptLoop $ Mystate []


More information about the Haskell-Cafe mailing list