[GHC] #8598: IO hack in demand analyzer gets in the way of CPR

Simon Peyton-Jones simonpj at microsoft.com
Fri Dec 6 14:27:16 UTC 2013


Well spotted.  I'm on a train, hence email response.  Maybe you can paste this into the ticket?

There are two different issues here.

'''First''', `isDoubleFinite` is declared as non-side-effecting:
{{{
foreign import ccall unsafe "isDoubleFinite" isDoubleFinite :: Double -> Int
}}}
But (as you can see from the code you give) we currently desugar it into something that looks (to Core) as though it might have a side effect, or raise a (synchronous) exception.  That is stupid.  

How might we fix that?  I can think of two ways. 
 * Generate a `FCallId` whose type is `Double -> Int` rather than (as now) `Double -> IO Int`.  There would be a few knock-on consequences to make sure they were correctly code-generated.  I like this path best, because it reflects the truth.

 * Currently
{{{ 
IO a = State# RealWorld# -> (# State# RealWorld#, a #)
}}}
  For these non-side-effecting things we could instead generate a `FCallId` with a type involving `SafeIO` instead of `IO`:
{{{
SafeIO a = State# SafeWorld# -> (# State# SafeWorld#, a #)
}}}
  The different "world token" would express the idea that the function can't throw an exception.  

  I don't like this as much, but it might in any case be useful for things that ''do'' have side effects but ''don't'' throw exceptions.

My preference is for the first.

'''Second''', as you point out, consider
{{{
   f x = do { when (x>3) exit
            ; return (True, False) }
}}}
Function `f` might throw an exception or exit rather than returning, but ''if it does return'' it will certainly have the CPR property.  So yes, CPR-ness is quite safe. 

It's not quite so obvious for divergence:
{{{
   g x = do { when (x>3) exit
            ; g x }

   h 0 y = y
   h x y = g x
}}}
Is `h` strict in `y`?  You might say (reasonably) that we can ignore the possible IO exception/exit in `g` when figuring out that `g` is sure to diverge. If so, we'd say that `h` is strict in `y`.  But if `(x>3)` then really `y` is not evaluated... and spotting that is exactly what the IO hack in the demand analyser is spotting.  So I think it is ''not'' safe to propagate divergence information.

In short, CPR info yes, guaranteed-divergence no.

Simon

| -----Original Message-----
| From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf Of
| GHC
| Sent: 06 December 2013 10:54
| Cc: ghc-tickets at haskell.org
| Subject: [GHC] #8598: IO hack in demand analyzer gets in the way of CPR
| 
| #8598: IO hack in demand analyzer gets in the way of CPR
| ------------------------------------+----------------------------------
| ---
|        Reporter:  nomeata           |             Owner:
|            Type:  task              |            Status:  new
|        Priority:  normal            |         Milestone:
|       Component:  Compiler          |           Version:  7.6.3
|        Keywords:                    |  Operating System:
| Unknown/Multiple
|    Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
|      Difficulty:  Unknown           |         Test Case:
|      Blocked By:                    |          Blocking:
| Related Tickets:                    |
| ------------------------------------+----------------------------------
| ---
|  After a lot of staring at code and comparing unexpected nofib results
| I
|  found the following:
| 
|  The IO hack in the demand analyzer (see `dmdAnalAlt` in `StrAnal.lhs`
| and
|  #1592 for a good discussion) prevents CPR in any function that uses a
| C
|  call. This is a small example, reduced from the `scaleFloat` method
| for
|  doubles:
| 
|  {{{
|  module Float(fun) where
| 
|  import GHC.Float (Double(..))
|  import GHC.Integer (decodeDoubleInteger, encodeDoubleInteger)
| 
|  fun :: Double -> Double
|  fun x | isFix           = x
|        | otherwise       = case x of
|            (D# x#) -> case decodeDoubleInteger x# of
|              (# i, j #) -> D# (encodeDoubleInteger i j)
|    where
|    isFix = isDoubleFinite x == 0
| 
|  foreign import ccall unsafe "isDoubleFinite" isDoubleFinite :: Double
| ->
|  Int
|  }}}
| 
|  Here, `fun` does current not get the CPR property, and the work gets
| type
|  `GHC.Prim.Double# -> GHC.Types.Double`. Why? Because in core, there
| will
|  be a
|  {{{
|      case {__pkg_ccall main isDoubleFinite GHC.Prim.Double#
|                                   -> GHC.Prim.State# GHC.Prim.RealWorld
|                                   -> (# GHC.Prim.State#
| GHC.Prim.RealWorld,
|  GHC.Prim.Int# #)}_dQD
|             ds_dQA GHC.Prim.realWorld#
|      of _ [Occ=Dead, Dmd=<L,A>]
|      { (# ds_dQC [Dmd=<L,A>, OS=OneShot], ds_dQB [Dmd=<S,1*U>] #) ->
|        ...
|  }}}
|  where the case body has `DmdType m {dQz-><L,1*U(U)> dQA-><L,U>}`, but
|  `dmdAnalAlt` detects that this is evaluating a possibly exiting
| function
|  and throws aways the information using `alt_ty `lubDmdType`
| topDmdType`.
| 
|  Would it be ok to `lub` only the demand on the free variables, but
| keep
|  the CPR information?
| 
|  In nofib (if I managed to compare the right results) this does nothing
| for
|  almost all benchmarks, `-9.2%` of allocations for `mandel` and `+4.9%`
| for
|  reverse-complement (but these numbers are not obtained very cleanly,
| and
|  all is happening on top of the better-ho-cardinality branch.
| 
| --
| Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8598>
| GHC <http://www.haskell.org/ghc/>
| The Glasgow Haskell Compiler
| _______________________________________________
| ghc-tickets mailing list
| ghc-tickets at haskell.org
| http://www.haskell.org/mailman/listinfo/ghc-tickets


More information about the ghc-devs mailing list