[Haskell-beginners] A first try

Heinrich Apfelmus apfelmus at quantentunnel.de
Mon Jun 27 09:50:51 CEST 2011


David Place wrote:
> On Jun 26, 2011, at 8:25 AM, Heinrich Apfelmus wrote:
> 
>> What about the combinator
>>
>>  withFile :: FilePath -> (String -> a) -> IO a
>>  withFile name f = bracket (openFile name ReadMode) hClose $ \h ->
>>      evaluate . f =<< hGetContents h
>>
>> ? It gives you the same thing as Iteratees - a way to apply a
>> function to the contents of a file - without the need to rewrite all the
>> existing list functions like map , lines , words , and so on.
> 
> How would you, for instance, implement the program for counting all
> the words in a list of files that Oleg describes in his message?
> 
>> http://okmij.org/ftp/Haskell/Iteratee/Lazy-vs-correct.txt
> 
> Nested calls to withFile would require too many open handles.

Good point, but this actually shows that  withFile  should be even 
lazier. In particular:

* The file should not be opened until the string is demanded.
* The file should be closed as soon as the string has been demanded in full.

As before, the idea is that resource usage is pushed into the 
operational semantics and file handles are treated as if they were 
ordinary lazy values. It's just that the operating system doesn't play 
along very well and demands explicit resource management.

Again, let me stress that the biggest drawback of the Iteratee approach 
is that you have to rewrite the consumer and cannot reuse ordinary list 
functions like  length , words , lines , and so on. But these functions 
are already lazy, so why not make use of this. (You don't lose anything, 
every Iteratee can be rewritten as an ordinary function  String -> IO a 
  by using  `seq`  in corresponding places.)



Here one possibility for a lazier version of  withFile' :

     -- an even lazier version of  withFile
     withFile' :: FilePath -> (String -> IO a) -> IO a
     withFile' name f = do
         fin <- newIORef (return ())
         let
             close = readIORef fin >>= id
             open  = do
                 putStrLn "open"
                 h <- openFile name ReadMode
                 writeIORef fin (do putStrLn "close"; hClose h)
                 lazyRead h
         finally (unsafeInterleaveIO open >>= f >>= evaluate) close

         where
         lazyRead h = hIsEOF h >>= \b ->
             if b
                 then do putStrLn "close"; hClose h; return []
                 else do
                     c  <- hGetChar h
                     cs <- unsafeInterleaveIO $ lazyRead h
                     return (c:cs)

     withFiles :: [FilePath] -> (String -> IO a) -> IO a
     withFiles [x]    f = withFile' x f
     withFiles (x:xs) f = withFile' x $ \s ->
         let f' t = f (s ++ t) in withFiles xs f'


     test = withFiles (replicate 200 "Test.hs") (return . length)
            >>= print



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com




More information about the Beginners mailing list