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

GHC ghc-devs at haskell.org
Fri Dec 6 10:54:25 UTC 2013


#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


More information about the ghc-tickets mailing list