Skip to content
Snippets Groups Projects
Commit b20bc181 authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

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.
parent 8bf8ce1e
No related merge requests found
......@@ -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 '#-}'
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment