Skip to content

Commit 623e6d0

Browse files
kl0tlerikd
authored andcommitted
Add back support for identifiers named as
Turns out 'as' _isn’t_ actually a keyword: https://www.ecma-international.org/ecma-262/#prod-Keyword.
1 parent e85ce52 commit 623e6d0

File tree

7 files changed

+22
-21
lines changed

7 files changed

+22
-21
lines changed

src/Language/JavaScript/Parser/AST.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,7 @@ data JSFromClause
8787

8888
-- | Import namespace, e.g. '* as whatever'
8989
data JSImportNameSpace
90-
= JSImportNameSpace !JSBinOp !JSBinOp !JSIdent -- ^ *, as, ident
90+
= JSImportNameSpace !JSBinOp !JSAnnot !JSIdent -- ^ *, as, ident
9191
deriving (Data, Eq, Show, Typeable)
9292

9393
-- | Named imports, e.g. '{ foo, bar, baz as quux }'
@@ -100,7 +100,7 @@ data JSImportsNamed
100100
-- grammar is slightly different (e.g. in handling of reserved words).
101101
data JSImportSpecifier
102102
= JSImportSpecifier !JSIdent -- ^ident
103-
| JSImportSpecifierAs !JSIdent !JSBinOp !JSIdent -- ^ident, as, ident
103+
| JSImportSpecifierAs !JSIdent !JSAnnot !JSIdent -- ^ident, as, ident
104104
deriving (Data, Eq, Show, Typeable)
105105

106106
data JSExportDeclaration
@@ -113,7 +113,7 @@ data JSExportDeclaration
113113

114114
data JSExportLocalSpecifier
115115
= JSExportLocalSpecifier !JSIdent -- ^ident
116-
| JSExportLocalSpecifierAs !JSIdent !JSBinOp !JSIdent -- ^ident1, as, ident2
116+
| JSExportLocalSpecifierAs !JSIdent !JSAnnot !JSIdent -- ^ident1, as, ident2
117117
deriving (Data, Eq, Show, Typeable)
118118

119119
data JSStatement
@@ -185,7 +185,6 @@ data JSExpression
185185

186186
data JSBinOp
187187
= JSBinOpAnd !JSAnnot
188-
| JSBinOpAs !JSAnnot
189188
| JSBinOpBitAnd !JSAnnot
190189
| JSBinOpBitOr !JSAnnot
191190
| JSBinOpBitXor !JSAnnot
@@ -458,7 +457,6 @@ instance ShowStripped JSSwitchParts where
458457

459458
instance ShowStripped JSBinOp where
460459
ss (JSBinOpAnd _) = "'&&'"
461-
ss (JSBinOpAs _) = "'as'"
462460
ss (JSBinOpBitAnd _) = "'&'"
463461
ss (JSBinOpBitOr _) = "'|'"
464462
ss (JSBinOpBitXor _) = "'^'"
@@ -555,7 +553,6 @@ commaIf xs = ',' : xs
555553

556554
deAnnot :: JSBinOp -> JSBinOp
557555
deAnnot (JSBinOpAnd _) = JSBinOpAnd JSNoAnnot
558-
deAnnot (JSBinOpAs _) = JSBinOpAs JSNoAnnot
559556
deAnnot (JSBinOpBitAnd _) = JSBinOpBitAnd JSNoAnnot
560557
deAnnot (JSBinOpBitOr _) = JSBinOpBitOr JSNoAnnot
561558
deAnnot (JSBinOpBitXor _) = JSBinOpBitXor JSNoAnnot

src/Language/JavaScript/Parser/Grammar7.y

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -194,6 +194,9 @@ Spread : '...' { mkJSAnnot $1 }
194194
Dot :: { AST.JSAnnot }
195195
Dot : '.' { mkJSAnnot $1 }
196196

197+
As :: { AST.JSAnnot }
198+
As : 'as' { mkJSAnnot $1 }
199+
197200
Increment :: { AST.JSUnaryOp }
198201
Increment : '++' { AST.JSUnaryOpIncr (mkJSAnnot $1) }
199202

@@ -251,9 +254,6 @@ Ge : '>=' { AST.JSBinOpGe (mkJSAnnot $1) }
251254
Gt :: { AST.JSBinOp }
252255
Gt : '>' { AST.JSBinOpGt (mkJSAnnot $1) }
253256

254-
As :: { AST.JSBinOp }
255-
As : 'as' { AST.JSBinOpAs (mkJSAnnot $1) }
256-
257257
In :: { AST.JSBinOp }
258258
In : 'in' { AST.JSBinOpIn (mkJSAnnot $1) }
259259

@@ -442,6 +442,7 @@ PrimaryExpression : 'this' { AST.JSLiteral (mkJSAnnot $1) "thi
442442
-- IdentifierName IdentifierPart
443443
Identifier :: { AST.JSExpression }
444444
Identifier : 'ident' { AST.JSIdentifier (mkJSAnnot $1) (tokenLiteral $1) }
445+
| 'as' { AST.JSIdentifier (mkJSAnnot $1) "as" }
445446
| 'get' { AST.JSIdentifier (mkJSAnnot $1) "get" }
446447
| 'set' { AST.JSIdentifier (mkJSAnnot $1) "set" }
447448
| 'from' { AST.JSIdentifier (mkJSAnnot $1) "from" }

src/Language/JavaScript/Parser/Lexer.x

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -503,8 +503,7 @@ keywords = Map.fromList keywordNames
503503
504504
keywordNames :: [(String, TokenPosn -> String -> [CommentAnnotation] -> Token)]
505505
keywordNames =
506-
[ ( "as", AsToken )
507-
, ( "break", BreakToken )
506+
[ ( "break", BreakToken )
508507
, ( "case", CaseToken )
509508
, ( "catch", CatchToken )
510509
@@ -549,6 +548,7 @@ keywordNames =
549548
, ( "with", WithToken )
550549
-- TODO: no idea if these are reserved or not, but they are needed
551550
-- handled in parser, in the Identifier rule
551+
, ( "as", AsToken ) -- not reserved
552552
, ( "get", GetToken )
553553
, ( "set", SetToken )
554554
{- Come from Table 6 of ECMASCRIPT 5.1, Attributes of a Named Accessor Property

src/Language/JavaScript/Parser/Token.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,6 @@ data Token
5656
-- ^ Literal: Regular Expression
5757

5858
-- Keywords
59-
| AsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
6059
| BreakToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
6160
| CaseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
6261
| CatchToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
@@ -155,6 +154,7 @@ data Token
155154
| CondcommentEndToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
156155

157156
-- Special cases
157+
| AsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
158158
| TailToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] } -- ^ Stuff between last JS and EOF
159159
| EOFToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] } -- ^ End of file
160160
deriving (Eq, Show, Typeable)

src/Language/JavaScript/Pretty/Printer.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -139,7 +139,6 @@ instance RenderJS [JSExpression] where
139139

140140
instance RenderJS JSBinOp where
141141
(|>) pacc (JSBinOpAnd annot) = pacc |> annot |> "&&"
142-
(|>) pacc (JSBinOpAs annot) = pacc |> annot |> "as"
143142
(|>) pacc (JSBinOpBitAnd annot) = pacc |> annot |> "&"
144143
(|>) pacc (JSBinOpBitOr annot) = pacc |> annot |> "|"
145144
(|>) pacc (JSBinOpBitXor annot) = pacc |> annot |> "^"
@@ -295,14 +294,14 @@ instance RenderJS JSFromClause where
295294
(|>) pacc (JSFromClause from annot m) = pacc |> from |> "from" |> annot |> m
296295

297296
instance RenderJS JSImportNameSpace where
298-
(|>) pacc (JSImportNameSpace star as x) = pacc |> star |> as |> x
297+
(|>) pacc (JSImportNameSpace star annot x) = pacc |> star |> annot |> "as" |> x
299298

300299
instance RenderJS JSImportsNamed where
301300
(|>) pacc (JSImportsNamed lb xs rb) = pacc |> lb |> "{" |> xs |> rb |> "}"
302301

303302
instance RenderJS JSImportSpecifier where
304303
(|>) pacc (JSImportSpecifier x1) = pacc |> x1
305-
(|>) pacc (JSImportSpecifierAs x1 as x2) = pacc |> x1 |> as |> x2
304+
(|>) pacc (JSImportSpecifierAs x1 annot x2) = pacc |> x1 |> annot |> "as" |> x2
306305

307306
instance RenderJS JSExportDeclaration where
308307
(|>) pacc (JSExport x1 s) = pacc |> " " |> x1 |> s
@@ -311,7 +310,7 @@ instance RenderJS JSExportDeclaration where
311310

312311
instance RenderJS JSExportLocalSpecifier where
313312
(|>) pacc (JSExportLocalSpecifier i) = pacc |> i
314-
(|>) pacc (JSExportLocalSpecifierAs x1 as x2) = pacc |> x1 |> as |> x2
313+
(|>) pacc (JSExportLocalSpecifierAs x1 annot x2) = pacc |> x1 |> annot |> "as" |> x2
315314

316315
instance RenderJS a => RenderJS (JSCommaList a) where
317316
(|>) pacc (JSLCons pl a i) = pacc |> pl |> a |> "," |> i

src/Language/JavaScript/Process/Minify.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -215,7 +215,6 @@ normalizeToSQ str =
215215

216216
instance MinifyJS JSBinOp where
217217
fix _ (JSBinOpAnd _) = JSBinOpAnd emptyAnnot
218-
fix a (JSBinOpAs _) = JSBinOpAs a
219218
fix _ (JSBinOpBitAnd _) = JSBinOpBitAnd emptyAnnot
220219
fix _ (JSBinOpBitOr _) = JSBinOpBitOr emptyAnnot
221220
fix _ (JSBinOpBitXor _) = JSBinOpBitXor emptyAnnot
@@ -299,22 +298,22 @@ instance MinifyJS JSFromClause where
299298
fix a (JSFromClause _ _ m) = JSFromClause a emptyAnnot m
300299

301300
instance MinifyJS JSImportNameSpace where
302-
fix a (JSImportNameSpace _ _ ident) = JSImportNameSpace (JSBinOpTimes a) (JSBinOpAs spaceAnnot) (fixSpace ident)
301+
fix a (JSImportNameSpace _ _ ident) = JSImportNameSpace (JSBinOpTimes a) spaceAnnot (fixSpace ident)
303302

304303
instance MinifyJS JSImportsNamed where
305-
fix _ (JSImportsNamed _ imps _) = JSImportsNamed emptyAnnot (fixEmpty imps) emptyAnnot
304+
fix _ (JSImportsNamed _ imps _) = JSImportsNamed emptyAnnot (fixEmpty imps) emptyAnnot
306305

307306
instance MinifyJS JSImportSpecifier where
308307
fix _ (JSImportSpecifier x1) = JSImportSpecifier (fixEmpty x1)
309-
fix _ (JSImportSpecifierAs x1 as x2) = JSImportSpecifierAs (fixEmpty x1) (fixSpace as) (fixSpace x2)
308+
fix _ (JSImportSpecifierAs x1 _ x2) = JSImportSpecifierAs (fixEmpty x1) spaceAnnot (fixSpace x2)
310309

311310
instance MinifyJS JSExportDeclaration where
312311
fix _ (JSExportLocals _ x1 _ _) = JSExportLocals emptyAnnot (fixEmpty x1) emptyAnnot noSemi
313312
fix _ (JSExport x1 _) = JSExport (fixStmt emptyAnnot noSemi x1) noSemi
314313

315314
instance MinifyJS JSExportLocalSpecifier where
316315
fix _ (JSExportLocalSpecifier x1) = JSExportLocalSpecifier (fixEmpty x1)
317-
fix _ (JSExportLocalSpecifierAs x1 as x2) = JSExportLocalSpecifierAs (fixEmpty x1) (fixSpace as) (fixSpace x2)
316+
fix _ (JSExportLocalSpecifierAs x1 _ x2) = JSExportLocalSpecifierAs (fixEmpty x1) spaceAnnot (fixSpace x2)
318317

319318
instance MinifyJS JSTryCatch where
320319
fix a (JSCatch _ _ x1 _ x3) = JSCatch a emptyAnnot (fixEmpty x1) emptyAnnot (fixEmpty x3)

test/Test/Language/Javascript/ModuleParser.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,11 @@ import Language.JavaScript.Parser
99

1010
testModuleParser :: Spec
1111
testModuleParser = describe "Parse modules:" $ do
12+
it "as" $
13+
test "as"
14+
`shouldBe`
15+
"Right (JSAstModule [JSModuleStatementListItem (JSIdentifier 'as')])"
16+
1217
it "import" $ do
1318
-- Not yet supported
1419
-- test "import 'a';" `shouldBe` ""

0 commit comments

Comments
 (0)