[commit: ghc] master: Warn if you use ANN annotations with a stage-1 compiler (Trac #4268) (6c1aba4)

git at git.haskell.org git at git.haskell.org
Tue Nov 12 15:07:33 UTC 2013


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6c1aba4ff27371fddfc0dce5f9256c97edf16eea/ghc

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

commit 6c1aba4ff27371fddfc0dce5f9256c97edf16eea
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Nov 11 08:52:51 2013 +0000

    Warn if you use ANN annotations with a stage-1 compiler (Trac #4268)
    
    This makes us give a civilised warning when we hit an
      {-# ANN f foo #-}
    pragma in a stage-1 compiler.
    
    We decided that, since it's a pragma, it does not need a language
    extension flag to enable it.


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

6c1aba4ff27371fddfc0dce5f9256c97edf16eea
 compiler/typecheck/TcAnnotations.lhs |   23 +++++++++++++++++++++--
 1 file changed, 21 insertions(+), 2 deletions(-)

diff --git a/compiler/typecheck/TcAnnotations.lhs b/compiler/typecheck/TcAnnotations.lhs
index c25a217..7c72dd7 100644
--- a/compiler/typecheck/TcAnnotations.lhs
+++ b/compiler/typecheck/TcAnnotations.lhs
@@ -7,7 +7,10 @@
 \begin{code}
 module TcAnnotations ( tcAnnotations ) where
 
+#ifdef GHCI
 import {-# SOURCE #-} TcSplice ( runAnnotation )
+import Module
+#endif
 
 import HsSyn
 import Annotations
@@ -16,13 +19,27 @@ import TcRnMonad
 import SrcLoc
 import Outputable
 
-import Module
 import FastString
 \end{code}
 
 \begin{code}
+
+#ifndef GHCI
+
 tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation]
-tcAnnotations = mapM tcAnnotation
+-- No GHCI; emit a warning (not an error) and ignore. cf Trac #4268
+tcAnnotations [] = return []
+tcAnnotations anns@(L loc _ : _)
+  = do { setSrcSpan loc $ addWarnTc $
+             (ptext (sLit "Ignoring ANN annotation") <> plural anns <> comma
+             <+> ptext (sLit "because this is a stage-1 compiler"))
+       ; return [] }
+
+#else
+
+tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation]
+-- GHCI exists, typecheck the annotations
+tcAnnotations anns = mapM tcAnnotation anns
 
 tcAnnotation :: LAnnDecl Name -> TcM Annotation
 tcAnnotation ann@(L loc (HsAnnotation provenance expr)) = do
@@ -41,4 +58,6 @@ annProvenanceToTarget mod ModuleAnnProvenance       = ModuleTarget mod
 annCtxt :: OutputableBndr id => LAnnDecl id -> SDoc
 annCtxt ann
   = hang (ptext (sLit "In the annotation:")) 2 (ppr ann)
+
+#endif
 \end{code}
\ No newline at end of file



More information about the ghc-commits mailing list