[commit: ghc] master: Fix mkGadtDecl does not set con_forall correctly (6e4e6d1)
git at git.haskell.org
git at git.haskell.org
Fri Jun 29 19:01:53 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/6e4e6d1c674a9d0257ca5c6caa26da18edf8ad8c/ghc
>---------------------------------------------------------------
commit 6e4e6d1c674a9d0257ca5c6caa26da18edf8ad8c
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date: Fri Jun 29 20:58:21 2018 +0200
Fix mkGadtDecl does not set con_forall correctly
A GADT declaration surrounded in parens does not det the con_forall
field correctly.
e.g.
data MaybeDefault v where
TestParens :: (forall v . (Eq v) => MaybeDefault v)
Closes #15323
>---------------------------------------------------------------
6e4e6d1c674a9d0257ca5c6caa26da18edf8ad8c
compiler/parser/RdrHsSyn.hs | 2 +-
testsuite/tests/parser/should_compile/T15323.hs | 6 ++
.../tests/parser/should_compile/T15323.stderr | 96 ++++++++++++++++++++++
testsuite/tests/parser/should_compile/all.T | 1 +
4 files changed, 104 insertions(+), 1 deletion(-)
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index 44159dc..7dc3aaf 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -643,7 +643,7 @@ mkGadtDecl :: [Located RdrName]
mkGadtDecl names ty
= (ConDeclGADT { con_g_ext = noExt
, con_names = names
- , con_forall = L l $ isLHsForAllTy ty
+ , con_forall = L l $ isLHsForAllTy ty'
, con_qvars = mkHsQTvs tvs
, con_mb_cxt = mcxt
, con_args = args'
diff --git a/testsuite/tests/parser/should_compile/T15323.hs b/testsuite/tests/parser/should_compile/T15323.hs
new file mode 100644
index 0000000..ffc8ad8
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/T15323.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE RankNTypes #-}
+module T15323 where
+
+data MaybeDefault v where
+ TestParens :: (forall v . (Eq v) => MaybeDefault v)
diff --git a/testsuite/tests/parser/should_compile/T15323.stderr b/testsuite/tests/parser/should_compile/T15323.stderr
new file mode 100644
index 0000000..93b254b
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/T15323.stderr
@@ -0,0 +1,96 @@
+
+==================== Parser AST ====================
+
+({ T15323.hs:1:1 }
+ (HsModule
+ (Just
+ ({ T15323.hs:3:8-13 }
+ {ModuleName: T15323}))
+ (Nothing)
+ []
+ [({ T15323.hs:(5,1)-(6,56) }
+ (TyClD
+ (NoExt)
+ (DataDecl
+ (NoExt)
+ ({ T15323.hs:5:6-17 }
+ (Unqual
+ {OccName: MaybeDefault}))
+ (HsQTvs
+ (NoExt)
+ [({ T15323.hs:5:19 }
+ (UserTyVar
+ (NoExt)
+ ({ T15323.hs:5:19 }
+ (Unqual
+ {OccName: v}))))])
+ (Prefix)
+ (HsDataDefn
+ (NoExt)
+ (DataType)
+ ({ <no location info> }
+ [])
+ (Nothing)
+ (Nothing)
+ [({ T15323.hs:6:5-56 }
+ (ConDeclGADT
+ (NoExt)
+ [({ T15323.hs:6:5-14 }
+ (Unqual
+ {OccName: TestParens}))]
+ ({ T15323.hs:6:21-55 }
+ (True))
+ (HsQTvs
+ (NoExt)
+ [({ T15323.hs:6:28 }
+ (UserTyVar
+ (NoExt)
+ ({ T15323.hs:6:28 }
+ (Unqual
+ {OccName: v}))))])
+ (Just
+ ({ T15323.hs:6:32-37 }
+ [({ T15323.hs:6:32-37 }
+ (HsParTy
+ (NoExt)
+ ({ T15323.hs:6:33-36 }
+ (HsAppTy
+ (NoExt)
+ ({ T15323.hs:6:33-34 }
+ (HsTyVar
+ (NoExt)
+ (NotPromoted)
+ ({ T15323.hs:6:33-34 }
+ (Unqual
+ {OccName: Eq}))))
+ ({ T15323.hs:6:36 }
+ (HsTyVar
+ (NoExt)
+ (NotPromoted)
+ ({ T15323.hs:6:36 }
+ (Unqual
+ {OccName: v}))))))))]))
+ (PrefixCon
+ [])
+ ({ T15323.hs:6:42-55 }
+ (HsAppTy
+ (NoExt)
+ ({ T15323.hs:6:42-53 }
+ (HsTyVar
+ (NoExt)
+ (NotPromoted)
+ ({ T15323.hs:6:42-53 }
+ (Unqual
+ {OccName: MaybeDefault}))))
+ ({ T15323.hs:6:55 }
+ (HsTyVar
+ (NoExt)
+ (NotPromoted)
+ ({ T15323.hs:6:55 }
+ (Unqual
+ {OccName: v}))))))
+ (Nothing)))]
+ ({ <no location info> }
+ [])))))]
+ (Nothing)
+ (Nothing)))
diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T
index ab0a393..1fd8c69 100644
--- a/testsuite/tests/parser/should_compile/all.T
+++ b/testsuite/tests/parser/should_compile/all.T
@@ -116,3 +116,4 @@ test('T14189', normal, compile, ['-dsuppress-uniques -ddump-rn-ast'])
test('T13986', normal, compile, [''])
test('T10855', normal, compile, [''])
test('T15139', normal, compile, ['-Wincomplete-patterns -fdiagnostics-show-caret'])
+test('T15323', normal, compile, ['-dsuppress-uniques -ddump-parsed-ast'])
More information about the ghc-commits
mailing list