Skip to content

Commit 6f96390

Browse files
kl0tlerikd
authored andcommitted
Add support for unparenthesized arrow functions of one parameter
1 parent 06cf7b3 commit 6f96390

File tree

7 files changed

+33
-8
lines changed

7 files changed

+33
-8
lines changed

src/Language/JavaScript/Parser/AST.hs

+12-2
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Language.JavaScript.Parser.AST
2222
, JSArrayElement (..)
2323
, JSCommaList (..)
2424
, JSCommaTrailingList (..)
25+
, JSArrowParameterList (..)
2526

2627
-- Modules
2728
, JSModuleItem (..)
@@ -175,7 +176,7 @@ data JSExpression
175176
| JSExpressionParen !JSAnnot !JSExpression !JSAnnot -- ^lb,expression,rb
176177
| JSExpressionPostfix !JSExpression !JSUnaryOp -- ^expression, operator
177178
| JSExpressionTernary !JSExpression !JSAnnot !JSExpression !JSAnnot !JSExpression -- ^cond, ?, trueval, :, falseval
178-
| JSArrowExpression !JSAnnot !(JSCommaList JSIdent) !JSAnnot !JSAnnot !JSStatement -- ^parameter list,arrow,block`
179+
| JSArrowExpression !JSArrowParameterList !JSAnnot !JSStatement -- ^parameter list,arrow,block`
179180
| JSFunctionExpression !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSIdent) !JSAnnot !JSBlock -- ^fn,name,lb, parameter list,rb,block`
180181
| JSMemberDot !JSExpression !JSAnnot !JSExpression -- ^firstpart, dot, name
181182
| JSMemberExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot -- expr, lb, args, rb
@@ -188,6 +189,11 @@ data JSExpression
188189
| JSVarInitExpression !JSExpression !JSVarInitializer -- ^identifier, initializer
189190
deriving (Data, Eq, Show, Typeable)
190191

192+
data JSArrowParameterList
193+
= JSUnparenthesizedArrowParameter !JSIdent
194+
| JSParenthesizedArrowParameterList !JSAnnot !(JSCommaList JSIdent) !JSAnnot
195+
deriving (Data, Eq, Show, Typeable)
196+
191197
data JSBinOp
192198
= JSBinOpAnd !JSAnnot
193199
| JSBinOpBitAnd !JSAnnot
@@ -373,7 +379,7 @@ instance ShowStripped JSExpression where
373379
ss (JSExpressionParen _lp x _rp) = "JSExpressionParen (" ++ ss x ++ ")"
374380
ss (JSExpressionPostfix xs op) = "JSExpressionPostfix (" ++ ss op ++ "," ++ ss xs ++ ")"
375381
ss (JSExpressionTernary x1 _q x2 _c x3) = "JSExpressionTernary (" ++ ss x1 ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
376-
ss (JSArrowExpression _ n _ _ e) = "JSArrowExpression (" ++ ss n ++ ") => " ++ ss e
382+
ss (JSArrowExpression ps _ e) = "JSArrowExpression (" ++ ss ps ++ ") => " ++ ss e
377383
ss (JSFunctionExpression _ n _lb pl _rb x3) = "JSFunctionExpression " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ "))"
378384
ss (JSHexInteger _ s) = "JSHexInteger " ++ singleQuote s
379385
ss (JSOctal _ s) = "JSOctal " ++ singleQuote s
@@ -392,6 +398,10 @@ instance ShowStripped JSExpression where
392398
ss (JSVarInitExpression x1 x2) = "JSVarInitExpression (" ++ ss x1 ++ ") " ++ ss x2
393399
ss (JSSpreadExpression _ x1) = "JSSpreadExpression (" ++ ss x1 ++ ")"
394400

401+
instance ShowStripped JSArrowParameterList where
402+
ss (JSUnparenthesizedArrowParameter x) = ss x
403+
ss (JSParenthesizedArrowParameterList _ xs _) = ss xs
404+
395405
instance ShowStripped JSModuleItem where
396406
ss (JSModuleExportDeclaration _ x1) = "JSModuleExportDeclaration (" ++ ss x1 ++ ")"
397407
ss (JSModuleImportDeclaration _ x1) = "JSModuleImportDeclaration (" ++ ss x1 ++ ")"

src/Language/JavaScript/Parser/Grammar7.y

+10-4
Original file line numberDiff line numberDiff line change
@@ -1137,10 +1137,16 @@ FunctionExpression : ArrowFunctionExpression { $1 {- 'ArrowFunctionExpressio
11371137
| NamedFunctionExpression { $1 {- 'FunctionExpression2' -} }
11381138

11391139
ArrowFunctionExpression :: { AST.JSExpression }
1140-
ArrowFunctionExpression : LParen RParen Arrow StatementOrBlock
1141-
{ AST.JSArrowExpression $1 AST.JSLNil $2 $3 $4 {- 'ArrowFunctionExpression1' -} }
1142-
| LParen FormalParameterList RParen Arrow StatementOrBlock
1143-
{ AST.JSArrowExpression $1 $2 $3 $4 $5 {- 'ArrowFunctionExpression3' -} }
1140+
ArrowFunctionExpression : ArrowParameterList Arrow StatementOrBlock
1141+
{ AST.JSArrowExpression $1 $2 $3 }
1142+
1143+
ArrowParameterList :: { AST.JSArrowParameterList }
1144+
ArrowParameterList : Identifier
1145+
{ AST.JSUnparenthesizedArrowParameter (identName $1) }
1146+
| LParen RParen
1147+
{ AST.JSParenthesizedArrowParameterList $1 AST.JSLNil $2 }
1148+
| LParen FormalParameterList RParen
1149+
{ AST.JSParenthesizedArrowParameterList $1 $2 $3 }
11441150

11451151
StatementOrBlock :: { AST.JSStatement }
11461152
StatementOrBlock : Block MaybeSemi { blockToStatement $1 $2 }

src/Language/JavaScript/Pretty/Printer.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ instance RenderJS JSExpression where
7272

7373
-- Non-Terminals
7474
(|>) pacc (JSArrayLiteral als xs ars) = pacc |> als |> "[" |> xs |> ars |> "]"
75-
(|>) pacc (JSArrowExpression lp xs rp a x) = pacc |> lp |> "(" |> xs |> rp |> ")" |> a |> "=>" |> x
75+
(|>) pacc (JSArrowExpression xs a x) = pacc |> xs |> a |> "=>" |> x
7676
(|>) pacc (JSAssignExpression lhs op rhs) = pacc |> lhs |> op |> rhs
7777
(|>) pacc (JSCallExpression ex lb xs rb) = pacc |> ex |> lb |> "(" |> xs |> rb |> ")"
7878
(|>) pacc (JSCallExpressionDot ex os xs) = pacc |> ex |> os |> "." |> xs
@@ -93,6 +93,9 @@ instance RenderJS JSExpression where
9393
(|>) pacc (JSVarInitExpression x1 x2) = pacc |> x1 |> x2
9494
(|>) pacc (JSSpreadExpression a e) = pacc |> a |> "..." |> e
9595

96+
instance RenderJS JSArrowParameterList where
97+
(|>) pacc (JSUnparenthesizedArrowParameter p) = pacc |> p
98+
(|>) pacc (JSParenthesizedArrowParameterList lb ps rb) = pacc |> lb |> "(" |> ps |> ")" |> rb
9699
-- -----------------------------------------------------------------------------
97100
-- Need an instance of RenderJS for every component of every JSExpression or JSAnnot
98101
-- constuctor.

src/Language/JavaScript/Process/Minify.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -148,7 +148,7 @@ instance MinifyJS JSExpression where
148148

149149
-- Non-Terminals
150150
fix _ (JSArrayLiteral _ xs _) = JSArrayLiteral emptyAnnot (map fixEmpty xs) emptyAnnot
151-
fix _ (JSArrowExpression _ ps _ _ ss) = JSArrowExpression emptyAnnot (fixEmpty ps) emptyAnnot emptyAnnot (fixStmt emptyAnnot noSemi ss)
151+
fix a (JSArrowExpression ps _ ss) = JSArrowExpression (fix a ps) emptyAnnot (fixStmt emptyAnnot noSemi ss)
152152
fix a (JSAssignExpression lhs op rhs) = JSAssignExpression (fix a lhs) (fixEmpty op) (fixEmpty rhs)
153153
fix a (JSCallExpression ex _ xs _) = JSCallExpression (fix a ex) emptyAnnot (fixEmpty xs) emptyAnnot
154154
fix a (JSCallExpressionDot ex _ xs) = JSCallExpressionDot (fix a ex) emptyAnnot (fixEmpty xs)
@@ -169,6 +169,9 @@ instance MinifyJS JSExpression where
169169
fix a (JSVarInitExpression x1 x2) = JSVarInitExpression (fix a x1) (fixEmpty x2)
170170
fix a (JSSpreadExpression _ e) = JSSpreadExpression a (fixEmpty e)
171171

172+
instance MinifyJS JSArrowParameterList where
173+
fix _ (JSUnparenthesizedArrowParameter p) = JSUnparenthesizedArrowParameter (fixEmpty p)
174+
fix _ (JSParenthesizedArrowParameterList _ ps _) = JSParenthesizedArrowParameterList emptyAnnot (fixEmpty ps) emptyAnnot
172175

173176
fixVarList :: JSCommaList JSExpression -> JSCommaList JSExpression
174177
fixVarList (JSLCons h _ v) = JSLCons (fixVarList h) emptyAnnot (fixEmpty v)

test/Test/Language/Javascript/ExpressionParser.hs

+1
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,7 @@ testExpressionParser = describe "Parse expressions:" $ do
123123
testExpr "function(){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' () (JSBlock []))))"
124124
testExpr "function(a){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSIdentifier 'a') (JSBlock []))))"
125125
testExpr "function(a,b){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSIdentifier 'a',JSIdentifier 'b') (JSBlock []))))"
126+
testExpr "a => {}" `shouldBe` "Right (JSAstExpression (JSArrowExpression (JSIdentifier 'a') => JSStatementBlock []))"
126127
testExpr "(a) => { a + 2 }" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a')) => JSStatementBlock [JSExpressionBinary ('+',JSIdentifier 'a',JSDecimal '2')]))"
127128
testExpr "(a, b) => {}" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a',JSIdentifier 'b')) => JSStatementBlock []))"
128129
testExpr "(a, b) => a + b" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a',JSIdentifier 'b')) => JSExpressionBinary ('+',JSIdentifier 'a',JSIdentifier 'b')))"

test/Test/Language/Javascript/Minify.hs

+1
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,7 @@ testMinifyExpr = describe "Minify expressions:" $ do
106106
minifyExpr " function ( a ) { } " `shouldBe` "function(a){}"
107107
minifyExpr " function ( a , b ) { return a + b ; } " `shouldBe` "function(a,b){return a+b}"
108108

109+
minifyExpr "a => {}" `shouldBe` "a=>{}"
109110
minifyExpr "(a) => {}" `shouldBe` "(a)=>{}"
110111
minifyExpr "( a ) => { a + 2 }" `shouldBe` "(a)=>a+2"
111112
minifyExpr "(a, b) => a + b" `shouldBe` "(a,b)=>a+b"

test/Test/Language/Javascript/RoundTrip.hs

+1
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,7 @@ testRoundTrip = describe "Roundtrip:" $ do
6363
testRT "/*a*/x/*b*/=/*c*/{/*d*/get/*e*/ foo/*f*/(/*g*/)/*h*/ {/*i*/return/*j*/ 1/*k*/}/*l*/,/*m*/set/*n*/ foo/*o*/(/*p*/a/*q*/) /*r*/{/*s*/x/*t*/=/*u*/a/*v*/}/*w*/}"
6464
testRT "... /*a*/ x"
6565

66+
testRT "a => {}"
6667
testRT "(a) => { a + 2 }"
6768
testRT "(a, b) => {}"
6869
testRT "(a, b) => a + b"

0 commit comments

Comments
 (0)