[commit: ghc] wip/7.10-api-annots2: ApiAnnotations : mkGadtDecl discards annotations for HsFunTy (0a42b31)

git at git.haskell.org git at git.haskell.org
Mon May 11 21:36:57 UTC 2015


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

On branch  : wip/7.10-api-annots2
Link       : http://ghc.haskell.org/trac/ghc/changeset/0a42b31c8fb7b59a31833d1b6a4a45db7cd13df2/ghc

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

commit 0a42b31c8fb7b59a31833d1b6a4a45db7cd13df2
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Mon May 11 10:57:25 2015 +0200

    ApiAnnotations : mkGadtDecl discards annotations for HsFunTy
    
    Summary:
    When mkGadtDecl is presented wih a HsFunTy it discards the SrcSpan, thus
    disconnecting any annotations on the HsFunTy.
    
    ```
    mkGadtDecl names (L ls (HsForAllTy imp Nothing qvars cxt tau))
      = return $ mk_gadt_con names
      where
        (details, res_ty)           -- See Note [Sorting out the result type]
          = case tau of
              L _ (HsFunTy (L l (HsRecTy flds)) res_ty)
                                                -> (RecCon (L l flds), res_ty)
              _other                                    -> (PrefixCon [], tau)
    ...
    ```
    
    This can be triggered by the following
    
    ```
    {-# LANGUAGE GADTs #-}
    module GADTRecords2 (H1(..)) where
    
    -- | h1
    data H1 a b where
      C3 :: (Num a) => { field :: a -- ^ hello docs
                       } -> H1 Int Int
    ```
    
    Test Plan: ./validate
    
    Reviewers: hvr, austin
    
    Reviewed By: austin
    
    Subscribers: bgamari, thomie, mpickering
    
    Differential Revision: https://phabricator.haskell.org/D848
    
    GHC Trac Issues: #10309
    
    (cherry picked from commit e4032b1951a35d8df63a74ebfee7449988b5ef40)


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

0a42b31c8fb7b59a31833d1b6a4a45db7cd13df2
 compiler/parser/Parser.y                           |  3 +-
 testsuite/tests/ghc-api/annotations/.gitignore     |  1 +
 testsuite/tests/ghc-api/annotations/Makefile       |  8 +++++
 testsuite/tests/ghc-api/annotations/T10255.stdout  |  2 ++
 testsuite/tests/ghc-api/annotations/T10309.stdout  | 38 ++++++++++++++++++++++
 testsuite/tests/ghc-api/annotations/T10312.stdout  |  2 ++
 testsuite/tests/ghc-api/annotations/Test10309.hs   |  6 ++++
 testsuite/tests/ghc-api/annotations/all.T          |  1 +
 .../ghc-api/annotations/{t10307.hs => t10309.hs}   |  2 +-
 9 files changed, 61 insertions(+), 2 deletions(-)

diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 602af19..4728df5 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -1488,7 +1488,8 @@ type :: { LHsType RdrName }
         : btype                         { $1 }
         | btype qtyconop type           { sLL $1 $> $ mkHsOpTy $1 $2 $3 }
         | btype tyvarop  type           { sLL $1 $> $ mkHsOpTy $1 $2 $3 }
-        | btype '->'     ctype          {% ams (sLL $1 $> $ HsFunTy $1 $3)
+        | btype '->'     ctype          {% ams $1 [mj AnnRarrow $2]
+                                        >> ams (sLL $1 $> $ HsFunTy $1 $3)
                                                [mj AnnRarrow $2] }
         | btype '~'      btype          {% ams (sLL $1 $> $ HsEqTy $1 $3)
                                                [mj AnnTilde $2] }
diff --git a/testsuite/tests/ghc-api/annotations/.gitignore b/testsuite/tests/ghc-api/annotations/.gitignore
index 8b7f082..8ff93b4 100644
--- a/testsuite/tests/ghc-api/annotations/.gitignore
+++ b/testsuite/tests/ghc-api/annotations/.gitignore
@@ -3,6 +3,7 @@ parseTree
 comments
 exampleTest
 listcomps
+t10309
 t10255
 t10268
 t10269
diff --git a/testsuite/tests/ghc-api/annotations/Makefile b/testsuite/tests/ghc-api/annotations/Makefile
index 15c3bc4..c7aa1e5 100644
--- a/testsuite/tests/ghc-api/annotations/Makefile
+++ b/testsuite/tests/ghc-api/annotations/Makefile
@@ -8,6 +8,7 @@ clean:
 	rm -f t10269
 	rm -f t10255 t10312
 	rm -f t1037
+	rm -f t10309
 
 annotations: 
 	rm -f annotations.o annotations.hi
@@ -73,3 +74,10 @@ t10307:
 	./t10307 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
 
 .PHONY: t10307
+
+t10309:
+	rm -f t10309.o t10309.hi
+	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc t10309
+	./t10309 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
+
+.PHONY: t10309
diff --git a/testsuite/tests/ghc-api/annotations/T10255.stdout b/testsuite/tests/ghc-api/annotations/T10255.stdout
index 099ef54..50e9bb7 100644
--- a/testsuite/tests/ghc-api/annotations/T10255.stdout
+++ b/testsuite/tests/ghc-api/annotations/T10255.stdout
@@ -29,6 +29,8 @@
 
 (AK Test10255.hs:6:11-26 AnnOpenP = [Test10255.hs:6:11])
 
+(AK Test10255.hs:6:12-18 AnnRarrow = [Test10255.hs:6:20-21])
+
 (AK Test10255.hs:6:12-25 AnnRarrow = [Test10255.hs:6:20-21])
 
 (AK <no location info> AnnEofPos = [Test10255.hs:8:1])
diff --git a/testsuite/tests/ghc-api/annotations/T10309.stdout b/testsuite/tests/ghc-api/annotations/T10309.stdout
new file mode 100644
index 0000000..1423466
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/T10309.stdout
@@ -0,0 +1,38 @@
+---Problems---------------------
+[
+(AK Test10309.hs:(5,20)-(6,34) AnnRarrow = [Test10309.hs:6:22-23])
+]
+
+--------------------------------
+[
+(AK Test10309.hs:1:1 AnnModule = [Test10309.hs:2:1-6])
+
+(AK Test10309.hs:1:1 AnnWhere = [Test10309.hs:2:18-22])
+
+(AK Test10309.hs:(4,1)-(6,34) AnnData = [Test10309.hs:4:1-4])
+
+(AK Test10309.hs:(4,1)-(6,34) AnnSemi = [Test10309.hs:7:1])
+
+(AK Test10309.hs:(4,1)-(6,34) AnnWhere = [Test10309.hs:4:13-17])
+
+(AK Test10309.hs:(5,3)-(6,34) AnnDcolon = [Test10309.hs:5:6-7])
+
+(AK Test10309.hs:5:9-15 AnnCloseP = [Test10309.hs:5:15])
+
+(AK Test10309.hs:5:9-15 AnnDarrow = [Test10309.hs:5:17-18])
+
+(AK Test10309.hs:5:9-15 AnnOpenP = [Test10309.hs:5:9])
+
+(AK Test10309.hs:(5,20)-(6,20) AnnCloseC = [Test10309.hs:6:20])
+
+(AK Test10309.hs:(5,20)-(6,20) AnnOpenC = [Test10309.hs:5:20])
+
+(AK Test10309.hs:(5,20)-(6,20) AnnRarrow = [Test10309.hs:6:22-23])
+
+(AK Test10309.hs:(5,20)-(6,34) AnnRarrow = [Test10309.hs:6:22-23])
+
+(AK Test10309.hs:5:22-31 AnnDcolon = [Test10309.hs:5:28-29])
+
+(AK <no location info> AnnEofPos = [Test10309.hs:7:1])
+]
+
diff --git a/testsuite/tests/ghc-api/annotations/T10312.stdout b/testsuite/tests/ghc-api/annotations/T10312.stdout
index 5e4fd1c..70af815 100644
--- a/testsuite/tests/ghc-api/annotations/T10312.stdout
+++ b/testsuite/tests/ghc-api/annotations/T10312.stdout
@@ -334,6 +334,8 @@
 
 (AK Test10312.hs:68:28-51 AnnRarrow = [Test10312.hs:68:37-38])
 
+(AK Test10312.hs:68:29 AnnRarrow = [Test10312.hs:68:31-32])
+
 (AK Test10312.hs:68:29-34 AnnRarrow = [Test10312.hs:68:31-32])
 
 (AK Test10312.hs:68:40-42 AnnCloseS = [Test10312.hs:68:42])
diff --git a/testsuite/tests/ghc-api/annotations/Test10309.hs b/testsuite/tests/ghc-api/annotations/Test10309.hs
new file mode 100644
index 0000000..75f18a9
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/Test10309.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE GADTs #-}
+module Test10309 where
+
+data H1 a b where
+  C3 :: (Num a) => { field :: a -- ^ hello docs
+                   } -> H1 Int Int
diff --git a/testsuite/tests/ghc-api/annotations/all.T b/testsuite/tests/ghc-api/annotations/all.T
index 3e145b9..81aec52 100644
--- a/testsuite/tests/ghc-api/annotations/all.T
+++ b/testsuite/tests/ghc-api/annotations/all.T
@@ -9,3 +9,4 @@ test('T10269',      normal, run_command, ['$MAKE -s --no-print-directory T10269'
 test('T10280',      normal, run_command, ['$MAKE -s --no-print-directory T10280'])
 test('T10312',      normal, run_command, ['$MAKE -s --no-print-directory t10312'])
 test('T10307',      normal, run_command, ['$MAKE -s --no-print-directory t10307'])
+test('T10309',      normal, run_command, ['$MAKE -s --no-print-directory t10309'])
diff --git a/testsuite/tests/ghc-api/annotations/t10307.hs b/testsuite/tests/ghc-api/annotations/t10309.hs
similarity index 98%
copy from testsuite/tests/ghc-api/annotations/t10307.hs
copy to testsuite/tests/ghc-api/annotations/t10309.hs
index 5c6f233..ebce40e 100644
--- a/testsuite/tests/ghc-api/annotations/t10307.hs
+++ b/testsuite/tests/ghc-api/annotations/t10309.hs
@@ -24,7 +24,7 @@ import Data.Dynamic ( fromDynamic,Dynamic )
 main::IO()
 main = do
         [libdir] <- getArgs
-        testOneFile libdir "Test10307"
+        testOneFile libdir "Test10309"
 
 testOneFile libdir fileName = do
        ((anns,cs),p) <- runGhc (Just libdir) $ do



More information about the ghc-commits mailing list