
"ssqHitNum.txt" contains data as below: 6 7 18 24 30 32 9 4 12 20 25 28 29 16 3 5 11 12 31 32 11 2 9 13 15 19 24 3 5 17 21 25 27 32 14 5 9 15 21 26 31 13 12 16 25 26 27 31 05 ... good_ssq_red:: IO [Int] good_ssq_red = withFile "ssqHitNum.txt" ReadMode (\h -> do { samp <- fmap str2Ints $ hGetContents h; print samp; --without this line, the result will always [1..16] return $ statis samp; }) statis :: [Int] -> [Int] statis samp = take 16 $ map (\(a,b) -> a) $ sortBy (\a b-> if (snd a >= snd b) then LT else GT) $ times4n where times = map (\n -> (foldl (\acc x -> if x==n then acc+1 else acc) 0 samp)) [1..33] times4n = map (\n -> (n,times!!(n-1))) [1..33] Does it mean that the sampe will not be evalued with `print samp` line ? thanks! -- View this message in context: http://www.nabble.com/Lazy-problem---tp26021845p26021845.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello zaxis, Friday, October 23, 2009, 11:15:01 AM, you wrote:
good_ssq_red = withFile "ssqHitNum.txt" ReadMode (\h -> do { samp <- fmap str2Ints $ hGetContents h; print samp; --without this line, the result will always [1..16] return $ statis samp; })
withFile and hGetContents shouldn't be used together. both closes file handle and, here, withFile closes it before hGetContents lazily reads data. it's why you need to force reading with print use readFile instead -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

good_ssq_red:: IO [Int] good_ssq_red =do { samp <- fmap str2Ints $ readFile "ssqHitNum.txt"; return $ statis samp; } It works now ! thank you Bulat Ziganshin-2 wrote:
Hello zaxis,
Friday, October 23, 2009, 11:15:01 AM, you wrote:
good_ssq_red = withFile "ssqHitNum.txt" ReadMode (\h -> do { samp <- fmap str2Ints $ hGetContents h; print samp; --without this line, the result will always [1..16] return $ statis samp; })
withFile and hGetContents shouldn't be used together. both closes file handle and, here, withFile closes it before hGetContents lazily reads data. it's why you need to force reading with print
use readFile instead
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- View this message in context: http://www.nabble.com/Lazy-problem---tp26021845p26022301.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello zaxis, Friday, October 23, 2009, 12:02:57 PM, you wrote: btw, good_ssq_red = fmap (statis.str2Ints) $ readFile "ssqHitNum.txt" or good_ssq_red = (statis.str2Ints) `fmap` readFile "ssqHitNum.txt"
good_ssq_red:: IO [Int] good_ssq_red =do { samp <- fmap str2Ints $ readFile "ssqHitNum.txt"; return $ statis samp; } It works now ! thank you
Bulat Ziganshin-2 wrote:
Hello zaxis,
Friday, October 23, 2009, 11:15:01 AM, you wrote:
good_ssq_red = withFile "ssqHitNum.txt" ReadMode (\h -> do { samp <- fmap str2Ints $ hGetContents h; print samp; --without this line, the result will always [1..16] return $ statis samp; })
withFile and hGetContents shouldn't be used together. both closes file handle and, here, withFile closes it before hGetContents lazily reads data. it's why you need to force reading with print
use readFile instead
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Or good_ssq_red = readFile "ssqHitNum.txt" >>= return . statis . str2Ints I personally prefer this because I like how the >>= illustrates that the result is being fed into "return . statis . str2Ints", but it is a matter of style. :-) Cheers, Greg On Oct 23, 2009, at 1:09 AM, Bulat Ziganshin wrote:
Hello zaxis,
Friday, October 23, 2009, 12:02:57 PM, you wrote:
btw,
good_ssq_red = fmap (statis.str2Ints) $ readFile "ssqHitNum.txt"
or
good_ssq_red = (statis.str2Ints) `fmap` readFile "ssqHitNum.txt"
good_ssq_red:: IO [Int] good_ssq_red =do { samp <- fmap str2Ints $ readFile "ssqHitNum.txt"; return $ statis samp; } It works now ! thank you
Bulat Ziganshin-2 wrote:
Hello zaxis,
Friday, October 23, 2009, 11:15:01 AM, you wrote:
good_ssq_red = withFile "ssqHitNum.txt" ReadMode (\h -> do { samp <- fmap str2Ints $ hGetContents h; print samp; --without this line, the result will always [1..16] return $ statis samp; })
withFile and hGetContents shouldn't be used together. both closes file handle and, here, withFile closes it before hGetContents lazily reads data. it's why you need to force reading with print
use readFile instead
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Bulat Ziganshin
-
Gregory Crosswhite
-
zaxis