[GHC] #13405: Reimplement unsafeInterleaveIO using runRW#
GHC
ghc-devs at haskell.org
Thu Mar 9 23:47:51 UTC 2017
#13405: Reimplement unsafeInterleaveIO using runRW#
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: dfeuer
Type: task | Status: new
Priority: normal | Milestone: 8.4.1
Component: Core Libraries | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by dfeuer:
Old description:
> Currently, we have
>
> {{{#!hs
> {-# INLINE unsafeInterleaveIO #-}
> unsafeInterleaveIO :: IO a -> IO a
> unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m)
>
> {-# NOINLINE unsafeDupableInterleaveIO #-}
> unsafeDupableInterleaveIO :: IO a -> IO a
> unsafeDupableInterleaveIO (IO m)
> = IO ( \ s -> let
> r = case m s of (# _, res #) -> res
> in
> (# s, r #))
> }}}
>
> This all seems a bit weird from a semantic standpoint, and also seems
> likely to get in the way of the best idea I have so for for converting
> precise exceptions to imprecise ones in unsafe functions.
>
> === The substantial semantic weirdness ===
>
> `unsafeDupableInterleaveIO` takes the current state of the world, `s`,
> and passes it to `m`. But it passes it to `m` at some time when the
> actual real world has most likely moved on! That is, we pass `m` a moment
> of the ''past''. Strange indeed.
>
> === The exception handling matter ===
>
> I would like to separate precise exceptions (thrown using `raiseIO#`)
> from imprecise ones (thrown using `raise#`). In particular, I want to
> offer an operation that catches only precise exceptions. But
> `unsafePerformIO` and `unsafeInterleaveIO` and such need to convert
> precise exceptions into imprecise ones to avoid breaking the more
> aggressive demand analysis of the hypothetical `catchThrowIO`.
>
> === The fix ===
>
> I believe the fix is pretty simple: rather than holding a piece of the
> past in our pocket, start a new timeline:
>
> {{{#!hs
> unsafeDupableInterleaveIO :: IO a -> IO a
> unsafeDupableInterleaveIO (IO m)
> = IO (\ s ->
> (# s, runRW# (\s2 -> case m s2 of (# _, res #) -> res) #))
> }}}
>
> This seems to me to get the point across a lot better, and it ''may''
> even allow us to remove the `NOINLINE`.
New description:
Currently, we have
{{{#!hs
{-# INLINE unsafeInterleaveIO #-}
unsafeInterleaveIO :: IO a -> IO a
unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m)
{-# NOINLINE unsafeDupableInterleaveIO #-}
unsafeDupableInterleaveIO :: IO a -> IO a
unsafeDupableInterleaveIO (IO m)
= IO ( \ s -> let
r = case m s of (# _, res #) -> res
in
(# s, r #))
}}}
This all seems a bit weird from a semantic standpoint, and also seems
likely to get in the way of the best idea I have so for for converting
precise exceptions to imprecise ones in unsafe functions.
=== The substantial semantic weirdness ===
`unsafeDupableInterleaveIO` takes the current state of the world, `s`, and
passes it to `m`. But it passes it to `m` at some time when the actual
real world has most likely moved on! That is, we pass `m` a moment of the
''past''. Strange indeed.
=== The exception handling matter ===
I would like to separate precise exceptions (thrown using `raiseIO#`) from
imprecise ones (thrown using `raise#`). In particular, I want to offer an
operation that catches only precise exceptions. But `unsafePerformIO` and
`unsafeInterleaveIO` and such need to convert precise exceptions into
imprecise ones to avoid breaking the more aggressive demand analysis of
the hypothetical `catchThrowIO`. The most obvious place to do this seems
likely to be `runRW#`, but we need to be sure to use that everywhere we
need the shift.
=== The fix ===
I believe the fix is pretty simple: rather than holding a piece of the
past in our pocket, start a new timeline:
{{{#!hs
unsafeDupableInterleaveIO :: IO a -> IO a
unsafeDupableInterleaveIO (IO m)
= IO (\ s ->
(# s, runRW# (\s2 -> case m s2 of (# _, res #) -> res) #))
}}}
This seems to me to get the point across a lot better, and it ''may'' even
allow us to remove the `NOINLINE`.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13405#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list