
Hi everyone, I think this is a totally newbie question as i am a complete novice to Haskell. I am trying to write down a few programs using GHC in order to get used with the language. I am having some problems with a piece of code (that is supposed to return a list of lines from a text file) which I transcribe below: module Test where import IO readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents)) The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected. Thanks in advance André

On Fri, Aug 12, 2005 at 09:17:32AM -0300, Andr Vargas Abs da Cruz wrote:
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
I think that this may be because hGetContents puts the file in a semi-closed state (and reads the contents lazily). Try removing the hClose (replacing it with (return ()). Lazy IO is nice, but gets tricky at times. -- David Roundy http://www.darcs.net

On 8/12/05, David Roundy
On Fri, Aug 12, 2005 at 09:17:32AM -0300, Andr Vargas Abs da Cruz wrote:
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
I think that this may be because hGetContents puts the file in a semi-closed state (and reads the contents lazily). Try removing the hClose (replacing it with (return ()). Lazy IO is nice, but gets tricky at times.
Or better yet, use 'readFile'. -- Friendly, Lemmih

On Fri, Aug 12, 2005 at 02:54:03PM +0200, Lemmih wrote:
On 8/12/05, David Roundy
wrote: On Fri, Aug 12, 2005 at 09:17:32AM -0300, Andr Vargas Abs da Cruz wrote:
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
I think that this may be because hGetContents puts the file in a semi-closed state (and reads the contents lazily). Try removing the hClose (replacing it with (return ()). Lazy IO is nice, but gets tricky at times.
Or better yet, use 'readFile'.
Indeed, that would be simpler, but it's still lazy IO, and if you're unaware of that you'll still get confused when you try to delete the file after reading the lines you wanted out of it, and it fails on windows, but not on POSIX systems... unless you read the entire file, or computed its length. -- David Roundy http://www.darcs.net

Hi André, The problem is that hGetContents does lazy reading of the handle. I you do: readDataFromFile "test.txt" >>= print the handle is closed by hClose (in readDataFromFile) before "print" demands the contents from the handle. Just don't close the Handle explicitly. This code works: readDataFromFile filename = do h <-openFile filename ReadMode contents <- hGetContents h return (lines contents) You do not really need to close it, because hGetContents "semi-closes" the handle. Read more: http://www.haskell.org/onlinereport/io.html (Section 21.2.2 Semi-Closed Handles) http://users.aber.ac.uk/afc/stricthaskell.html#semiclosed Cheers, Arthur On 12-aug-05, at 14:17, André Vargas Abs da Cruz wrote:
Hi everyone,
I think this is a totally newbie question as i am a complete novice to Haskell. I am trying to write down a few programs using GHC in order to get used with the language. I am having some problems with a piece of code (that is supposed to return a list of lines from a text file) which I transcribe below:
module Test where
import IO
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
Thanks in advance André _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you all for your answers. I'll try to be more careful with lazy evaluations while doing IO operations from now on. Best regards André
On Fri, Aug 12, 2005 at 02:54:03PM +0200, Lemmih wrote:
On 8/12/05, David Roundy
wrote: On Fri, Aug 12, 2005 at 09:17:32AM -0300, Andr Vargas Abs da Cruz wrote:
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
I think that this may be because hGetContents puts the file in a semi-closed state (and reads the contents lazily). Try removing the hClose (replacing it with (return ()). Lazy IO is nice, but gets tricky at times.
Or better yet, use 'readFile'.
Indeed, that would be simpler, but it's still lazy IO, and if you're unaware of that you'll still get confused when you try to delete the file after reading the lines you wanted out of it, and it fails on windows, but not on POSIX systems... unless you read the entire file, or computed its length.
Glynn Clements wrote:
hGetContents reads the file lazily; it won't actually read anything until you try to "consume" the result. However, by that point, you will have called hClose.
In general, you shouldn't use hClose in conjunction with lazy I/O (hGetContents etc) unless you are certain that the data will have been read.
When you put the "print" in place of the return, you force the data to be consumed immediately, so the issue doesn't arise.
Arthur Baars wrote: Hi André,
The problem is that hGetContents does lazy reading of the handle.
I you do: readDataFromFile "test.txt" >>= print
the handle is closed by hClose (in readDataFromFile) before "print" demands the contents from the handle.
Just don't close the Handle explicitly. This code works: readDataFromFile filename = do h <-openFile filename ReadMode contents <- hGetContents h return (lines contents)
You do not really need to close it, because hGetContents "semi-closes" the handle. Read more: http://www.haskell.org/onlinereport/io.html (Section 21.2.2 Semi-Closed Handles) http://users.aber.ac.uk/afc/stricthaskell.html#semiclosed
Cheers,
Arthur

André Vargas Abs da Cruz wrote:
I think this is a totally newbie question as i am a complete novice to Haskell. I am trying to write down a few programs using GHC in order to get used with the language. I am having some problems with a piece of code (that is supposed to return a list of lines from a text file) which I transcribe below:
module Test where
import IO
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
hGetContents reads the file lazily; it won't actually read anything
until you try to "consume" the result. However, by that point, you
will have called hClose.
In general, you shouldn't use hClose in conjunction with lazy I/O
(hGetContents etc) unless you are certain that the data will have been
read.
When you put the "print" in place of the return, you force the data to
be consumed immediately, so the issue doesn't arise.
--
Glynn Clements

This question comes up often, and there are lots of ways to answer it.
Not too long ago, I posted a simplistic (but not terribly practical)
solution, writing a strict version of readFile in terms of hGetChar,
to which Simon Marlow replied with an actually pratical implementation
which allocates memory enough for the file, reads the file into that
memory, and only lazily converts it into a string. That discussion
seems to have been immortalised at
http://users.aber.ac.uk/afc/stricthaskell.html which I think has
already been mentioned. (As a side note, I disagree with that author's
views on laziness at the top of the page -- it's usually lazy
evaluation that I want because it increases compositionality of the
code so much. Only very rarely do I care for things to be strict.)
One other (again, not terribly practical, but nice to know about)
thing that you can do is to force Haskell to evaluate all of the
characters in the returned list (which will automatically close the
handle for you). This isn't such a good thing to do if the file you're
reading is huge, as it will consume time and memory for the whole
file, and it's quite possible to run out of stack space, but if you
really want the file to be read and closed before continuing, it will
make sure of that. In addition to this, there may be other reasons for
wanting to control the strictness and order of evaluation, so it's
probably useful to know in any event.
The IO action to use is called
evaluate :: a -> IO a
and is located in Control.Exception. What evaluate does is to force
its parameter to be evaluated so far as the topmost node in the data
structure. We want to completely evaluate the list returned by
fmap lines . hGetContents
not just the first cell, so we'll mapM_ evaluate over the list as follows:
do hdl <- openFile "myFile" ReadMode
ls <- fmap lines (hGetContents hdl)
mapM_ evaluate ls
-- at this point, hdl is closed, and ls contains the contents
-- of the whole file so we can go on to use it...
If we want to get carried away, we can also (ab)use the strategies in
Control.Parallel.Strategies to get things to be evaluated as far as we
might like. There is a function there:
rnf :: Strategy a
(where Strategy a is a synonym for a -> ()) which when evaluated,
reduces its argument to normal form before returning (). Basically, it
will completely evaluate the data structure as far as possible. While
it works for a bunch of types in the class NFData (anything which is a
combination of lists, arrays and tuples) it would be nice to be able
to derive it for new data types like:
data MyType = ... deriving (NFData)
While as far as I know there isn't a GHC extension to derive NFData,
there is a GHC extension to derive another class which is somewhat
more general in its scope. This class is called Data, and is in
Data.Generics. With it, provided I haven't made any mistakes, we can
write our own version of rnf as follows:
rnf :: (Data a) => a -> ()
rnf x = everything seq (\y -> y `seq` ()) x
The function seq :: a -> b -> b is a primitive in Haskell for creating
strictness. The expression (seq x y), when evaluated, will cause x to
be evaluated (to weak head normal form) before returning y. The
everything function is a sort of generalisation of folding which is
available on any data type in the class Data, which is actually most
common types. You can read about it in
http://homepages.cwi.nl/~ralf/syb1/
The overall effect of evaluating (rnf x) should then be to completely
evaluate x, and return (), which is what we want.
To parallel some other things people have done, we can write
deepSeq x y = rnf x `seq` y
as well as
f $!! x = rnf x `seq` f x
the latter of which is a strict form of function application.
When we want these functions to apply to our own data types, it will
suffice to just write "deriving Data" on the end of the data
declaration.
I'm not sure how relevant or comprehensible this will seem to someone
new to Haskell, but I hope it's somewhat interesting at least, and
maybe some other people on the list will find bits of it useful too.
- Cale Gibbard
On 12/08/05, André Vargas Abs da Cruz
Hi everyone,
I think this is a totally newbie question as i am a complete novice to Haskell. I am trying to write down a few programs using GHC in order to get used with the language. I am having some problems with a piece of code (that is supposed to return a list of lines from a text file) which I transcribe below:
module Test where
import IO
readDataFromFile filename = do bracket (openFile filename ReadMode) hClose (\h -> do contents <- hGetContents h return (lines contents))
The question is: if i try to run this, it returns me nothing (just an empty list). Why does this happen ? When i remove the "return" and put a "print" instead, it prints everything as i expected.
Thanks in advance André _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, Basically, my program has 7 threads for 7 rules Rule1 Rule2 .. .. .. and they all use pattern-mattching (a rule MUST be evaluated by a thread) The problem is there are some overlapping rules, which match the same pattern and diifferent rules are likely to give different results (one rule might give a result, others might loop forever). Also, for a particular pattern, there's at least one matching rule and there may be some rule looping forever (try to evaluate a "bottom" _|_) Im thinking of getting a list of all the applicable rules for a pattern, then hopefully can choose the best rule out of it. But we have no control over the scheduling of threads, so dont know when a thread finishs its evaluation (if it is applicable rule) or it just never terminates (rule that tries evaluating a _|_) So any ideas ? TuanAnh _________________________________________________________________ Want to block unwanted pop-ups? Download the free MSN Toolbar now! http://toolbar.msn.co.uk/

At 3:39 PM +0000 8/22/05, Dinh Tien Tuan Anh wrote:
Hi, Basically, my program has 7 threads for 7 rules
Rule1 Rule2 .. .. ..
and they all use pattern-mattching (a rule MUST be evaluated by a thread)
The problem is there are some overlapping rules, which match the same pattern and diifferent rules are likely to give different results (one rule might give a result, others might loop forever).
Also, for a particular pattern, there's at least one matching rule and there may be some rule looping forever (try to evaluate a "bottom" _|_)
Im thinking of getting a list of all the applicable rules for a pattern, then hopefully can choose the best rule out of it. But we have no control over the scheduling of threads, so dont know when a thread finishs its evaluation (if it is applicable rule) or it just never terminates (rule that tries evaluating a _|_)
So any ideas ?
If you can't choose a single best rule, you could start a thread on each of the applicable rules and let them "race" each other. The first to complete would provide the result and terminate its "competitors". Concurrent Haskell (http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control.Concurren...) provides the facilities you'd need. Dean

Hi, Basically, i have several rules: f1 x y ... f2 x y ... ..... They are all of the same type, but different names because i'll later on launch one thread for each of them, i.e: forkIO (f1 x y) forkIO (f2 x y) ..... There maybe still more rules, and i dont want to manually writing forkIO ... for every new one. So is there an elegant way to put all those rules together in a list and then call "mapIO forkIO" just once, (of course, a new rule should be attached to the list as well) ? Thanks a lot TuanAnh _________________________________________________________________ Winks & nudges are here - download MSN Messenger 7.0 today! http://messenger.msn.co.uk

On 8/30/05, Dinh Tien Tuan Anh
Hi, Basically, i have several rules: f1 x y ... f2 x y ... .....
They are all of the same type, but different names because i'll later on launch one thread for each of them, i.e: forkIO (f1 x y) forkIO (f2 x y) .....
There maybe still more rules, and i dont want to manually writing forkIO ... for every new one. So is there an elegant way to put all those rules together in a list and then call "mapIO forkIO" just once, (of course, a new rule should be attached to the list as well) ?
Thanks a lot TuanAnh
_________________________________________________________________ Winks & nudges are here - download MSN Messenger 7.0 today! http://messenger.msn.co.uk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

On 8/30/05, Dinh Tien Tuan Anh
Hi, Basically, i have several rules: f1 x y ... f2 x y ... .....
They are all of the same type, but different names because i'll later on launch one thread for each of them, i.e: forkIO (f1 x y) forkIO (f2 x y) .....
There maybe still more rules, and i dont want to manually writing forkIO ... for every new one. So is there an elegant way to put all those rules together in a list and then call "mapIO forkIO" just once, (of course, a new rule should be attached to the list as well) ?
Thanks a lot TuanAnh
Something like (untested)... xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs /S /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

On 8/30/05, Sebastian Sylvan
On 8/30/05, Dinh Tien Tuan Anh
wrote: Hi, Basically, i have several rules: f1 x y ... f2 x y ... .....
They are all of the same type, but different names because i'll later on launch one thread for each of them, i.e: forkIO (f1 x y) forkIO (f2 x y) .....
There maybe still more rules, and i dont want to manually writing forkIO ... for every new one. So is there an elegant way to put all those rules together in a list and then call "mapIO forkIO" just once, (of course, a new rule should be attached to the list as well) ?
Thanks a lot TuanAnh
Something like (untested)...
xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs
or: 'mapM_ [ f x y | f <- rules ]' -- Friendly, Lemmih

Something like (untested)...
xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs
what does "zipWith ($)" do ? _________________________________________________________________ Be the first to hear what's new at MSN - sign up to our free newsletters! http://www.msn.co.uk/newsletters

On 8/31/05, Dinh Tien Tuan Anh
Something like (untested)...
xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs
what does "zipWith ($)" do ?
$ is function application, so zipWith ($) will "zip" a list of functions with a list of arguments, by applying the functions to the arguments pair-wise, producing a list of results. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

2005/8/31, Sebastian Sylvan
On 8/31/05, Dinh Tien Tuan Anh
wrote: Something like (untested)...
xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs
what does "zipWith ($)" do ?
$ is function application, so zipWith ($) will "zip" a list of functions with a list of arguments, by applying the functions to the arguments pair-wise, producing a list of results.
But forkIO is function not a list of functions. The above example is incorrect. I think it should be: tids <- sequence [forkIO (f x y) | f <- funs] Cheers, Krasimir

On 8/31/05, Krasimir Angelov
2005/8/31, Sebastian Sylvan
: On 8/31/05, Dinh Tien Tuan Anh
wrote: Something like (untested)...
xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs
what does "zipWith ($)" do ?
$ is function application, so zipWith ($) will "zip" a list of functions with a list of arguments, by applying the functions to the arguments pair-wise, producing a list of results.
But forkIO is function not a list of functions. The above example is incorrect. I think it should be:
tids <- sequence [forkIO (f x y) | f <- funs]
The following corrects the zipWith example: xs <- zipWith ($) (repeat forkIO) (map (\f -> f x y) funs) tids <- sequence xs -- "50% of marriages today end in divorce, the other 50% end in death. Which would you rather have?"

On 8/31/05, Krasimir Angelov
wrote: 2005/8/31, Sebastian Sylvan
: On 8/31/05, Dinh Tien Tuan Anh
wrote: Something like (untested)...
xs <- zipWith ($) forkIO (map (\f -> f x y) funs) tids <- sequence xs
what does "zipWith ($)" do ?
$ is function application, so zipWith ($) will "zip" a list of functions with a list of arguments, by applying the functions to
Mark Goldman writes: the
arguments pair-wise, producing a list of results.
But forkIO is function not a list of functions. The above example is incorrect. I think it should be:
tids <- sequence [forkIO (f x y) | f <- funs]
The following corrects the zipWith example: xs <- zipWith ($) (repeat forkIO) (map (\f -> f x y) funs) tids <- sequence xs
It's not always obvious when to use sequence or mapM, but I think this
one calls for the latter.
mapM (\f -> forkIO (f x y)) funs :: IO [ThreadId]
If you don't care about the thread IDs, then this is more efficient:
mapM_ (\f -> forkIO (f x y)) funs :: IO ()
--
David Menendez
participants (12)
-
André Vargas Abs da Cruz
-
Arthur Baars
-
Cale Gibbard
-
David Menendez
-
David Roundy
-
Dean Herington
-
Dinh Tien Tuan Anh
-
Glynn Clements
-
Krasimir Angelov
-
Lemmih
-
Mark Goldman
-
Sebastian Sylvan