[GHC] #6056: INLINABLE pragma prevents worker-wrapper to happen.

GHC ghc-devs at haskell.org
Thu Mar 27 17:26:45 UTC 2014


#6056: INLINABLE pragma prevents worker-wrapper to happen.
--------------------------------------------+------------------------------
        Reporter:  milan                    |            Owner:  simonpj
            Type:  bug                      |           Status:  new
        Priority:  normal                   |        Milestone:  7.8.1
       Component:  Compiler                 |          Version:  7.4.1
      Resolution:                           |         Keywords:
Operating System:  Unknown/Multiple         |     Architecture:
 Type of failure:  Runtime performance bug  |  Unknown/Multiple
       Test Case:                           |       Difficulty:  Unknown
        Blocking:                           |       Blocked By:
                                            |  Related Tickets:
--------------------------------------------+------------------------------

Comment (by carter):

 I tested this just now  on current HEAD (well, built 2 weeks ago)

 here are the three versions

 {{{
 module Test where

 smallerAndRest :: Ord a => a -> [a] -> (Maybe a, [a])
 smallerAndRest x [] = (Nothing, [])
 smallerAndRest x (y:ys) | y < x = (Just y, ys)
                         | otherwise = smallerAndRest x ys

 {-# INLINABLE smallerAndRest #-}

 smallerAndRestGood :: Ord a => a -> [a] -> (Maybe a, [a])
 smallerAndRestGood x ys = go  x ys
     where
         go  x [] = (Nothing, [])
         go x (y:ys)  | y < x = (Just y, ys)
                         | otherwise = go x ys

 {-# INLINABLE smallerAndRestGood #-}


 smallerAndRestGoodNotInlined :: Ord a => a -> [a] -> (Maybe a, [a])
 smallerAndRestGoodNotInlined x ys = go  x ys
     where
         go  x [] = (Nothing, [])
         go x (y:ys)  | y < x = (Just y, ys)
                         | otherwise = go x ys


 }}}

 i used
 {{{
 ghc  -O1 -ddump-prep test.hs -fforce-recomp
 }}}

 with the following results

 {{{
 ==================== CorePrep ====================
 Result size of CorePrep = {terms: 123, types: 192, coercions: 0}

 lvl_r10X :: forall a_aTr. (Data.Maybe.Maybe a_aTr, [a_aTr])
 [GblId, Caf=NoCafRefs, Str=DmdType m, Unf=OtherCon []]
 lvl_r10X =
   \ (@ a_aTr) -> (Data.Maybe.Nothing @ a_aTr, GHC.Types.[] @ a_aTr)

 Rec {
 Test.smallerAndRest [InlPrag=INLINABLE[ALWAYS], Occ=LoopBreaker]
   :: forall a_aDK.
      GHC.Classes.Ord a_aDK =>
      a_aDK -> [a_aDK] -> (Data.Maybe.Maybe a_aDK, [a_aDK])
 [GblId,
  Arity=3,
  Caf=NoCafRefs,
  Str=DmdType <L,U(A,A,C(C1(U)),A,A,A,A,A)><L,U><S,1*U>m,
  Unf=OtherCon []]
 Test.smallerAndRest =
   \ (@ a_aTr)
     ($dOrd_s17b :: GHC.Classes.Ord a_aTr)
     (x_s17c :: a_aTr)
     (ds_s17d [Occ=Once!] :: [a_aTr]) ->
     case ds_s17d of _ [Occ=Dead] {
       [] -> lvl_r10X @ a_aTr;
       : y_s17f ys_s17g [Occ=Once*] ->
         case GHC.Classes.< @ a_aTr $dOrd_s17b y_s17f x_s17c
         of _ [Occ=Dead] {
           GHC.Types.False ->
             Test.smallerAndRest @ a_aTr $dOrd_s17b x_s17c ys_s17g;
           GHC.Types.True ->
             let {
               sat_s17i [Occ=Once] :: Data.Maybe.Maybe a_aTr
               [LclId, Str=DmdType]
               sat_s17i = Data.Maybe.Just @ a_aTr y_s17f } in
             (sat_s17i, ys_s17g)
         }
     }
 end Rec }

 Test.smallerAndRestGood [InlPrag=INLINABLE[ALWAYS]]
   :: forall a_aDJ.
      GHC.Classes.Ord a_aDJ =>
      a_aDJ -> [a_aDJ] -> (Data.Maybe.Maybe a_aDJ, [a_aDJ])
 [GblId,
  Arity=3,
  Caf=NoCafRefs,
  Str=DmdType <L,U(A,A,C(C1(U)),A,A,A,A,A)><L,U><S,1*U>m,
  Unf=OtherCon []]
 Test.smallerAndRestGood =
   \ (@ a_aTb)
     ($dOrd_s17j :: GHC.Classes.Ord a_aTb)
     (x_s17k [Occ=Once] :: a_aTb)
     (ys_s17l [Occ=Once] :: [a_aTb]) ->
     let {
       lvl1_s17m [Occ=OnceL!] :: a_aTb -> a_aTb -> GHC.Types.Bool
       [LclId, Str=DmdType]
       lvl1_s17m = GHC.Classes.< @ a_aTb $dOrd_s17j } in
     letrec {
       $wgo_s17n [Occ=LoopBreaker]
         :: a_aTb -> [a_aTb] -> (# Data.Maybe.Maybe a_aTb, [a_aTb] #)
       [LclId, Arity=2, Str=DmdType <L,U><S,1*U>, Unf=OtherCon []]
       $wgo_s17n =
         \ (w_s17o :: a_aTb) (w1_s17p [Occ=Once!] :: [a_aTb]) ->
           case w1_s17p of _ [Occ=Dead] {
             [] -> (# Data.Maybe.Nothing @ a_aTb, GHC.Types.[] @ a_aTb #);
             : y_s17r ys1_s17s [Occ=Once*] ->
               case lvl1_s17m y_s17r w_s17o of _ [Occ=Dead] {
                 GHC.Types.False -> $wgo_s17n w_s17o ys1_s17s;
                 GHC.Types.True ->
                   let {
                     sat_s17u [Occ=Once] :: Data.Maybe.Maybe a_aTb
                     [LclId, Str=DmdType]
                     sat_s17u = Data.Maybe.Just @ a_aTb y_s17r } in
                   (# sat_s17u, ys1_s17s #)
               }
           }; } in
     case $wgo_s17n x_s17k ys_s17l
     of _ [Occ=Dead] { (# ww1_s17w [Occ=Once], ww2_s17x [Occ=Once] #) ->
     (ww1_s17w, ww2_s17x)
     }

 Test.$wsmallerAndRestGoodNotInlined
   :: forall a_aql.
      GHC.Classes.Ord a_aql =>
      a_aql -> [a_aql] -> (# Data.Maybe.Maybe a_aql, [a_aql] #)
 [GblId,
  Arity=3,
  Caf=NoCafRefs,
  Str=DmdType <L,U(A,A,C(C1(U)),A,A,A,A,A)><L,U><S,1*U>,
  Unf=OtherCon []]
 Test.$wsmallerAndRestGoodNotInlined =
   \ (@ a_aql)
     (w_s17y :: GHC.Classes.Ord a_aql)
     (w1_s17z [Occ=Once] :: a_aql)
     (w2_s17A [Occ=Once] :: [a_aql]) ->
     let {
       lvl1_s17B [Occ=OnceL!] :: a_aql -> a_aql -> GHC.Types.Bool
       [LclId, Str=DmdType]
       lvl1_s17B = GHC.Classes.< @ a_aql w_s17y } in
     letrec {
       $wgo_s17C [Occ=LoopBreaker]
         :: a_aql -> [a_aql] -> (# Data.Maybe.Maybe a_aql, [a_aql] #)
       [LclId, Arity=2, Str=DmdType <L,U><S,1*U>, Unf=OtherCon []]
       $wgo_s17C =
         \ (w3_s17D :: a_aql) (w4_s17E [Occ=Once!] :: [a_aql]) ->
           case w4_s17E of _ [Occ=Dead] {
             [] -> (# Data.Maybe.Nothing @ a_aql, GHC.Types.[] @ a_aql #);
             : y_s17G ys_s17H [Occ=Once*] ->
               case lvl1_s17B y_s17G w3_s17D of _ [Occ=Dead] {
                 GHC.Types.False -> $wgo_s17C w3_s17D ys_s17H;
                 GHC.Types.True ->
                   let {
                     sat_s17J [Occ=Once] :: Data.Maybe.Maybe a_aql
                     [LclId, Str=DmdType]
                     sat_s17J = Data.Maybe.Just @ a_aql y_s17G } in
                   (# sat_s17J, ys_s17H #)
               }
           }; } in
     $wgo_s17C w1_s17z w2_s17A

 Test.smallerAndRestGoodNotInlined [InlPrag=INLINE[0]]
   :: forall a_aql.
      GHC.Classes.Ord a_aql =>
      a_aql -> [a_aql] -> (Data.Maybe.Maybe a_aql, [a_aql])
 [GblId,
  Arity=3,
  Caf=NoCafRefs,
  Str=DmdType <L,U(A,A,C(C1(U)),A,A,A,A,A)><L,U><S,1*U>m,
  Unf=OtherCon []]
 Test.smallerAndRestGoodNotInlined =
   \ (@ a_aql)
     (w_s17K [Occ=Once] :: GHC.Classes.Ord a_aql)
     (w1_s17L [Occ=Once] :: a_aql)
     (w2_s17M [Occ=Once] :: [a_aql]) ->
     case Test.$wsmallerAndRestGoodNotInlined
            @ a_aql w_s17K w1_s17L w2_s17M
     of _ [Occ=Dead] { (# ww1_s17O [Occ=Once], ww2_s17P [Occ=Once] #) ->
     (ww1_s17O, ww2_s17P)
     }


 }}}


 this seems to hint that doing worker wrapper by hand works, whether or not
 you marked it INLINEABLE.

 (i don't know enough about this topic to judge if that means its resolved
 or still a problem mind you)

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


More information about the ghc-tickets mailing list