[GHC] #14955: Musings on manual type class desugaring

GHC ghc-devs at haskell.org
Fri Apr 6 13:33:15 UTC 2018


#14955: Musings on manual type class desugaring
-------------------------------------+-------------------------------------
        Reporter:  mpickering        |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.2.2
      Resolution:                    |             Keywords:  SpecConstr
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 (2) is slow becuase we don't (yet) do cross-module !SpecConstr.  If `dors`
 was `INLINEABLE` then in principle !SpecConstr could specialise it in
 `Main`, in a similar way to `Specialise`.  But that is a whole new thing.
 (A very good thing, incidentally: that is Trac #10346.

 (3) jolly well ought to be fast.  That's a bug.  Here is what is
 happening.

 The `INLINABLE` pragma on `pors` (for (3)) or `porsProxy` (for (4)) should
 arrange that these functions can be speicalised in a separate module.  But
 in fact `pors` is worker/wrappered by the demand analyser!  We get this in
 the .hi file:
 {{{
   pors :: PropProxy r => [r] -> r
   {- Arity: 2, HasNoCafRefs,
      Strictness: <S,1*U(C(C1(U)),A,1*U,A)><S,1*U>, Inline: [0],
      Unfolding: InlineRule (2, True, False)
                 (\ @ r (w :: PropProxy r) (w1 :: [r]) ->
                  case w `cast`
                       (N:PropProxy[0] <r>_N) of ww { PropDict ww1 ww2 ww3
 ww4 ->
                  $wpors @ r ww1 ww3 w1 }) -}

   porsProxy :: PropProxy2 r => [r] -> r
   {- Arity: 2, HasNoCafRefs,
      Strictness: <S(SL),U(U(C(C1(U)),A,U,A),A)><S,1*U>, Inline:,
      Unfolding(loop-breaker): <stable> (\ @ r
                                           ($dPropProxy2 :: PropProxy2 r)
                                           (ds :: [r]) ->
                                         case ds of wild {
                                           []
                                           -> case propDict2
                                                     @ r
                                                     $dPropProxy2 of wild1
 { PropDict ds1 ds2 ds3 ds4 ->
                                              ds3 }
                                           : o os
                                           -> case propDict2
                                                     @ r
                                                     $dPropProxy2 of wild1
 { PropDict ds1 ds2 ds3 ds4 ->
                                              ds1 o (porsProxy @ r
 $dPropProxy2 os) } }) -}
 }}}

 So `porsProxy` can be specialised in the calling file -- good.  And so
 can `pors` -- but the specialised version of its code is silly, just a
 call to the un-specialised `$wpors`; still a higher order function,
 which is bad bad bad.

 But I fixed this more 6 years ago. See this Note in `WwLib`:
 {{{
 Note [Do not unpack class dictionaries]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 If we have
    f :: Ord a => [a] -> Int -> a
    {-# INLINABLE f #-}
 and we worker/wrapper f, we'll get a worker with an INLINABLE pragma
 (see Note [Worker-wrapper for INLINABLE functions] in WorkWrap), which
 can still be specialised by the type-class specialiser, something like
    fw :: Ord a => [a] -> Int# -> a

 BUT if f is strict in the Ord dictionary, we might unpack it, to get
    fw :: (a->a->Bool) -> [a] -> Int# -> a
 and the type-class specialiser can't specialise that.  An example is
 Trac #6056.

 Moreover, dictionaries can have a lot of fields, so unpacking them can
 increase closure sizes.

 Conclusion: don't unpack dictionaries.
 }}}
 So why isn't this preventing the w/w for `pors`?  Because the bit that
 prevents the unpacking is here:
 {{{
 deepSplitProductType_maybe fam_envs ty
   | let (co, ty1) = topNormaliseType_maybe fam_envs ty
                     `orElse` (mkRepReflCo ty, ty)
   , Just (tc, tc_args) <- splitTyConApp_maybe ty1
   , Just con <- isDataProductTyCon_maybe tc
   , not (isClassTyCon tc)  -- See Note [Do not unpack class dictionaries]
   , let arg_tys = dataConInstArgTys con tc_args
         strict_marks = dataConRepStrictness con
   = Just (con, tc_args, zipEqual "dspt" arg_tys strict_marks, co)
 }}}
 Ha!  We do `topNormaliseType_maybe` before checking `isClassTyCon`.  And
 when the class is a newtype, that `topNormaliseType_maybe` unwraps it.

 It's easy to fix: just move the test earlier.  Patch coming -- but maybe
 after next week when I'm on holiday.

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


More information about the ghc-tickets mailing list