[Haskell-cafe] Does inlinePerformIO = unsafePerformIO . unsafeInterleaveIO semantically?

Duncan Coutts duncan.coutts at worc.ox.ac.uk
Sun Mar 18 07:02:13 EDT 2007


On Sun, 2007-03-18 at 05:48 -0400, Isaac Dupree wrote: 
> -----BEGIN PGP SIGNED MESSAGE-----
> Hash: SHA1
> 
> Compare the guarantees (in practice and/or theoretically) of
> inlinePerformIO
> and
> unsafePerformIO . unsafeInterleaveIO  (i.e. function composition)
> (aside from inlinePerformIO being better optimized). Are they the same,
> or if not, what do they mean - what are the differences?

I think unsafePerformIO . unsafeInterleaveIO = unsafePerformIO

and semantically inlinePerformIO = unsafePerformIO
in as much as either of those have any semantics at all.

The difference of course is that inlinePerformIO is even less safe than
unsafePerformIO. While ghc will try not to duplicate or common up
different uses of unsafePerformIO, we aggressively inline
inlinePerformIO. So you can really only use it where the IO content is
really properly pure, like reading from an immutable memory buffer (as
in the case of ByteStrings). However things like allocating new buffers
should not be done inside inlinePerformIO since that can easily be
floated out and performed just once for the whole program, so you end up
with many things sharing the same buffer, which would be bad.

So the rule of thumb is that IO things wrapped in unsafePerformIO have
to be exernally pure while with inlinePerformIO it has to be really
really pure or it'll all go horribly wrong.

That said, here's some really hairy code. This should frighten any pure
functional programmer...

write :: Int -> (Ptr Word8 -> IO ()) -> Put ()
write !n body = Put $ \c buf@(Buffer fp o u l) ->
  if n <= l
    then write' c fp o u l
    else write' (flushOld c n fp o u) (newBuffer c n) 0 0 0

  where {-# NOINLINE write' #-}
        write' c !fp !o !u !l =
          -- warning: this is a tad hardcore
          inlinePerformIO
            (withForeignPtr fp
              (\p -> body $! (p `plusPtr` (o+u))))
          `seq` c () (Buffer fp o (u+n) (l-n))

it's used like:
word8 w = write 1 (\p -> poke p w)

This does not adhere to my rule of thumb above. Don't ask exactly why we
claim it's safe :-) (and if anyone really wants to know, ask Ross
Paterson who did it first in the Builder monoid)

Duncan



More information about the Haskell-Cafe mailing list