beginner question

Philip K.F. Hölzenspies p.k.f.holzenspies at utwente.nl
Wed Oct 14 04:26:49 EDT 2009


Dear Luca,

The problem in your alternative code is that hGetContents lazily reads
the contents of the handle it is passed. You've run into a cognitive
bootstrap problem; the documentation for System.IO [1] does explain it,
but I can see that you need to understand it to be able to read it ;)

These are the important bits for your example:
- hGetContents h puts handle h into a "semi-closed" state, but doesn't
actually read anything (yet).
- Any other function that gets a semi-closed handle (except hClose) will
see it as a closed handle.
- When a semi-closed handle becomes closes, the contents of the
associated list becomes fixed.

In other words; the actual reading from the handle doesn't happen until
you evaluate the resulting list (and then still only the part that you
evaluate). In your bracket, you open a handle, then you "convert" the
handle into a lazy list that would evaluate to the contents of the file,
but then you close the handle, fixing the list you got to an empty list.

If you want to do this, you would want something like this:

withTableContents :: String -> (String -> IO a) -> IO a
withTableContents table cont = bracket (openFile table ReadMode)
                               hClose
                               (\h -> hGetContents h >>= cont)

Hope this helps. By the way, this type of question should probably go to
haskell-cafe at haskell.org which will usually give you a lot of
explanation quite quickly.

Regards,
Philip

[1]
http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html#v:hGetContents

On Wed, 2009-10-14 at 07:26 +0100, Luca Ciciriello wrote:
> Just a Haskell beginner question. 
> If I load in GHCi the code below all works fine, I load a file and its
> content is shown on screen. But if I use the second version of my
> "load_by_key" (the commented one) no error is reported loading and
> executing this code, but nothing is shown on screen. Where is my
> mistake?
> I'm using GHC 6.10.4 on MacOS X 10.5.8
>  
> Thanks in advance.
>  
> Luca.
>  
> 
> module BackEnd
>     where
>  
> import IO
>  
> load_by_key :: String -> String -> IO ()
>  
> load_by_key table key = do
>                           inh <- openFile table ReadMode
>                           contents <- hGetContents inh
>                           get_record (get_string contents) key
>                           hClose inh
>  
> {-
> load_by_key table key = do
>                           contents <- getTableContent table
>                           get_record (get_string contents) key
> -}  
>  
> get_string :: String -> String
> get_string = (\x -> x)
>  
> get_record :: String -> String -> IO ()
> get_record contents key = putStr( contents ) 
>  
> getTableContent :: String -> IO String
> getTableContent table = bracket (openFile table ReadMode)
>                                 hClose
>                                 (\h -> (hGetContents h))
> 
> 
> ______________________________________________________________________
> Did you know you can get Messenger on your mobile? Learn more.
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list