[commit: ghc] wip/T9156: Add a type signature to hsConDeclsBindersâs go (3630c2b)
git at git.haskell.org
git at git.haskell.org
Tue Jul 22 12:24:27 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T9156
Link : http://ghc.haskell.org/trac/ghc/changeset/3630c2bdcbe34a3ac92f5555bee9ef2a2226512d/ghc
>---------------------------------------------------------------
commit 3630c2bdcbe34a3ac92f5555bee9ef2a2226512d
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Tue Jul 22 14:24:21 2014 +0200
Add a type signature to hsConDeclsBinders’s go
>---------------------------------------------------------------
3630c2bdcbe34a3ac92f5555bee9ef2a2226512d
compiler/hsSyn/HsUtils.lhs | 7 +++++--
1 file changed, 5 insertions(+), 2 deletions(-)
diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs
index 38d340c..e12daf4 100644
--- a/compiler/hsSyn/HsUtils.lhs
+++ b/compiler/hsSyn/HsUtils.lhs
@@ -1,3 +1,5 @@
+> {-# LANGUAGE ScopedTypeVariables #-}
+
%
% (c) The University of Glasgow, 1992-2006
%
@@ -746,12 +748,13 @@ hsDataDefnBinders (HsDataDefn { dd_cons = cons }) = hsConDeclsBinders cons
-- See Note [Binders in family instances]
-------------------
-hsConDeclsBinders :: (Eq name) => [LConDecl name] -> [Located name]
+hsConDeclsBinders :: forall name. (Eq name) => [LConDecl name] -> [Located name]
-- See hsLTyClDeclBinders for what this does
-- The function is boringly complicated because of the records
-- And since we only have equality, we have to be a little careful
hsConDeclsBinders cons = go id cons
- where go _ [] = []
+ where go :: ([Located name] -> [Located name]) -> [LConDecl name] -> [Located name]
+ go _ [] = []
go remSeen (r:rs) =
-- don't re-mangle the location of field names, because we don't
-- have a record of the full location of the field declaration anyway
More information about the ghc-commits
mailing list