[GHC] #14790: eqTypeRep does not inline

GHC ghc-devs at haskell.org
Sun Feb 11 10:06:14 UTC 2018


#14790: eqTypeRep does not inline
-------------------------------------+-------------------------------------
           Reporter:  dfeuer         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.1-alpha2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Runtime
  Unknown/Multiple                   |  performance bug
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 GHC never seems to inline `eqTypeRep`. That's no good! It produces a
 `Maybe`, which users will almost certainly want to match on immediately.

 I really don't understand ''why'' it doesn't inline. It's a tiny function,
 none of the functions it calls are themselves marked `INLINE`, and the
 advantage to inlining seems obvious. Does the `unsafeCoerce` get in the
 way somehow? If so, how can we fix it?

 Example:

 {{{#!hs
 {-# language GADTs, ScopedTypeVariables, TypeApplications #-}
 module Foo where
 import Type.Reflection

 foo :: forall proxy a. Typeable a => proxy a -> Bool
 foo _ = case eqTypeRep (typeRep @a) (typeRep @Int) of
           Just _ -> True
           Nothing -> False

 }}}

 compiles (with `-O2`) to

 {{{
 foo
   = \ (@ (proxy_a6tT :: * -> *))
       (@ a_a6tU)
       ($dTypeable_a6tW :: Typeable a_a6tU) ->
       let {
         lvl_s6Sc :: Maybe (a_a6tU :~~: Int)
         [LclId]
         lvl_s6Sc
           = eqTypeRep
               @ *
               @ *
               @ a_a6tU
               @ Int
               ($dTypeable_a6tW
                `cast` (base-4.11.0.0:Data.Typeable.Internal.N:Typeable[0]
 <*>_N <a_a6tU>_N
                        :: (Typeable a_a6tU :: Constraint) ~R# (TypeRep
 a_a6tU :: *)))
               Foo.foo1 } in
       \ _ [Occ=Dead] ->
         case lvl_s6Sc of {
           Nothing -> GHC.Types.False;
           Just ds1_d6Rq -> GHC.Types.True
         }
 }}}

 For reference, `eqTypeRep` is defined like this:

 {{{#!hs
 eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2).
              TypeRep a -> TypeRep b -> Maybe (a :~~: b)
 eqTypeRep a b
   | typeRepFingerprint a == typeRepFingerprint b = Just (unsafeCoerce
 HRefl)
   | otherwise                                    = Nothing
 }}}

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


More information about the ghc-tickets mailing list