[commit: ghc] master: Minor tweaks to API Annotation (bdeab90)

git at git.haskell.org git at git.haskell.org
Mon Nov 24 15:43:27 UTC 2014


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

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

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

commit bdeab901ffda47cb8f4a28ab3880626e8b23b4d6
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Mon Nov 24 09:43:45 2014 -0600

    Minor tweaks to API Annotation
    
    Summary:
    Add missing Outputable instance for AnnotationComment
    
    Update documentation
    
    Adjust parser to capture annotations correctly
    
    Test Plan: ./validate
    
    Reviewers: austin
    
    Reviewed By: austin
    
    Subscribers: thomie, carter
    
    Differential Revision: https://phabricator.haskell.org/D520


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

bdeab901ffda47cb8f4a28ab3880626e8b23b4d6
 compiler/hsSyn/HsImpExp.lhs                            | 13 +++++++------
 compiler/parser/ApiAnnotation.hs                       |  2 ++
 compiler/parser/Parser.y                               | 16 ++++++++--------
 testsuite/tests/ghc-api/annotations/annotations.stdout |  4 ++++
 testsuite/tests/ghc-api/annotations/parseTree.stdout   |  4 ++++
 5 files changed, 25 insertions(+), 14 deletions(-)

diff --git a/compiler/hsSyn/HsImpExp.lhs b/compiler/hsSyn/HsImpExp.lhs
index b6ec66a..d627591 100644
--- a/compiler/hsSyn/HsImpExp.lhs
+++ b/compiler/hsSyn/HsImpExp.lhs
@@ -39,16 +39,16 @@ type LImportDecl name = Located (ImportDecl name)
 data ImportDecl name
   = ImportDecl {
       ideclName      :: Located ModuleName, -- ^ Module name.
-      ideclPkgQual   :: Maybe FastString,   -- ^ Package qualifier.
-      ideclSource    :: Bool,               -- ^ True <=> {-# SOURCE #-} import
+      ideclPkgQual   :: Maybe FastString,  -- ^ Package qualifier.
+      ideclSource    :: Bool,              -- ^ True <=> {-\# SOURCE \#-} import
       ideclSafe      :: Bool,               -- ^ True => safe import
       ideclQualified :: Bool,               -- ^ True => qualified
       ideclImplicit  :: Bool,               -- ^ True => implicit import (of Prelude)
       ideclAs        :: Maybe ModuleName,   -- ^ as Module
       ideclHiding    :: Maybe (Bool, Located [LIE name])
-    }
                                             -- ^ (True => hiding, names)
-     --
+    }
+     -- ^
      --  'ApiAnnotation.AnnKeywordId's
      --
      --  - 'ApiAnnotation.AnnImport'
@@ -57,6 +57,7 @@ data ImportDecl name
      --
      --  - 'ApiAnnotation.AnnSafe','ApiAnnotation.AnnQualified',
      --    'ApiAnnotation.AnnPackageName','ApiAnnotation.AnnAs',
+     --    'ApiAnnotation.AnnVal'
      --
      --  - 'ApiAnnotation.AnnHiding','ApiAnnotation.AnnOpen',
      --    'ApiAnnotation.AnnClose' attached
@@ -130,10 +131,10 @@ type LIE name = Located (IE name)
 data IE name
   = IEVar       (Located name)
         -- ^ - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern',
-        --                                     'ApiAnnotation.AnnType'
+        --             'ApiAnnotation.AnnType'
   | IEThingAbs           name      -- ^ Class/Type (can't tell)
         --  - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern',
-        --                                     'ApiAnnotation.AnnType'
+        --             'ApiAnnotation.AnnType','ApiAnnotation.AnnVal'
   | IEThingAll  (Located name)     -- ^ Class/Type plus all methods/constructors
         --
         -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs
index 140cd1d..4640a98 100644
--- a/compiler/parser/ApiAnnotation.hs
+++ b/compiler/parser/ApiAnnotation.hs
@@ -229,6 +229,8 @@ data AnnotationComment =
 -- Note: these are based on the Token versions, but the Token type is
 -- defined in Lexer.x and bringing it in here would create a loop
 
+instance Outputable AnnotationComment where
+  ppr x = text (show x)
 
 -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
 --             'ApiAnnotation.AnnClose','ApiAnnotation.AnnComma',
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index d9c0991..eb800ba 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -544,7 +544,7 @@ exp_doc :: { OrdList (LIE RdrName) }
    -- They are built in syntax, always available
 export  :: { OrdList (LIE RdrName) }
         : qcname_ext export_subspec  {% amsu (sLL $1 $> (mkModuleImpExp $1
-                                                           (snd $ unLoc $2)))
+                                                    (snd $ unLoc $2)))
                                              (fst $ unLoc $2) }
         |  'module' modid            {% amsu (sLL $1 $> (IEModuleContents $2))
                                              [mj AnnModule $1] }
@@ -565,9 +565,9 @@ qcnames :: { [Located RdrName] }     -- A reversed list
 
 qcname_ext :: { Located RdrName }       -- Variable or data constructor
                                         -- or tagged type constructor
-        :  qcname                       { $1 }
-        |  'type' qcname                {% am (mkTypeImpExp (sLL $1 $> (unLoc $2)))
-                                              (AnnType, $1) }
+        :  qcname                   {% ams $1 [mj AnnVal $1] }
+        |  'type' qcname            {% amms (mkTypeImpExp (sLL $1 $> (unLoc $2)))
+                                            [mj AnnType $1,mj AnnVal $2] }
 
 -- Cannot pull into qcname_ext, as qcname is also used in expression.
 qcname  :: { Located RdrName }  -- Variable or data constructor
@@ -598,7 +598,7 @@ importdecl :: { LImportDecl RdrName }
                              , ideclAs = unLoc (snd $7)
                              , ideclHiding = unLoc $8 })
                    ((mj AnnImport $1 : fst $2 ++ fst $3 ++ fst $4
-                                    ++ fst $7) ++ (fst $5)) }
+                                    ++ fst $5 ++ fst $7)) }
 
 maybe_src :: { ([AddAnn],IsBootInterface) }
         : '{-# SOURCE' '#-}'           { ([mo $1,mc $2],True) }
@@ -618,9 +618,9 @@ optqualified :: { ([AddAnn],Bool) }
         | {- empty -}                           { ([],False) }
 
 maybeas :: { ([AddAnn],Located (Maybe ModuleName)) }
-        : 'as' modid                            { ([mj AnnAs $1]
-                                                  ,sLL $1 $> (Just (unLoc $2))) }
-        | {- empty -}                           { ([],noLoc Nothing) }
+        : 'as' modid                           { ([mj AnnAs $1,mj AnnVal $2]
+                                                 ,sLL $1 $> (Just (unLoc $2))) }
+        | {- empty -}                          { ([],noLoc Nothing) }
 
 maybeimpspec :: { Located (Maybe (Bool, Located [LIE RdrName])) }
         : impspec                  { L (gl $1) (Just (unLoc $1)) }
diff --git a/testsuite/tests/ghc-api/annotations/annotations.stdout b/testsuite/tests/ghc-api/annotations/annotations.stdout
index e0c311e..ddf4f8d 100644
--- a/testsuite/tests/ghc-api/annotations/annotations.stdout
+++ b/testsuite/tests/ghc-api/annotations/annotations.stdout
@@ -13,12 +13,16 @@
 
 (AK AnnotationLet.hs:1:22-26 AnnOpen = [AnnotationLet.hs:1:22])
 
+(AK AnnotationLet.hs:1:23-25 AnnVal = [AnnotationLet.hs:1:23-25])
+
 (AK AnnotationLet.hs:4:1-32 AnnAs = [AnnotationLet.hs:4:28-29])
 
 (AK AnnotationLet.hs:4:1-32 AnnImport = [AnnotationLet.hs:4:1-6])
 
 (AK AnnotationLet.hs:4:1-32 AnnQualified = [AnnotationLet.hs:4:8-16])
 
+(AK AnnotationLet.hs:4:1-32 AnnVal = [AnnotationLet.hs:4:31-32])
+
 (AK AnnotationLet.hs:(6,1)-(10,12) AnnEqual = [AnnotationLet.hs:6:5])
 
 (AK AnnotationLet.hs:(6,1)-(10,12) AnnFunId = [AnnotationLet.hs:6:1-3])
diff --git a/testsuite/tests/ghc-api/annotations/parseTree.stdout b/testsuite/tests/ghc-api/annotations/parseTree.stdout
index b8b9aa6..ed71b5a 100644
--- a/testsuite/tests/ghc-api/annotations/parseTree.stdout
+++ b/testsuite/tests/ghc-api/annotations/parseTree.stdout
@@ -25,12 +25,16 @@
 
 (AK AnnotationTuple.hs:2:24-28 AnnOpen = [AnnotationTuple.hs:2:24])
 
+(AK AnnotationTuple.hs:2:25-27 AnnVal = [AnnotationTuple.hs:2:25-27])
+
 (AK AnnotationTuple.hs:5:1-32 AnnAs = [AnnotationTuple.hs:5:28-29])
 
 (AK AnnotationTuple.hs:5:1-32 AnnImport = [AnnotationTuple.hs:5:1-6])
 
 (AK AnnotationTuple.hs:5:1-32 AnnQualified = [AnnotationTuple.hs:5:8-16])
 
+(AK AnnotationTuple.hs:5:1-32 AnnVal = [AnnotationTuple.hs:5:31-32])
+
 (AK AnnotationTuple.hs:(7,1)-(10,14) AnnEqual = [AnnotationTuple.hs:7:5])
 
 (AK AnnotationTuple.hs:(7,1)-(10,14) AnnFunId = [AnnotationTuple.hs:7:1-3])



More information about the ghc-commits mailing list