Skip to content

Commit 6598e83

Browse files
committed
Introduce ES2015 module parsing
1 parent 580990e commit 6598e83

File tree

12 files changed

+215
-88
lines changed

12 files changed

+215
-88
lines changed

language-javascript.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,7 @@ Test-Suite testsuite
8383
Test.Language.Javascript.Lexer
8484
Test.Language.Javascript.LiteralParser
8585
Test.Language.Javascript.Minify
86+
Test.Language.Javascript.ModuleParser
8687
Test.Language.Javascript.ProgramParser
8788
Test.Language.Javascript.RoundTrip
8889
Test.Language.Javascript.StatementParser

src/Language/JavaScript/Parser.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
11
module Language.JavaScript.Parser
22
(
33
PA.parse
4+
, PA.parseModule
45
, PA.readJs
6+
, PA.readJsModule
57
, PA.parseFile
68
, PA.parseFileUtf8
79
, PA.showStripped

src/Language/JavaScript/Parser/AST.hs

Lines changed: 39 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,6 @@ module Language.JavaScript.Parser.AST
1010
, JSTryCatch (..)
1111
, JSTryFinally (..)
1212
, JSStatement (..)
13-
, JSExportBody (..)
14-
, JSExportSpecifier (..)
1513
, JSBlock (..)
1614
, JSSwitchParts (..)
1715
, JSAST (..)
@@ -25,6 +23,11 @@ module Language.JavaScript.Parser.AST
2523
, JSCommaList (..)
2624
, JSCommaTrailingList (..)
2725

26+
-- Modules
27+
, JSModuleItem (..)
28+
, JSExportDeclaration (..)
29+
, JSExportLocalSpecifier (..)
30+
2831
, binOpEq
2932
, showStripped
3033
) where
@@ -44,12 +47,34 @@ data JSAnnot
4447

4548

4649
data JSAST
47-
= JSAstProgram ![JSStatement] !JSAnnot -- ^source elements, tailing whitespace
50+
= JSAstProgram ![JSStatement] !JSAnnot -- ^source elements, trailing whitespace
51+
| JSAstModule ![JSModuleItem] !JSAnnot
4852
| JSAstStatement !JSStatement !JSAnnot
4953
| JSAstExpression !JSExpression !JSAnnot
5054
| JSAstLiteral !JSExpression !JSAnnot
5155
deriving (Data, Eq, Show, Typeable)
5256

57+
-- Shift AST
58+
-- https://github.com/shapesecurity/shift-spec/blob/83498b92c436180cc0e2115b225a68c08f43c53e/spec.idl#L229-L234
59+
data JSModuleItem
60+
-- = JSImportDeclaration
61+
= JSModuleExportDeclaration !JSAnnot !JSExportDeclaration -- ^export,decl
62+
| JSModuleStatementListItem !JSStatement
63+
deriving (Data, Eq, Show, Typeable)
64+
65+
data JSExportDeclaration
66+
-- = JSExportAllFrom
67+
-- | JSExportFrom
68+
= JSExportLocals !JSAnnot !(JSCommaList JSExportLocalSpecifier) !JSAnnot !JSSemi -- ^lb, specifiers, rb, autosemi
69+
| JSExport !JSStatement !JSSemi -- ^body, autosemi
70+
-- | JSExportDefault
71+
deriving (Data, Eq, Show, Typeable)
72+
73+
data JSExportLocalSpecifier
74+
= JSExportLocalSpecifier !JSIdent -- ^ident
75+
| JSExportLocalSpecifierAs !JSIdent !JSBinOp !JSIdent -- ^ident1, as, ident2
76+
deriving (Data, Eq, Show, Typeable)
77+
5378
data JSStatement
5479
= JSStatementBlock !JSAnnot ![JSStatement] !JSAnnot !JSSemi -- ^lbrace, stmts, rbrace, autosemi
5580
| JSBreak !JSAnnot !JSIdent !JSSemi -- ^break,optional identifier, autosemi
@@ -76,7 +101,6 @@ data JSStatement
76101
| JSVariable !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^var, decl, autosemi
77102
| JSWhile !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement -- ^while,lb,expr,rb,stmt
78103
| JSWith !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSSemi -- ^with,lb,expr,rb,stmt list
79-
| JSExport !JSAnnot !JSExportBody !JSSemi -- ^export, body, autosemi
80104
deriving (Data, Eq, Show, Typeable)
81105

82106
data JSExpression
@@ -172,16 +196,6 @@ data JSAssignOp
172196
| JSBwOrAssign !JSAnnot
173197
deriving (Data, Eq, Show, Typeable)
174198

175-
data JSExportBody
176-
= JSExportStatement !JSStatement
177-
| JSExportClause !JSAnnot !(Maybe (JSCommaList JSExportSpecifier)) !JSAnnot -- ^lb,body,rb
178-
deriving (Data, Eq, Show, Typeable)
179-
180-
data JSExportSpecifier
181-
= JSExportSpecifier !JSIdent
182-
| JSExportSpecifierAs !JSIdent !JSBinOp !JSIdent
183-
deriving (Data, Eq, Show, Typeable)
184-
185199
data JSTryCatch
186200
= JSCatch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSBlock -- ^catch,lb,ident,rb,block
187201
| JSCatchIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSExpression !JSAnnot !JSBlock -- ^catch,lb,ident,if,expr,rb,block
@@ -252,6 +266,7 @@ data JSCommaTrailingList a
252266
-- Strip out the location info
253267
showStripped :: JSAST -> String
254268
showStripped (JSAstProgram xs _) = "JSAstProgram " ++ ss xs
269+
showStripped (JSAstModule xs _) = "JSAstModule " ++ ss xs
255270
showStripped (JSAstStatement s _) = "JSAstStatement (" ++ ss s ++ ")"
256271
showStripped (JSAstExpression e _) = "JSAstExpression (" ++ ss e ++ ")"
257272
showStripped (JSAstLiteral s _) = "JSAstLiteral (" ++ ss s ++ ")"
@@ -289,7 +304,6 @@ instance ShowStripped JSStatement where
289304
ss (JSVariable _ xs _as) = "JSVariable " ++ ss xs
290305
ss (JSWhile _ _lb x1 _rb x2) = "JSWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
291306
ss (JSWith _ _lb x1 _rb x _) = "JSWith (" ++ ss x1 ++ ") (" ++ ss x ++ ")"
292-
ss (JSExport _ b _) = "JSExport (" ++ ss b ++ ")"
293307

294308
instance ShowStripped JSExpression where
295309
ss (JSArrayLiteral _lb xs _rb) = "JSArrayLiteral " ++ ss xs
@@ -322,14 +336,17 @@ instance ShowStripped JSExpression where
322336
ss (JSVarInitExpression x1 x2) = "JSVarInitExpression (" ++ ss x1 ++ ") " ++ ss x2
323337
ss (JSSpreadExpression _ x1) = "JSSpreadExpression (" ++ ss x1 ++ ")"
324338

325-
instance ShowStripped JSExportBody where
326-
ss (JSExportStatement x1) = "JSExportStatement (" ++ ss x1 ++ ")"
327-
ss (JSExportClause _ Nothing _) = "JSExportClause ()"
328-
ss (JSExportClause _ (Just x1) _) = "JSExportClause (" ++ ss x1 ++ ")"
339+
instance ShowStripped JSModuleItem where
340+
ss (JSModuleExportDeclaration _ x1) = "JSModuleExportDeclaration (" ++ ss x1 ++ ")"
341+
ss (JSModuleStatementListItem x1) = "JSModuleStatementListItem (" ++ ss x1 ++ ")"
342+
343+
instance ShowStripped JSExportDeclaration where
344+
ss (JSExportLocals _ xs _ _) = "JSExportLocals (" ++ ss xs ++ ")"
345+
ss (JSExport x1 _) = "JSExport (" ++ ss x1 ++ ")"
329346

330-
instance ShowStripped JSExportSpecifier where
331-
ss (JSExportSpecifier x1) = "JSExportSpecifier (" ++ ss x1 ++ ")"
332-
ss (JSExportSpecifierAs x1 _ x2) = "JSExportSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
347+
instance ShowStripped JSExportLocalSpecifier where
348+
ss (JSExportLocalSpecifier x1) = "JSExportLocalSpecifier (" ++ ss x1 ++ ")"
349+
ss (JSExportLocalSpecifierAs x1 _ x2) = "JSExportLocalSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
333350

334351
instance ShowStripped JSTryCatch where
335352
ss (JSCatch _ _lb x1 _rb x3) = "JSCatch (" ++ ss x1 ++ "," ++ ss x3 ++ ")"

src/Language/JavaScript/Parser/Grammar7.y

Lines changed: 52 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,12 @@
11
{
22
{-# LANGUAGE BangPatterns #-}
33
module Language.JavaScript.Parser.Grammar7
4-
( parseProgram
5-
, parseStatement
6-
, parseExpression
7-
, parseLiteral
8-
) where
4+
( parseProgram
5+
, parseModule
6+
, parseStatement
7+
, parseExpression
8+
, parseLiteral
9+
) where
910

1011
import Data.Char
1112
import Language.JavaScript.Parser.Lexer
@@ -18,6 +19,7 @@ import qualified Language.JavaScript.Parser.AST as AST
1819

1920
-- The name of the generated function to be exported from the module
2021
%name parseProgram Program
22+
%name parseModule Module
2123
%name parseLiteral LiteralMain
2224
%name parseExpression ExpressionMain
2325
%name parseStatement StatementMain
@@ -897,7 +899,6 @@ StatementNoEmpty : StatementBlock { $1 {- 'StatementNoEmpty1' -} }
897899
| ThrowStatement { $1 {- 'StatementNoEmpty13' -} }
898900
| TryStatement { $1 {- 'StatementNoEmpty14' -} }
899901
| DebuggerStatement { $1 {- 'StatementNoEmpty15' -} }
900-
| ExportDeclaration { $1 {- 'StatementNoEmpty16' -} }
901902

902903

903904
StatementBlock :: { AST.JSStatement }
@@ -1119,6 +1120,11 @@ StatementOrBlock :: { AST.JSStatement }
11191120
StatementOrBlock : Block MaybeSemi { blockToStatement $1 $2 }
11201121
| Expression MaybeSemi { expressionToStatement $1 $2 }
11211122
1123+
-- StatementListItem :
1124+
-- Statement
1125+
-- Declaration
1126+
StatementListItem :: { AST.JSStatement }
1127+
StatementListItem : Statement { $1 }
11221128
11231129
NamedFunctionExpression :: { AST.JSExpression }
11241130
NamedFunctionExpression : Function Identifier LParen RParen FunctionBody
@@ -1156,6 +1162,32 @@ Program :: { AST.JSAST }
11561162
Program : StatementList Eof { AST.JSAstProgram $1 $2 {- 'Program1' -} }
11571163
| Eof { AST.JSAstProgram [] $1 {- 'Program2' -} }
11581164
1165+
-- Module : See 15.2
1166+
-- ModuleBody[opt]
1167+
--
1168+
-- ModuleBody :
1169+
-- ModuleItemList
1170+
Module :: { AST.JSAST }
1171+
Module : ModuleItemList Eof { AST.JSAstModule $1 $2 {- 'Module1' -} }
1172+
| Eof { AST.JSAstModule [] $1 {- 'Module2' -} }
1173+
1174+
-- ModuleItemList :
1175+
-- ModuleItem
1176+
-- ModuleItemList ModuleItem
1177+
ModuleItemList :: { [AST.JSModuleItem] }
1178+
ModuleItemList : ModuleItem { [$1] {- 'ModuleItemList1' -} }
1179+
| ModuleItemList ModuleItem { ($1++[$2]) {- 'ModuleItemList2' -} }
1180+
1181+
-- ModuleItem :
1182+
-- ImportDeclaration
1183+
-- ExportDeclaration
1184+
-- StatementListItem
1185+
ModuleItem :: { AST.JSModuleItem }
1186+
ModuleItem : Export ExportDeclaration
1187+
{ AST.JSModuleExportDeclaration $1 $2 {- 'ModuleItem1' -} }
1188+
| StatementListItem
1189+
{ AST.JSModuleStatementListItem $1 {- 'ModuleItem2' -} }
1190+
11591191
-- ExportDeclaration : See 15.2.3
11601192
-- [ ] export * FromClause ;
11611193
-- [ ] export ExportClause FromClause ;
@@ -1165,26 +1197,26 @@ Program : StatementList Eof { AST.JSAstProgram $1 $2 {- 'Program1' -} }
11651197
-- [ ] export default HoistableDeclaration[Default]
11661198
-- [ ] export default ClassDeclaration[Default]
11671199
-- [ ] export default [lookahead ∉ { function, class }] AssignmentExpression[In] ;
1168-
ExportDeclaration :: { AST.JSStatement }
1169-
ExportDeclaration : Export ExportClause AutoSemi
1170-
{ AST.JSExport $1 $2 $3 {- 'ExportDeclaration1' -} }
1171-
| Export VariableStatement AutoSemi
1172-
{ AST.JSExport $1 (AST.JSExportStatement $2) $3 {- 'ExportDeclaration2' -} }
1200+
ExportDeclaration :: { AST.JSExportDeclaration }
1201+
ExportDeclaration : ExportClause AutoSemi
1202+
{ $1 {- 'ExportDeclaration1' -} }
1203+
| VariableStatement AutoSemi
1204+
{ AST.JSExport $1 $2 {- 'ExportDeclaration2' -} }
11731205
11741206
-- ExportClause :
11751207
-- { }
11761208
-- { ExportsList }
11771209
-- { ExportsList , }
1178-
ExportClause :: { AST.JSExportBody }
1179-
ExportClause : LBrace RBrace
1180-
{ AST.JSExportClause $1 Nothing $2 {- 'ExportClause1' -} }
1181-
| LBrace ExportsList RBrace
1182-
{ AST.JSExportClause $1 (Just $2) $3 {- 'ExportClause2' -} }
1210+
ExportClause :: { AST.JSExportDeclaration }
1211+
ExportClause : LBrace RBrace AutoSemi
1212+
{ AST.JSExportLocals $1 AST.JSLNil $2 $3 {- 'ExportClause1' -} }
1213+
| LBrace ExportsList RBrace AutoSemi
1214+
{ AST.JSExportLocals $1 $2 $3 $4 {- 'ExportClause2' -} }
11831215
11841216
-- ExportsList :
11851217
-- ExportSpecifier
11861218
-- ExportsList , ExportSpecifier
1187-
ExportsList :: { AST.JSCommaList AST.JSExportSpecifier }
1219+
ExportsList :: { AST.JSCommaList AST.JSExportLocalSpecifier }
11881220
ExportsList : ExportSpecifier
11891221
{ AST.JSLOne $1 {- 'ExportsList1' -} }
11901222
| ExportsList Comma ExportSpecifier
@@ -1193,11 +1225,11 @@ ExportsList : ExportSpecifier
11931225
-- ExportSpecifier :
11941226
-- IdentifierName
11951227
-- IdentifierName as IdentifierName
1196-
ExportSpecifier :: { AST.JSExportSpecifier }
1228+
ExportSpecifier :: { AST.JSExportLocalSpecifier }
11971229
ExportSpecifier : IdentifierName
1198-
{ AST.JSExportSpecifier (identName $1) {- 'ExportSpecifier1' -} }
1230+
{ AST.JSExportLocalSpecifier (identName $1) {- 'ExportSpecifier1' -} }
11991231
| IdentifierName As IdentifierName
1200-
{ AST.JSExportSpecifierAs (identName $1) $2 (identName $3) {- 'ExportSpecifier2' -} }
1232+
{ AST.JSExportLocalSpecifierAs (identName $1) $2 (identName $3) {- 'ExportSpecifier2' -} }
12011233
12021234
-- For debugging/other entry points
12031235
LiteralMain :: { AST.JSAST }

src/Language/JavaScript/Parser/Parser.hs

Lines changed: 25 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
11
module Language.JavaScript.Parser.Parser (
22
-- * Parsing
33
parse
4+
, parseModule
45
, readJs
6+
, readJsModule
57
-- , readJsKeepComments
68
, parseFile
79
, parseFileUtf8
@@ -12,28 +14,44 @@ module Language.JavaScript.Parser.Parser (
1214
, showStrippedMaybe
1315
) where
1416

15-
import Language.JavaScript.Parser.Grammar7
17+
import qualified Language.JavaScript.Parser.Grammar7 as P
1618
import Language.JavaScript.Parser.Lexer
1719
import qualified Language.JavaScript.Parser.AST as AST
1820
import System.IO
1921

20-
-- | Parse one compound statement, or a sequence of simple statements.
22+
-- | Parse JavaScript Program (Script)
23+
-- Parse one compound statement, or a sequence of simple statements.
2124
-- Generally used for interactive input, such as from the command line of an interpreter.
2225
-- Return comments in addition to the parsed statements.
2326
parse :: String -- ^ The input stream (Javascript source code).
2427
-> String -- ^ The name of the Javascript source (filename or input device).
25-
-> Either String AST.JSAST
28+
-> Either String AST.JSAST
2629
-- ^ An error or maybe the abstract syntax tree (AST) of zero
2730
-- or more Javascript statements, plus comments.
28-
parse input _srcName = runAlex input parseProgram
31+
parse = parseUsing P.parseProgram
2932

33+
-- | Parse JavaScript module
34+
parseModule :: String -- ^ The input stream (JavaScript source code).
35+
-> String -- ^ The name of the JavaScript source (filename or input device).
36+
-> Either String AST.JSAST
37+
-- ^ An error or maybe the abstract syntax tree (AST) of zero
38+
-- or more JavaScript statements, plus comments.
39+
parseModule = parseUsing P.parseModule
3040

31-
readJs :: String -> AST.JSAST
32-
readJs input =
33-
case parse input "src" of
41+
readJsWith :: (String -> String -> Either String AST.JSAST)
42+
-> String
43+
-> AST.JSAST
44+
readJsWith f input =
45+
case f input "src" of
3446
Left msg -> error (show msg)
3547
Right p -> p
3648

49+
readJs :: String -> AST.JSAST
50+
readJs = readJsWith parse
51+
52+
readJsModule :: String -> AST.JSAST
53+
readJsModule = readJsWith parseModule
54+
3755
-- | Parse the given file.
3856
-- For UTF-8 support, make sure your locale is set such that
3957
-- "System.IO.localeEncoding" returns "utf8"
@@ -74,4 +92,3 @@ parseUsing ::
7492
-- or more Javascript statements, plus comments.
7593

7694
parseUsing p input _srcName = runAlex input p
77-

src/Language/JavaScript/Pretty/Printer.hs

Lines changed: 15 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ class RenderJS a where
5555

5656
instance RenderJS JSAST where
5757
(|>) pacc (JSAstProgram xs a) = pacc |> xs |> a
58+
(|>) pacc (JSAstModule xs a) = pacc |> xs |> a
5859
(|>) pacc (JSAstStatement s a) = pacc |> s |> a
5960
(|>) pacc (JSAstExpression e a) = pacc |> e |> a
6061
(|>) pacc (JSAstLiteral x a) = pacc |> x |> a
@@ -239,11 +240,17 @@ instance RenderJS JSStatement where
239240
(|>) pacc (JSVariable annot xs s) = pacc |> annot |> "var" |> xs |> s
240241
(|>) pacc (JSWhile annot alp x1 arp x2) = pacc |> annot |> "while" |> alp |> "(" |> x1 |> arp |> ")" |> x2
241242
(|>) pacc (JSWith annot alp x1 arp x s) = pacc |> annot |> "with" |> alp |> "(" |> x1 |> arp |> ")" |> x |> s
242-
(|>) pacc (JSExport annot b s) = pacc |> annot |> "export" |> b |> s
243243

244244
instance RenderJS [JSStatement] where
245245
(|>) = foldl' (|>)
246246

247+
instance RenderJS [JSModuleItem] where
248+
(|>) = foldl' (|>)
249+
250+
instance RenderJS JSModuleItem where
251+
(|>) pacc (JSModuleExportDeclaration annot decl) = pacc |> annot |> "export" |> decl
252+
(|>) pacc (JSModuleStatementListItem s) = pacc |> s
253+
247254
instance RenderJS JSBlock where
248255
(|>) pacc (JSBlock alb ss arb) = pacc |> alb |> "{" |> ss |> arb |> "}"
249256

@@ -267,14 +274,14 @@ instance RenderJS JSArrayElement where
267274
instance RenderJS [JSArrayElement] where
268275
(|>) = foldl' (|>)
269276

270-
instance RenderJS JSExportBody where
271-
(|>) pacc (JSExportStatement s) = pacc |> " " |> s
272-
(|>) pacc (JSExportClause alb Nothing arb) = pacc |> alb |> "{}" |> arb
273-
(|>) pacc (JSExportClause alb (Just s) arb) = pacc |> alb |> "{" |> s |> "}" |> arb
277+
instance RenderJS JSExportDeclaration where
278+
(|>) pacc (JSExport x1 s) = pacc |> " " |> x1 |> s
279+
(|>) pacc (JSExportLocals alb JSLNil arb semi) = pacc |> alb |> "{" |> arb |> "}" |> semi
280+
(|>) pacc (JSExportLocals alb s arb semi) = pacc |> alb |> "{" |> s |> arb |> "}" |> semi
274281

275-
instance RenderJS JSExportSpecifier where
276-
(|>) pacc (JSExportSpecifier i) = pacc |> i
277-
(|>) pacc (JSExportSpecifierAs x1 as x2) = pacc |> x1 |> as |> x2
282+
instance RenderJS JSExportLocalSpecifier where
283+
(|>) pacc (JSExportLocalSpecifier i) = pacc |> i
284+
(|>) pacc (JSExportLocalSpecifierAs x1 as x2) = pacc |> x1 |> as |> x2
278285

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

0 commit comments

Comments
 (0)