diff options
author | Alan Zimmerman <alan.zimm@gmail.com> | 2015-05-08 12:00:33 +0200 |
---|---|---|
committer | Alan Zimmerman <alan.zimm@gmail.com> | 2015-05-08 12:02:27 +0200 |
commit | 2f3bfec0337b05ba5175925f7561238edb5d352c (patch) | |
tree | 064d901d8640e6c7a744d1ac797c1855aceebe5d | |
parent | 4d290ad44ee56d7da9d6c780ce581c64e11331e9 (diff) | |
download | haskell-2f3bfec0337b05ba5175925f7561238edb5d352c.tar.gz |
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
Subscribers: bgamari, thomie, mpickering
Differential Revision: https://phabricator.haskell.org/D848
GHC Trac Issues: #10309
Conflicts:
testsuite/tests/ghc-api/annotations/Makefile
testsuite/tests/ghc-api/annotations/all.T
-rw-r--r-- | compiler/parser/Parser.y | 3 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/.gitignore | 1 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/Makefile | 8 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/T10255.stdout | 2 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/T10309.stdout | 38 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/Test10309.hs | 6 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/all.T | 1 | ||||
-rw-r--r-- | testsuite/tests/ghc-api/annotations/t10309.hs | 106 |
8 files changed, 164 insertions, 1 deletions
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 1baf606173..3d9b2a39cb 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -1621,7 +1621,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 8b7f082773..8ff93b44f8 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 15c3bc4237..c7aa1e5cb8 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 099ef5454e..50e9bb7643 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 0000000000..1423466bf5 --- /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/Test10309.hs b/testsuite/tests/ghc-api/annotations/Test10309.hs new file mode 100644 index 0000000000..75f18a9b71 --- /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 3e145b946b..81aec52b60 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/t10309.hs b/testsuite/tests/ghc-api/annotations/t10309.hs new file mode 100644 index 0000000000..ebce40e34d --- /dev/null +++ b/testsuite/tests/ghc-api/annotations/t10309.hs @@ -0,0 +1,106 @@ +{-# LANGUAGE RankNTypes #-} + +-- This program must be called with GHC's libdir as the single command line +-- argument. +module Main where + +-- import Data.Generics +import Data.Data +import Data.List +import System.IO +import GHC +import BasicTypes +import DynFlags +import MonadUtils +import Outputable +import ApiAnnotation +import Bag (filterBag,isEmptyBag) +import System.Directory (removeFile) +import System.Environment( getArgs ) +import qualified Data.Map as Map +import qualified Data.Set as Set +import Data.Dynamic ( fromDynamic,Dynamic ) + +main::IO() +main = do + [libdir] <- getArgs + testOneFile libdir "Test10309" + +testOneFile libdir fileName = do + ((anns,cs),p) <- runGhc (Just libdir) $ do + dflags <- getSessionDynFlags + setSessionDynFlags dflags + let mn =mkModuleName fileName + addTarget Target { targetId = TargetModule mn + , targetAllowObjCode = True + , targetContents = Nothing } + load LoadAllTargets + modSum <- getModSummary mn + p <- parseModule modSum + return (pm_annotations p,p) + + let spans = Set.fromList $ getAllSrcSpans (pm_parsed_source p) + + problems = filter (\(s,a) -> not (Set.member s spans)) + $ getAnnSrcSpans (anns,cs) + putStrLn "---Problems---------------------" + putStrLn (intercalate "\n" [showAnns $ Map.fromList $ map snd problems]) + putStrLn "--------------------------------" + putStrLn (intercalate "\n" [showAnns anns]) + + where + getAnnSrcSpans :: ApiAnns -> [(SrcSpan,(ApiAnnKey,[SrcSpan]))] + getAnnSrcSpans (anns,_) = map (\a@((ss,_),_) -> (ss,a)) $ Map.toList anns + + getAllSrcSpans :: (Data t) => t -> [SrcSpan] + getAllSrcSpans ast = everything (++) ([] `mkQ` getSrcSpan) ast + where + getSrcSpan :: SrcSpan -> [SrcSpan] + getSrcSpan ss = [ss] + + +showAnns anns = "[\n" ++ (intercalate "\n" + $ map (\((s,k),v) + -> ("(AK " ++ pp s ++ " " ++ show k ++" = " ++ pp v ++ ")\n")) + $ Map.toList anns) + ++ "]\n" + +pp a = showPpr unsafeGlobalDynFlags a + + +-- --------------------------------------------------------------------- + +-- Copied from syb for the test + + +-- | Generic queries of type \"r\", +-- i.e., take any \"a\" and return an \"r\" +-- +type GenericQ r = forall a. Data a => a -> r + + +-- | Make a generic query; +-- start from a type-specific case; +-- return a constant otherwise +-- +mkQ :: ( Typeable a + , Typeable b + ) + => r + -> (b -> r) + -> a + -> r +(r `mkQ` br) a = case cast a of + Just b -> br b + Nothing -> r + + + +-- | Summarise all nodes in top-down, left-to-right order +everything :: (r -> r -> r) -> GenericQ r -> GenericQ r + +-- Apply f to x to summarise top-level node; +-- use gmapQ to recurse into immediate subterms; +-- use ordinary foldl to reduce list of intermediate results + +everything k f x = foldl k (f x) (gmapQ (everything k f) x) |