beginner question

Luca Ciciriello luca_ciciriello at hotmail.com
Wed Oct 14 02:26:10 EDT 2009


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?
http://clk.atdmt.com/UKM/go/174426567/direct/01/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20091014/60cb0175/attachment-0001.html


More information about the Glasgow-haskell-users mailing list