Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/d8d65a2939fbbab478c895de5f432cb0da869709

>---------------------------------------------------------------

commit d8d65a2939fbbab478c895de5f432cb0da869709
Author: Simon Peyton Jones <[email protected]>
Date:   Sat Jun 11 14:21:26 2011 +0100

    Without -O do not complain about SPECIALISE pragmas for non-INLINABLE things
    
    Otherwise Haddock (which compiles stuff without -O) falls over

>---------------------------------------------------------------

 compiler/typecheck/TcBinds.lhs |   21 +++++++++++++++++----
 1 files changed, 17 insertions(+), 4 deletions(-)

diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs
index 2eefb8c..881c304 100644
--- a/compiler/typecheck/TcBinds.lhs
+++ b/compiler/typecheck/TcBinds.lhs
@@ -555,11 +555,20 @@ tcSpec _ prag = pprPanic "tcSpec" (ppr prag)
 
 --------------
 tcImpPrags :: [LSig Name] -> TcM [LTcSpecPrag]
+-- SPECIALISE pragamas for imported things
 tcImpPrags prags
   = do { this_mod <- getModule
-       ; mapAndRecoverM (wrapLocM tcImpSpec) 
-         [L loc (name,prag) | (L loc prag@(SpecSig (L _ name) _ _)) <- prags
-                            , not (nameIsLocalOrFrom this_mod name) ] }
+       ; dflags <- getDOpts
+       ; if not (dopt Opt_Specialise dflags) then
+            return []    -- Ignore SPECIALISE pragmas for imported things
+                        -- when -O is not on; otherwise we get bogus 
+                        -- complaints about lack of INLINABLE pragmas 
+                        -- in the imported module (also compiled without -O)
+                        -- Notably, when Haddocking the base library
+         else
+            mapAndRecoverM (wrapLocM tcImpSpec) 
+            [L loc (name,prag) | (L loc prag@(SpecSig (L _ name) _ _)) <- prags
+                               , not (nameIsLocalOrFrom this_mod name) ] }
 
 tcImpSpec :: (Name, Sig Name) -> TcM TcSpecPrag
 tcImpSpec (name, prag)
@@ -572,7 +581,11 @@ impSpecErr :: Name -> SDoc
 impSpecErr name
   = hang (ptext (sLit "You cannot SPECIALISE") <+> quotes (ppr name))
        2 (vcat [ ptext (sLit "because its definition has no INLINE/INLINABLE 
pragma")
-               , ptext (sLit "(or you compiled its defining module without 
-O)")])
+               , parens $ sep 
+                   [ ptext (sLit "or its defining module") <+> quotes (ppr mod)
+                   , ptext (sLit "was compiled without -O")]])
+  where
+    mod = nameModule name
 
 --------------
 tcVectDecls :: [LVectDecl Name] -> TcM ([LVectDecl TcId])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to