problems with working with Handles
Dean Herington
heringto@cs.unc.edu
Fri, 13 Jun 2003 10:34:53 -0400
Niels Reyngoud wrote:
> Hello all,
>
> Thanks for your replies on our previous posts. To avoid the lazy
> behaviour, we tried to write our own IO module "IOExts2" which basically
> redifnes
> readFile, writeFile and appendFile to make sure they use binary-mode and
> strict behaviour. The libary is as follows:
>
> ----------
> module IOExts2(readFile', writeFile', appendFile') where
>
> import IO
> import IOExts
>
> readFile' :: String -> IO String
> readFile' inputfile = do readhandle <- openFileEx inputfile (BinaryMode
> ReadMode)
> x <- hGetContents readhandle
> seq x (return x)
> {- seq x (do hClose readhandle
> return x) -}
`seq` guarantees only enough evaluation to determine whether its first
argument is bottom. That's why your commented code reads only the first
character. You need to evaluate the entire string. As someone else
suggested, `deepSeq` is one way to do this. I've appended the current
version of my DeepSeq module to this reply.
> writeFile' :: String -> String -> IO()
> writeFile' outputfile text = seq text (writeFile'' outputfile text)
>
> writeFile'' :: String -> String -> IO()
> writeFile'' outputfile text = do writehandle <- openFileEx outputfile
> (BinaryMode WriteMode)
> hPutStr writehandle text
> hFlush writehandle
> hClose writehandle
>
> appendFile' :: String -> String -> IO()
> appendFile' outputfile text = seq text (appendFile'' outputfile text)
>
> appendFile'' :: String -> String -> IO()
> appendFile'' outputfile text = do appendhandle <- openFileEx outputfile
> (BinaryMode AppendMode)
> hPutStr appendhandle text
> hFlush appendhandle
> hClose appendhandle
Output is not done lazily, so use of `seq` in the above is superfluous.
> ---------------
>
> Yet, there's still one problem left with readFile'. The handles of
> appendFile' and writeFile' are properly closed, but when I try to close
> the handle used for reading (as shown by the parts
> commented above) and try the following small test, which uses a file
> "123.txt" that consists of the string "blaat" only a "b" is outputted.
> When I do not close the handle, the entire string "blaat" is outputted.
>
> test = do x <- readFile' "123.txt"
> putStr x
>
> Regards,
> Niels Reyngoud
DeepSeq.lhs -- deep strict evaluation support
The `DeepSeq` class provides a method `deepSeq` that is similar to
`seq` except that it forces deep evaluation of its first argument
before returning its second argument.
Instances of `DeepSeq` are provided for Prelude types. Other
instances must be supplied by users of this module.
$Id: DeepSeq.lhs,v 1.5 2002/04/01 20:58:24 heringto Exp $
> module DeepSeq where
> class DeepSeq a where deepSeq :: a -> b -> b
> infixr 0 `deepSeq`, $!!
> ($!!) :: (DeepSeq a) => (a -> b) -> a -> b
> f $!! x = x `deepSeq` f x
> instance DeepSeq () where deepSeq = seq
> instance DeepSeq Bool where deepSeq = seq
> instance DeepSeq Char where deepSeq = seq
> instance (DeepSeq a) => DeepSeq (Maybe a) where
> deepSeq Nothing y = y
> deepSeq (Just x) y = deepSeq x y
> instance (DeepSeq a, DeepSeq b) => DeepSeq (Either a b) where
> deepSeq (Left a) y = deepSeq a y
> deepSeq (Right b) y = deepSeq b y
> instance DeepSeq Ordering where deepSeq = seq
> instance DeepSeq Int where deepSeq = seq
> instance DeepSeq Integer where deepSeq = seq
> instance DeepSeq Float where deepSeq = seq
> instance DeepSeq Double where deepSeq = seq
> instance DeepSeq (a -> b) where deepSeq = seq
> instance DeepSeq (IO a) where deepSeq = seq
> instance (DeepSeq a) => DeepSeq [a] where
> deepSeq [] y = y
> deepSeq (x:xs) y = deepSeq x $ deepSeq xs y
> instance (DeepSeq a,DeepSeq b) => DeepSeq (a,b) where
> deepSeq (a,b) y = deepSeq a $ deepSeq b y
> instance (DeepSeq a,DeepSeq b,DeepSeq c) => DeepSeq (a,b,c) where
> deepSeq (a,b,c) y = deepSeq a $ deepSeq b $ deepSeq c y
> instance (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d) => DeepSeq (a,b,c,d)
where
> deepSeq (a,b,c,d) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d y
> instance (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e) => DeepSeq
(a,b,c,d,e) where
> deepSeq (a,b,c,d,e) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d $ deepSeq e y
> instance (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e,DeepSeq f) =>
DeepSeq (a,b,c,d,e,f) where
> deepSeq (a,b,c,d,e,f) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d $ deepSeq e $ deepSeq f y
> instance (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e,DeepSeq
f,DeepSeq g) => DeepSeq (a,b,c,d,e,f,g) where
> deepSeq (a,b,c,d,e,f,g) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d $ deepSeq e $ deepSeq f $ deepSeq g y
--end--