Skip to content

Commit 366b684

Browse files
committed
Add support for ES module import statements
This commit adds support for all forms of the ES module import statement apart from the dynamic 'import()' form and the bare 'import "mod";' form (where the import is only being performed for the sake of some side effects). Supercedes #77, refs #71.
1 parent 5257216 commit 366b684

File tree

9 files changed

+219
-7
lines changed

9 files changed

+219
-7
lines changed

Diff for: src/Language/JavaScript/Parser/AST.hs

+67-2
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,12 @@ module Language.JavaScript.Parser.AST
2525

2626
-- Modules
2727
, JSModuleItem (..)
28+
, JSImportDeclaration (..)
29+
, JSImportClause (..)
30+
, JSFromClause (..)
31+
, JSImportNameSpace (..)
32+
, JSImportsNamed (..)
33+
, JSImportSpecifier (..)
2834
, JSExportDeclaration (..)
2935
, JSExportLocalSpecifier (..)
3036

@@ -57,11 +63,46 @@ data JSAST
5763
-- Shift AST
5864
-- https://github.com/shapesecurity/shift-spec/blob/83498b92c436180cc0e2115b225a68c08f43c53e/spec.idl#L229-L234
5965
data JSModuleItem
60-
-- = JSImportDeclaration
61-
= JSModuleExportDeclaration !JSAnnot !JSExportDeclaration -- ^export,decl
66+
= JSModuleImportDeclaration !JSAnnot !JSImportDeclaration -- ^import,decl
67+
| JSModuleExportDeclaration !JSAnnot !JSExportDeclaration -- ^export,decl
6268
| JSModuleStatementListItem !JSStatement
6369
deriving (Data, Eq, Show, Typeable)
6470

71+
data JSImportDeclaration
72+
= JSImportDeclaration !JSImportClause !JSFromClause !JSSemi -- ^imports, module, semi
73+
-- | JSImportDeclarationBare -- ^ module, semi
74+
deriving (Data, Eq, Show, Typeable)
75+
76+
data JSImportClause
77+
= JSImportClauseDefault !JSIdent -- ^default
78+
| JSImportClauseNameSpace !JSImportNameSpace -- ^namespace
79+
| JSImportClauseNamed !JSImportsNamed -- ^named imports
80+
| JSImportClauseDefaultNameSpace !JSIdent !JSAnnot !JSImportNameSpace -- ^default, comma, namespace
81+
| JSImportClauseDefaultNamed !JSIdent !JSAnnot !JSImportsNamed -- ^default, comma, named imports
82+
deriving (Data, Eq, Show, Typeable)
83+
84+
data JSFromClause
85+
= JSFromClause !JSAnnot !JSAnnot !String -- ^ from, string literal, string literal contents
86+
deriving (Data, Eq, Show, Typeable)
87+
88+
-- | Import namespace, e.g. '* as whatever'
89+
data JSImportNameSpace
90+
= JSImportNameSpace !JSBinOp !JSBinOp !JSIdent -- ^ *, as, ident
91+
deriving (Data, Eq, Show, Typeable)
92+
93+
-- | Named imports, e.g. '{ foo, bar, baz as quux }'
94+
data JSImportsNamed
95+
= JSImportsNamed !JSAnnot !(JSCommaList JSImportSpecifier) !JSAnnot -- ^lb, specifiers, rb
96+
deriving (Data, Eq, Show, Typeable)
97+
98+
-- |
99+
-- Note that this data type is separate from ExportSpecifier because the
100+
-- grammar is slightly different (e.g. in handling of reserved words).
101+
data JSImportSpecifier
102+
= JSImportSpecifier !JSIdent -- ^ident
103+
| JSImportSpecifierAs !JSIdent !JSBinOp !JSIdent -- ^ident, as, ident
104+
deriving (Data, Eq, Show, Typeable)
105+
65106
data JSExportDeclaration
66107
-- = JSExportAllFrom
67108
-- | JSExportFrom
@@ -338,8 +379,32 @@ instance ShowStripped JSExpression where
338379

339380
instance ShowStripped JSModuleItem where
340381
ss (JSModuleExportDeclaration _ x1) = "JSModuleExportDeclaration (" ++ ss x1 ++ ")"
382+
ss (JSModuleImportDeclaration _ x1) = "JSModuleImportDeclaration (" ++ ss x1 ++ ")"
341383
ss (JSModuleStatementListItem x1) = "JSModuleStatementListItem (" ++ ss x1 ++ ")"
342384

385+
instance ShowStripped JSImportDeclaration where
386+
ss (JSImportDeclaration imp from _) = "JSImportDeclaration (" ++ ss imp ++ "," ++ ss from ++ ")"
387+
388+
instance ShowStripped JSImportClause where
389+
ss (JSImportClauseDefault x) = "JSImportClauseDefault (" ++ ss x ++ ")"
390+
ss (JSImportClauseNameSpace x) = "JSImportClauseNameSpace (" ++ ss x ++ ")"
391+
ss (JSImportClauseNamed x) = "JSImportClauseNameSpace (" ++ ss x ++ ")"
392+
ss (JSImportClauseDefaultNameSpace x1 _ x2) = "JSImportClauseDefaultNameSpace (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
393+
ss (JSImportClauseDefaultNamed x1 _ x2) = "JSImportClauseDefaultNamed (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
394+
395+
instance ShowStripped JSFromClause where
396+
ss (JSFromClause _ _ m) = "JSFromClause " ++ singleQuote m
397+
398+
instance ShowStripped JSImportNameSpace where
399+
ss (JSImportNameSpace _ _ x) = "JSImportNameSpace (" ++ ss x ++ ")"
400+
401+
instance ShowStripped JSImportsNamed where
402+
ss (JSImportsNamed _ xs _) = "JSImportsNamed (" ++ ss xs ++ ")"
403+
404+
instance ShowStripped JSImportSpecifier where
405+
ss (JSImportSpecifier x1) = "JSImportSpecifier (" ++ ss x1 ++ ")"
406+
ss (JSImportSpecifierAs x1 _ x2) = "JSImportSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
407+
343408
instance ShowStripped JSExportDeclaration where
344409
ss (JSExportLocals _ xs _ _) = "JSExportLocals (" ++ ss xs ++ ")"
345410
ss (JSExport x1 _) = "JSExport (" ++ ss x1 ++ ")"

Diff for: src/Language/JavaScript/Parser/Grammar7.y

+53-1
Original file line numberDiff line numberDiff line change
@@ -101,8 +101,10 @@ import qualified Language.JavaScript.Parser.AST as AST
101101
'finally' { FinallyToken {} }
102102
'for' { ForToken {} }
103103
'function' { FunctionToken {} }
104+
'from' { FromToken {} }
104105
'get' { GetToken {} }
105106
'if' { IfToken {} }
107+
'import' { ImportToken {} }
106108
'in' { InToken {} }
107109
'instanceof' { InstanceofToken {} }
108110
'let' { LetToken {} }
@@ -312,6 +314,12 @@ Let : 'let' { mkJSAnnot $1 }
312314
Const :: { AST.JSAnnot }
313315
Const : 'const' { mkJSAnnot $1 }
314316

317+
Import :: { AST.JSAnnot }
318+
Import : 'import' { mkJSAnnot $1 }
319+
320+
From :: { AST.JSAnnot }
321+
From : 'from' { mkJSAnnot $1 }
322+
315323
Export :: { AST.JSAnnot }
316324
Export : 'export' { mkJSAnnot $1 }
317325

@@ -432,6 +440,7 @@ Identifier :: { AST.JSExpression }
432440
Identifier : 'ident' { AST.JSIdentifier (mkJSAnnot $1) (tokenLiteral $1) }
433441
| 'get' { AST.JSIdentifier (mkJSAnnot $1) "get" }
434442
| 'set' { AST.JSIdentifier (mkJSAnnot $1) "set" }
443+
| 'from' { AST.JSIdentifier (mkJSAnnot $1) "from" }
435444

436445
-- TODO: make this include any reserved word too, including future ones
437446
IdentifierName :: { AST.JSExpression }
@@ -453,6 +462,7 @@ IdentifierName : Identifier {$1}
453462
| 'finally' { AST.JSIdentifier (mkJSAnnot $1) "finally" }
454463
| 'for' { AST.JSIdentifier (mkJSAnnot $1) "for" }
455464
| 'function' { AST.JSIdentifier (mkJSAnnot $1) "function" }
465+
| 'from' { AST.JSIdentifier (mkJSAnnot $1) "from" }
456466
| 'get' { AST.JSIdentifier (mkJSAnnot $1) "get" }
457467
| 'if' { AST.JSIdentifier (mkJSAnnot $1) "if" }
458468
| 'in' { AST.JSIdentifier (mkJSAnnot $1) "in" }
@@ -1183,11 +1193,53 @@ ModuleItemList : ModuleItem { [$1] {- 'ModuleItemList1'
11831193
-- ExportDeclaration
11841194
-- StatementListItem
11851195
ModuleItem :: { AST.JSModuleItem }
1186-
ModuleItem : Export ExportDeclaration
1196+
ModuleItem : Import ImportDeclaration
1197+
{ AST.JSModuleImportDeclaration $1 $2 {- 'ModuleItem1' -} }
1198+
| Export ExportDeclaration
11871199
{ AST.JSModuleExportDeclaration $1 $2 {- 'ModuleItem1' -} }
11881200
| StatementListItem
11891201
{ AST.JSModuleStatementListItem $1 {- 'ModuleItem2' -} }
11901202
1203+
ImportDeclaration :: { AST.JSImportDeclaration }
1204+
ImportDeclaration : ImportClause FromClause AutoSemi
1205+
{ AST.JSImportDeclaration $1 $2 $3 }
1206+
1207+
ImportClause :: { AST.JSImportClause }
1208+
ImportClause : IdentifierName
1209+
{ AST.JSImportClauseDefault (identName $1) }
1210+
| NameSpaceImport
1211+
{ AST.JSImportClauseNameSpace $1 }
1212+
| NamedImports
1213+
{ AST.JSImportClauseNamed $1 }
1214+
| IdentifierName ',' NameSpaceImport
1215+
{ AST.JSImportClauseDefaultNameSpace (identName $1) (mkJSAnnot $2) $3 }
1216+
| IdentifierName ',' NamedImports
1217+
{ AST.JSImportClauseDefaultNamed (identName $1) (mkJSAnnot $2) $3 }
1218+
1219+
FromClause :: { AST.JSFromClause }
1220+
FromClause : From 'string'
1221+
{ AST.JSFromClause $1 (mkJSAnnot $2) (tokenLiteral $2) }
1222+
1223+
NameSpaceImport :: { AST.JSImportNameSpace }
1224+
NameSpaceImport : Mul As IdentifierName
1225+
{ AST.JSImportNameSpace $1 $2 (identName $3) }
1226+
1227+
NamedImports :: { AST.JSImportsNamed }
1228+
NamedImports : LBrace ImportsList RBrace
1229+
{ AST.JSImportsNamed $1 $2 $3 }
1230+
1231+
ImportsList :: { AST.JSCommaList AST.JSImportSpecifier }
1232+
ImportsList : ImportSpecifier
1233+
{ AST.JSLOne $1 }
1234+
| ImportsList Comma ImportSpecifier
1235+
{ AST.JSLCons $1 $2 $3 }
1236+
1237+
ImportSpecifier :: { AST.JSImportSpecifier }
1238+
ImportSpecifier : IdentifierName
1239+
{ AST.JSImportSpecifier (identName $1) }
1240+
| IdentifierName As IdentifierName
1241+
{ AST.JSImportSpecifierAs (identName $1) $2 (identName $3) }
1242+
11911243
-- ExportDeclaration : See 15.2.3
11921244
-- [ ] export * FromClause ;
11931245
-- [ ] export ExportClause FromClause ;

Diff for: src/Language/JavaScript/Parser/Lexer.x

+2-2
Original file line numberDiff line numberDiff line change
@@ -525,7 +525,9 @@ keywordNames =
525525
, ( "finally", FinallyToken )
526526
, ( "for", ForToken )
527527
, ( "function", FunctionToken )
528+
, ( "from", FromToken )
528529
, ( "if", IfToken )
530+
, ( "import", ImportToken )
529531
, ( "in", InToken )
530532
, ( "instanceof", InstanceofToken )
531533
, ( "let", LetToken )
@@ -566,8 +568,6 @@ keywordNames =
566568
-- ( "const", FutureToken ) **** an actual token, used in productions
567569
-- enum **** an actual token, used in productions
568570
, ( "extends", FutureToken )
569-
570-
, ( "import", FutureToken )
571571
, ( "super", FutureToken )
572572
573573

Diff for: src/Language/JavaScript/Parser/Token.hs

+2
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,7 @@ data Token
7373
| FinallyToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
7474
| ForToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
7575
| FunctionToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
76+
| FromToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
7677
| IfToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
7778
| InToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
7879
| InstanceofToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
@@ -88,6 +89,7 @@ data Token
8889
| VarToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
8990
| VoidToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
9091
| WhileToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
92+
| ImportToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
9193
| WithToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
9294
| ExportToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
9395
-- Future reserved words

Diff for: src/Language/JavaScript/Pretty/Printer.hs

+24
Original file line numberDiff line numberDiff line change
@@ -248,6 +248,7 @@ instance RenderJS [JSModuleItem] where
248248
(|>) = foldl' (|>)
249249

250250
instance RenderJS JSModuleItem where
251+
(|>) pacc (JSModuleImportDeclaration annot decl) = pacc |> annot |> "import" |> decl
251252
(|>) pacc (JSModuleExportDeclaration annot decl) = pacc |> annot |> "export" |> decl
252253
(|>) pacc (JSModuleStatementListItem s) = pacc |> s
253254

@@ -274,6 +275,29 @@ instance RenderJS JSArrayElement where
274275
instance RenderJS [JSArrayElement] where
275276
(|>) = foldl' (|>)
276277

278+
instance RenderJS JSImportDeclaration where
279+
(|>) pacc (JSImportDeclaration imp from annot) = pacc |> imp |> from |> annot
280+
281+
instance RenderJS JSImportClause where
282+
(|>) pacc (JSImportClauseDefault x) = pacc |> x
283+
(|>) pacc (JSImportClauseNameSpace x) = pacc |> x
284+
(|>) pacc (JSImportClauseNamed x) = pacc |> x
285+
(|>) pacc (JSImportClauseDefaultNameSpace x1 annot x2) = pacc |> x1 |> annot |> "," |> x2
286+
(|>) pacc (JSImportClauseDefaultNamed x1 annot x2) = pacc |> x1 |> annot |> "," |> x2
287+
288+
instance RenderJS JSFromClause where
289+
(|>) pacc (JSFromClause from annot m) = pacc |> from |> "from" |> annot |> m
290+
291+
instance RenderJS JSImportNameSpace where
292+
(|>) pacc (JSImportNameSpace star as x) = pacc |> star |> as |> x
293+
294+
instance RenderJS JSImportsNamed where
295+
(|>) pacc (JSImportsNamed lb xs rb) = pacc |> lb |> "{" |> xs |> rb |> "}"
296+
297+
instance RenderJS JSImportSpecifier where
298+
(|>) pacc (JSImportSpecifier x1) = pacc |> x1
299+
(|>) pacc (JSImportSpecifierAs x1 as x2) = pacc |> x1 |> as |> x2
300+
277301
instance RenderJS JSExportDeclaration where
278302
(|>) pacc (JSExport x1 s) = pacc |> " " |> x1 |> s
279303
(|>) pacc (JSExportLocals alb JSLNil arb semi) = pacc |> alb |> "{" |> arb |> "}" |> semi

Diff for: src/Language/JavaScript/Process/Minify.hs

+31
Original file line numberDiff line numberDiff line change
@@ -268,9 +268,40 @@ instance MinifyJS JSAssignOp where
268268
fix a (JSBwOrAssign _) = JSBwOrAssign a
269269

270270
instance MinifyJS JSModuleItem where
271+
fix _ (JSModuleImportDeclaration _ x1) = JSModuleImportDeclaration emptyAnnot (fixEmpty x1)
271272
fix _ (JSModuleExportDeclaration _ x1) = JSModuleExportDeclaration emptyAnnot (fixEmpty x1)
272273
fix a (JSModuleStatementListItem s) = JSModuleStatementListItem (fixStmt a noSemi s)
273274

275+
instance MinifyJS JSImportDeclaration where
276+
fix _ (JSImportDeclaration imps from _) = JSImportDeclaration (fixEmpty imps) (fix annot from) noSemi
277+
where
278+
annot = case imps of
279+
JSImportClauseDefault {} -> spaceAnnot
280+
JSImportClauseNameSpace {} -> spaceAnnot
281+
JSImportClauseNamed {} -> emptyAnnot
282+
JSImportClauseDefaultNameSpace {} -> spaceAnnot
283+
JSImportClauseDefaultNamed {} -> emptyAnnot
284+
285+
instance MinifyJS JSImportClause where
286+
fix _ (JSImportClauseDefault n) = JSImportClauseDefault (fixSpace n)
287+
fix _ (JSImportClauseNameSpace ns) = JSImportClauseNameSpace (fixSpace ns)
288+
fix _ (JSImportClauseNamed named) = JSImportClauseNamed (fixEmpty named)
289+
fix _ (JSImportClauseDefaultNameSpace def _ ns) = JSImportClauseDefaultNameSpace (fixSpace def) emptyAnnot (fixEmpty ns)
290+
fix _ (JSImportClauseDefaultNamed def _ ns) = JSImportClauseDefaultNamed (fixSpace def) emptyAnnot (fixEmpty ns)
291+
292+
instance MinifyJS JSFromClause where
293+
fix a (JSFromClause _ _ m) = JSFromClause a emptyAnnot m
294+
295+
instance MinifyJS JSImportNameSpace where
296+
fix a (JSImportNameSpace _ _ ident) = JSImportNameSpace (JSBinOpTimes a) (JSBinOpAs spaceAnnot) (fixSpace ident)
297+
298+
instance MinifyJS JSImportsNamed where
299+
fix _ (JSImportsNamed _ imps _) = JSImportsNamed emptyAnnot (fixEmpty imps) emptyAnnot
300+
301+
instance MinifyJS JSImportSpecifier where
302+
fix _ (JSImportSpecifier x1) = JSImportSpecifier (fixEmpty x1)
303+
fix _ (JSImportSpecifierAs x1 as x2) = JSImportSpecifierAs (fixEmpty x1) (fixSpace as) (fixSpace x2)
304+
274305
instance MinifyJS JSExportDeclaration where
275306
fix _ (JSExportLocals _ x1 _ _) = JSExportLocals emptyAnnot (fixEmpty x1) emptyAnnot noSemi
276307
fix _ (JSExport x1 _) = JSExport (fixStmt emptyAnnot noSemi x1) noSemi

Diff for: test/Test/Language/Javascript/Minify.hs

+8-1
Original file line numberDiff line numberDiff line change
@@ -255,7 +255,14 @@ testMinifyProg = describe "Minify programs:" $ do
255255
minifyProg " try { } catch (a) {} finally {} ; try { } catch ( b ) { } ; " `shouldBe` "try{}catch(a){}finally{}try{}catch(b){}"
256256

257257
testMinifyModule :: Spec
258-
testMinifyModule = describe "Minify modules:" $
258+
testMinifyModule = describe "Minify modules:" $ do
259+
it "import" $ do
260+
minifyModule "import def from 'mod' ; " `shouldBe` "import def from'mod'"
261+
minifyModule "import * as foo from \"mod\" ; " `shouldBe` "import * as foo from\"mod\""
262+
minifyModule "import def, * as foo from \"mod\" ; " `shouldBe` "import def,* as foo from\"mod\""
263+
minifyModule "import { baz, bar as foo } from \"mod\" ; " `shouldBe` "import{baz,bar as foo}from\"mod\""
264+
minifyModule "import def, { baz, bar as foo } from \"mod\" ; " `shouldBe` "import def,{baz,bar as foo}from\"mod\""
265+
259266
it "export" $ do
260267
minifyModule " export { } ; " `shouldBe` "export{}"
261268
minifyModule " export { a } ; " `shouldBe` "export{a}"

Diff for: test/Test/Language/Javascript/ModuleParser.hs

+25-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,30 @@ import Language.JavaScript.Parser
88

99

1010
testModuleParser :: Spec
11-
testModuleParser = describe "Parse modules:" $
11+
testModuleParser = describe "Parse modules:" $ do
12+
it "import" $ do
13+
-- Not yet supported
14+
-- test "import 'a';" `shouldBe` ""
15+
16+
test "import def from 'mod';"
17+
`shouldBe`
18+
"Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefault (JSIdentifier 'def'),JSFromClause ''mod''))])"
19+
test "import def from \"mod\";"
20+
`shouldBe`
21+
"Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefault (JSIdentifier 'def'),JSFromClause '\"mod\"'))])"
22+
test "import * as thing from 'mod';"
23+
`shouldBe`
24+
"Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseNameSpace (JSImportNameSpace (JSIdentifier 'thing')),JSFromClause ''mod''))])"
25+
test "import { foo, bar, baz as quux } from 'mod';"
26+
`shouldBe`
27+
"Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseNameSpace (JSImportsNamed ((JSImportSpecifier (JSIdentifier 'foo'),JSImportSpecifier (JSIdentifier 'bar'),JSImportSpecifierAs (JSIdentifier 'baz',JSIdentifier 'quux')))),JSFromClause ''mod''))])"
28+
test "import def, * as thing from 'mod';"
29+
`shouldBe`
30+
"Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefaultNameSpace (JSIdentifier 'def',JSImportNameSpace (JSIdentifier 'thing')),JSFromClause ''mod''))])"
31+
test "import def, { foo, bar, baz as quux } from 'mod';"
32+
`shouldBe`
33+
"Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefaultNamed (JSIdentifier 'def',JSImportsNamed ((JSImportSpecifier (JSIdentifier 'foo'),JSImportSpecifier (JSIdentifier 'bar'),JSImportSpecifierAs (JSIdentifier 'baz',JSIdentifier 'quux')))),JSFromClause ''mod''))])"
34+
1235
it "export" $ do
1336
test "export {}"
1437
`shouldBe`
@@ -26,5 +49,6 @@ testModuleParser = describe "Parse modules:" $
2649
`shouldBe`
2750
"Right (JSAstModule [JSModuleExportDeclaration (JSExportLocals ((JSExportLocalSpecifierAs (JSIdentifier 'a',JSIdentifier 'b'))))])"
2851

52+
2953
test :: String -> String
3054
test str = showStrippedMaybe (parseModule str "src")

Diff for: test/Test/Language/Javascript/RoundTrip.hs

+7
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,13 @@ testRoundTrip = describe "Roundtrip:" $ do
101101
testRT "var x=1;let y=2;"
102102

103103
it "module" $ do
104+
testRTModule "import def from 'mod'"
105+
testRTModule "import def from \"mod\";"
106+
testRTModule "import * as foo from \"mod\" ; "
107+
testRTModule "import def, * as foo from \"mod\" ; "
108+
testRTModule "import { baz, bar as foo } from \"mod\" ; "
109+
testRTModule "import def, { baz, bar as foo } from \"mod\" ; "
110+
104111
testRTModule "export {};"
105112
testRTModule " export {} ; "
106113
testRTModule "export { a , b , c };"

0 commit comments

Comments
 (0)