[GHC] #12791: Superclass methods could be more aggressively specialised.
GHC
ghc-devs at haskell.org
Mon Oct 31 20:54:39 UTC 2016
#12791: Superclass methods could be more aggressively specialised.
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by mpickering:
@@ -2,2 +2,3 @@
- If this type variable is fixed then we know that we are going to use the
- specific dictionary. Thus, the optimiser *could* specialise all methods
+ If this type variable is fixed then we know that we are going to use a
+ specific instance for `R`. Thus, the optimiser *could* specialise all
+ methods
New description:
Say `R` is a superclass of `MR` but only uses one of the type variables.
If this type variable is fixed then we know that we are going to use a
specific instance for `R`. Thus, the optimiser *could* specialise all
methods
from the superclass at this point leading to better code.
{{{#!hs
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
module Foo where
class R t => MR t m where
push :: t -> m -> Int
class R t where
pull :: t -> Int
--type MR2 t m = (R t, MR t m)
instance MR Int Int where
push = max
instance R Int where
pull = negate
myf :: (MR Int a) => a -> Int -> Int
myf _ = pull
}}}
To give a concrete example, `R` is a super class of `MR` but only mentions
the first type variable. Thus when we fix it in `myf`, we could optimise
the definition to `myf _ = negate` by inlining the class method.
Reid points out that if you have a definition like
{{{
data X = X
f :: R X => Int -> Int
f = pull
}}}
then the instance for `R X` could be provided by another module. However
it is common to structure large applications with super class constraints
so it would be desirable to do better.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12791#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list