[commit: ghc] master: Do not complain about SPECIALISE for INLINE (617f696)
git at git.haskell.org
git at git.haskell.org
Wed Aug 5 13:25:06 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/617f6966b5aaedd3ecd3f4c0f3735253187b7ff5/ghc
>---------------------------------------------------------------
commit 617f6966b5aaedd3ecd3f4c0f3735253187b7ff5
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Aug 5 13:38:20 2015 +0100
Do not complain about SPECIALISE for INLINE
Fixes Trac #10721.
See Note [SPECIALISE on INLINE functions]
>---------------------------------------------------------------
617f6966b5aaedd3ecd3f4c0f3735253187b7ff5
compiler/deSugar/DsBinds.hs | 25 +++++++++++++++++--------
1 file changed, 17 insertions(+), 8 deletions(-)
diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs
index b6edf7c..55c82dd 100644
--- a/compiler/deSugar/DsBinds.hs
+++ b/compiler/deSugar/DsBinds.hs
@@ -67,9 +67,7 @@ import Bag
import BasicTypes hiding ( TopLevel )
import DynFlags
import FastString
-import ErrUtils( MsgDoc )
import Util
-import Control.Monad( when )
import MonadUtils
import Control.Monad(liftM)
import Fingerprint(Fingerprint(..), fingerprintString)
@@ -460,8 +458,10 @@ dsSpec mb_poly_rhs (L loc (SpecPrag poly_id spec_co spec_inl))
; spec_rhs <- dsHsWrapper spec_co poly_rhs
- ; when (isInlinePragma id_inl && wopt Opt_WarnPointlessPragmas dflags)
- (warnDs (specOnInline poly_name))
+-- Commented out: see Note [SPECIALISE on INLINE functions]
+-- ; when (isInlinePragma id_inl)
+-- (warnDs $ ptext (sLit "SPECIALISE pragma on INLINE function probably won't fire:")
+-- <+> quotes (ppr poly_name))
; return (Just (unitOL (spec_id, spec_rhs), rule))
-- NB: do *not* use makeCorePair on (spec_id,spec_rhs), because
@@ -503,11 +503,20 @@ dsSpec mb_poly_rhs (L loc (SpecPrag poly_id spec_co spec_inl))
| otherwise = spec_prag_act -- Specified by user
-specOnInline :: Name -> MsgDoc
-specOnInline f = ptext (sLit "SPECIALISE pragma on INLINE function probably won't fire:")
- <+> quotes (ppr f)
-{-
+{- Note [SPECIALISE on INLINE functions]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We used to warn that using SPECIALISE for a function marked INLINE
+would be a no-op; but it isn't! Especially with worker/wrapper split
+we might have
+ {-# INLINE f #-}
+ f :: Ord a => Int -> a -> ...
+ f d x y = case x of I# x' -> $wf d x' y
+
+We might want to specialise 'f' so that we in turn specialise '$wf'.
+We can't even /name/ '$wf' in the source code, so we can't specialise
+it even if we wanted to. Trac #10721 is a case in point.
+
Note [Activation pragmas for SPECIALISE]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
From a user SPECIALISE pragma for f, we generate
More information about the ghc-commits
mailing list