[GHC] #9509: No automatic specialization of inlinable imports in 7.8

GHC ghc-devs at haskell.org
Sat Aug 23 05:50:00 UTC 2014


#9509: No automatic specialization of inlinable imports in 7.8
-------------------------------------+-------------------------------------
       Reporter:  dolio              |                   Owner:
           Type:  bug                |                  Status:  new
       Priority:  normal             |               Milestone:
      Component:  Compiler           |                 Version:  7.8.3
       Keywords:                     |        Operating System:
   Architecture:  Unknown/Multiple   |  Unknown/Multiple
     Difficulty:  Unknown            |         Type of failure:  Runtime
     Blocked By:                     |  performance bug
Related Tickets:                     |               Test Case:
                                     |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------
 According to the GHC manual, any uses of an imported definition that is
 overloaded and INLINABLE will automatically cause a SPECIALIZE to be
 generated for those uses, if appropriate. However, this no longer appears
 to be the case in 7.8(.3). Here is a simple test case:

 {{{#!hs
 module A (foo) where

 import Data.IORef

 foo :: Ord a => a -> IO a
 foo x = newIORef x >>= readIORef >>= \y -> case compare x y of LT ->
 return x ; _ -> return y
 {-# INLINABLE foo #-}
 }}}

 {{{#!hs
 module Main (main) where

 import A

 main = foo (5 :: Int) >>= print
 }}}

 `foo` is constructed to be long enough that GHC 7.8.3 will elect to not
 inline it.

 When compiling with 7.6.3, the core contains the following:

 {{{
 Main.$sfoo1
   :: GHC.Types.Int
      -> GHC.Prim.State# GHC.Prim.RealWorld
      -> (# GHC.Prim.State# GHC.Prim.RealWorld, GHC.Types.Int #)
 [GblId,
  Arity=2,
  Caf=NoCafRefs,
  Str=DmdType LL,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=2, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [20 0] 55 30}]
 Main.$sfoo1 =
   \ (x_XkE :: GHC.Types.Int)
     (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) ->
     case GHC.Prim.newMutVar#
            @ GHC.Types.Int @ GHC.Prim.RealWorld x_XkE eta_B1
     of _ { (# ipv_amT, ipv1_amU #) ->
     case GHC.Prim.readMutVar#
            @ GHC.Prim.RealWorld @ GHC.Types.Int ipv1_amU ipv_amT
     of ds1_amJ { (# ipv2_Xn8, ipv3_Xna #) ->
     case x_XkE of wild_axu { GHC.Types.I# x#_axw ->
     case ipv3_Xna of _ { GHC.Types.I# y#_axA ->
     case GHC.Prim.<# x#_axw y#_axA of _ {
       GHC.Types.False -> ds1_amJ;
       GHC.Types.True -> (# ipv2_Xn8, wild_axu #)
     }
     }
     }
     }
     }

 Main.$sfoo :: GHC.Types.Int -> GHC.Types.IO GHC.Types.Int
 [GblId,
  Arity=2,
  Caf=NoCafRefs,
  Str=DmdType LL,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}]
 Main.$sfoo =
   Main.$sfoo1
   `cast` (<GHC.Types.Int>
           -> Sym <(GHC.Types.NTCo:IO <GHC.Types.Int>)>
           :: (GHC.Types.Int
               -> GHC.Prim.State# GHC.Prim.RealWorld
               -> (# GHC.Prim.State# GHC.Prim.RealWorld, GHC.Types.Int #))
                ~#
              (GHC.Types.Int -> GHC.Types.IO GHC.Types.Int))

 ...

 ------ Local rules for imported ids --------
 "SPEC A.foo [GHC.Types.Int]" [ALWAYS]
     forall ($dOrd_sxj :: GHC.Classes.Ord GHC.Types.Int).
       A.foo @ GHC.Types.Int $dOrd_sxj
       = Main.$sfoo
 }}}

 However, in 7.8.3 and newer (I'm actually using 7.9.20140725 for this
 particular output, but 7.8.3 is similar), we see the following:

 {{{
 Main.main1
   :: GHC.Prim.State# GHC.Prim.RealWorld
      -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #)
 [GblId,
  Arity=1,
  Str=DmdType <L,U>,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [0] 100 0}]
 Main.main1 =
   \ (s_aIb :: GHC.Prim.State# GHC.Prim.RealWorld) ->
     case ((A.foo @ GHC.Types.Int GHC.Classes.$fOrdInt Main.main2)
           `cast` (GHC.Types.NTCo:IO[0] <GHC.Types.Int>_R
                   :: GHC.Types.IO GHC.Types.Int
                      ~R# (GHC.Prim.State# GHC.Prim.RealWorld
                           -> (# GHC.Prim.State# GHC.Prim.RealWorld,
 GHC.Types.Int #))))
            s_aIb
     of _ [Occ=Dead] { (# ipv_aIe, ipv1_aIf #) ->
     GHC.IO.Handle.Text.hPutStr2
       GHC.IO.Handle.FD.stdout
       (GHC.Show.$fShowInt_$cshow ipv1_aIf)
       GHC.Types.True
       ipv_aIe
     }
 }}}

 There is no local rules section in 7.8.3. Putting a manual SPECIALIZE
 pragma in the main module generates comparable code to 7.6.3, so it does
 not appear to be a failure at that level. Rather, GHC seems to just not be
 generating the SPECIALIZE equivalent.

 Presumably this is a regression, but even if not, the manual should be
 revised.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9509>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list