[Haskell-cafe] Is it safe to use unsafePerformIO here?

Daniel Fischer daniel.is.fischer at web.de
Tue Sep 15 15:13:02 EDT 2009


Am Dienstag 15 September 2009 20:36:06 schrieb Cristiano Paris:
> Hi Cafè,
>
> I've the following problem: I have a (possibly very long) list of
> files on disk. Each file contains some metadata at the beginning and
> continues with a (possibly very large) chunk of data.
>
> Now, the program I'm writing can be run in two modes: either read a
> specific file from the disk and show the whole chunk of data on
> screen, or read all the files' metadata, sort the file list based on
> the metadata, and display a summary of those without reading the chunk
> of data from each file. I've factored out the file access machinery in
> a single module so as to use it indifferently under the two scenarios.
>
> At first, I wrote a piece of code which, in spirit, works like the
> following reduced case:
>
> ------
> module Main where
>
> import System.IO
> import Control.Applicative
> import Data.List
> import Data.Ord
>
> import Debug.Trace
>
> data Bit = Bit { index :: Integer, body :: String }
>
> readBit fn = withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>=
> return . read) <*> readBody
>              where readBody = withFile fn ReadMode $ \h -> do b <-
> hGetContents h
>                                                               seq b $
> trace ("Read body from: " ++ fn) $ return b

Still, the body should be read lazily.
I'm not sure, but the tracing message may be output because of its position.

With

where
    readBody = withFile fn ReadMode $ \h -> do
        b <- hGetContents h
        seq b $ return (trace ("Read body from: " ++ fn) b)

there's no tracing output.
>
> main = do bl <- mapM readBit ["file1.txt","file2.txt"]
>           mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
> ----
>
> which is very expressive as it's written in applicative style.
>
> Each file is like the following:
>
> ---- file1.txt ----
> 1
> foo
> ----
>
> I've created a separate IO action for reading the body in the hope
> that it wouldn't get executed when the file list is sorted. But, to my
> surprise, it didn't work as the trace message gets written for each
> file before the summary is displayed.
>
> Thinking about this, I came to the conclusion that the IO Monad is
> enforcing proper IO ordering so that the IO action for file1's body
> must be executed right before IO action for file2's index one.
>
> If this is true, the only solution that came into my mind was to wrap
> the IO action for reading the body in an unsafePerformIO call. I
> actually ran the program with this modification and it works properly.
>
> So, as using unsafePerformIO is a Great Evil (TM), I'm wondering if
> there's a different way to do this which doesn't rely on retyping body
> as an IO action returning a String, which would break my pure code
> manipulating the files.
>
> My opinion is that using unsafePerformIO here is like ensuring the
> compiler that there're no observable side effects in running the IO
> action for reading the body and that no other side effects would
> impact this IO action.
>
> Thank you for any thoughts.
>
> Cristiano




More information about the Haskell-Cafe mailing list