[GHC] #5835: Make better use of known dictionaries

GHC ghc-devs at haskell.org
Thu Nov 27 01:35:30 UTC 2014


#5835: Make better use of known dictionaries
-------------------------------------+-------------------------------------
              Reporter:  rl          |            Owner:
                  Type:  feature     |           Status:  new
  request                            |        Milestone:  7.10.1
              Priority:  normal      |          Version:  7.5
             Component:  Compiler    |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:  Runtime     |  Related Tickets:
  performance bug                    |
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
Changes (by thomie):

 * failure:  None/Unknown => Runtime performance bug


Old description:

> Example:
>
> {{{
> data T a where
>   T :: Eq a => a -> T a
>
> foo :: a -> T a -> Bool
> {-# INLINE foo #-}
> foo x = \(T y) -> x == y
>
> appl :: (a -> b) -> a -> b
> {-# NOINLINE appl #-}
> appl f x = f x
>
> bar :: T Int -> Bool
> bar t = appl (foo 42) t
> }}}
>
> GHC generates this for `bar`:
>
> {{{
> bar2 :: Int
> bar2 = I# 42
>
> bar1 :: T Int -> Bool
> bar1 =
>   \ (ds_dhk :: T Int) ->
>     case ds_dhk of _ { T $dEq_agz y_aa4 ->
>     == @ Int $dEq_agz bar2 y_aa4
>     }
>
> bar :: T Int -> Bool
> bar = \ (t_aga :: T Int) -> appl @ (T Int) @ Bool bar1 t_aga
> }}}
>
> Note how it want to get the `Eq` dictionary for `Int` from `T`. But we
> know the `Eq Int` instance without inspecting `T` and `bar` could be
> significantly simplified if we used that.

New description:

 Example:

 {{{
 {-# LANGUAGE GADTs #-}
 module T5835 where

 data T a where
   T :: Eq a => a -> T a

 foo :: a -> T a -> Bool
 {-# INLINE foo #-}
 foo x = \(T y) -> x == y

 appl :: (a -> b) -> a -> b
 {-# NOINLINE appl #-}
 appl f x = f x

 bar :: T Int -> Bool
 bar t = appl (foo 42) t
 }}}

 GHC generates this for `bar`:

 {{{
 bar2 :: Int
 bar2 = I# 42

 bar1 :: T Int -> Bool
 bar1 =
   \ (ds_dhk :: T Int) ->
     case ds_dhk of _ { T $dEq_agz y_aa4 ->
     == @ Int $dEq_agz bar2 y_aa4
     }

 bar :: T Int -> Bool
 bar = \ (t_aga :: T Int) -> appl @ (T Int) @ Bool bar1 t_aga
 }}}

 Note how it want to get the `Eq` dictionary for `Int` from `T`. But we
 know the `Eq Int` instance without inspecting `T` and `bar` could be
 significantly simplified if we used that.

--

Comment:

 Core unchanged in HEAD vs 7.5. To reproduce, use this command:

 `ghc -O2 -ddump-simpl -dsuppress-module-prefixes -dsuppress-idinfo
 T5835.hs`

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


More information about the ghc-tickets mailing list