
#12972: Missed specialisation opportunity with phantom type class parameter? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I am unsure of my analysis of this code fragment. It seems like we could do a better job optimising `test3`. First the code, then the analysis at the bottom. {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE IncoherentInstances #-} module Foo where data Proxy a = Proxy --type role Phantom phantom nominal class Phantom x a | a -> x where method :: a method1 :: a instance Phantom x (Proxy x) where method = Proxy method1 = Proxy -- This doesn't optimise test3 :: Phantom x (Proxy x) => Proxy x test3 = method -- This does optimise instance Phantom Char Int where method = 5 method1 = 5 test4 :: Phantom x Int => Int test4 = method }}} Here is the relevant part of the core {{{#!hs -- RHS size: {terms: 4, types: 9, coercions: 0} test3 test3 = \ @ x_ayL $dPhantom_ayS -> method $dPhantom_ayS -- RHS size: {terms: 3, types: 5, coercions: 0} test4 test4 = \ @ x_ayz _ -> $cmethod1_az4 }}} In `test4` the dictionary selector `method` is eliminated but in the analogous case `test3` where `x` is used in both arguments then `method` is not specialised. It seems that we could do a similar specialisation and ultimately replace the dictionary with `Proxy` as `x` is phantom. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12972 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler