[commit: ghc] master: Parse the variables in a type signature in the order given (Trac #8945) (b20bc18)
git at git.haskell.org
git at git.haskell.org
Thu Apr 3 14:56:31 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/b20bc181d8ba496f866c44ae65d26118c2c502a1/ghc
>---------------------------------------------------------------
commit b20bc181d8ba496f866c44ae65d26118c2c502a1
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Apr 3 15:55:46 2014 +0100
Parse the variables in a type signature in the order given (Trac #8945)
This is just making the parser behave more sensibly, and return
the list [x,y,z] from the signature
x,y,z :: Int
rathe than [x,z,y] as now.
Turns out that the other use of sig_vars *did* do the right
thing already.
>---------------------------------------------------------------
b20bc181d8ba496f866c44ae65d26118c2c502a1
compiler/parser/Parser.y.pp | 4 ++--
1 file changed, 2 insertions(+), 2 deletions(-)
diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp
index 27d6c38..8e4da8c 100644
--- a/compiler/parser/Parser.y.pp
+++ b/compiler/parser/Parser.y.pp
@@ -1041,7 +1041,7 @@ sigtypedoc :: { LHsType RdrName } -- Always a HsForAllTy
: ctypedoc { L1 (mkImplicitHsForAllTy (noLoc []) $1) }
-- Wrap an Implicit forall if there isn't one there already
-sig_vars :: { Located [Located RdrName] }
+sig_vars :: { Located [Located RdrName] } -- Returned in reversed order
: sig_vars ',' var { LL ($3 : unLoc $1) }
| var { L1 [$1] }
@@ -1423,7 +1423,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) }
{% do s <- checkValSig $1 $3
; return (LL $ unitOL (LL $ SigD s)) }
| var ',' sig_vars '::' sigtypedoc
- { LL $ toOL [ LL $ SigD (TypeSig ($1 : unLoc $3) $5) ] }
+ { LL $ toOL [ LL $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] }
| infix prec ops { LL $ toOL [ LL $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1))))
| n <- unLoc $3 ] }
| '{-# INLINE' activation qvar '#-}'
More information about the ghc-commits
mailing list