1+ {-# LANGUAGE OverloadedStrings #-}
2+ module Test.Language.Javascript.ExportStar
3+ ( testExportStar
4+ ) where
5+
6+ import Test.Hspec
7+ import Language.JavaScript.Parser
8+ import qualified Language.JavaScript.Parser.AST as AST
9+
10+ -- | Comprehensive test suite for export * from 'module' syntax
11+ testExportStar :: Spec
12+ testExportStar = describe " Export Star Syntax Tests" $ do
13+
14+ describe " basic export * parsing" $ do
15+ it " parses export * from 'module'" $ do
16+ case parseModule " export * from 'module';" " test" of
17+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
18+ pure ()
19+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
20+ Left err -> expectationFailure (" Parse failed: " ++ show err)
21+
22+ it " parses export * from double quotes" $ do
23+ case parseModule " export * from \" module\" ;" " test" of
24+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
25+ pure ()
26+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
27+ Left err -> expectationFailure (" Parse failed: " ++ show err)
28+
29+ it " parses export * without semicolon" $ do
30+ case parseModule " export * from 'module'" " test" of
31+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
32+ pure ()
33+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
34+ Left err -> expectationFailure (" Parse failed: " ++ show err)
35+
36+ describe " module specifier variations" $ do
37+ it " parses relative paths" $ do
38+ case parseModule " export * from './utils';" " test" of
39+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
40+ pure ()
41+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
42+ Left err -> expectationFailure (" Parse failed: " ++ show err)
43+
44+ it " parses parent directory paths" $ do
45+ case parseModule " export * from '../parent';" " test" of
46+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
47+ pure ()
48+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
49+ Left err -> expectationFailure (" Parse failed: " ++ show err)
50+
51+ it " parses scoped packages" $ do
52+ case parseModule " export * from '@scope/package';" " test" of
53+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
54+ pure ()
55+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
56+ Left err -> expectationFailure (" Parse failed: " ++ show err)
57+
58+ it " parses file extensions" $ do
59+ case parseModule " export * from './file.js';" " test" of
60+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
61+ pure ()
62+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
63+ Left err -> expectationFailure (" Parse failed: " ++ show err)
64+
65+ describe " whitespace handling" $ do
66+ it " handles extra whitespace" $ do
67+ case parseModule " export * from 'module' ;" " test" of
68+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
69+ pure ()
70+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
71+ Left err -> expectationFailure (" Parse failed: " ++ show err)
72+
73+ it " handles newlines" $ do
74+ case parseModule " export\n *\n from\n 'module';" " test" of
75+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
76+ pure ()
77+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
78+ Left err -> expectationFailure (" Parse failed: " ++ show err)
79+
80+ it " handles tabs" $ do
81+ case parseModule " export\t *\t from\t 'module';" " test" of
82+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
83+ pure ()
84+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
85+ Left err -> expectationFailure (" Parse failed: " ++ show err)
86+
87+ describe " comment handling" $ do
88+ it " handles comments before *" $ do
89+ case parseModule " export /* comment */ * from 'module';" " test" of
90+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
91+ pure ()
92+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
93+ Left err -> expectationFailure (" Parse failed: " ++ show err)
94+
95+ it " handles comments after *" $ do
96+ case parseModule " export * /* comment */ from 'module';" " test" of
97+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
98+ pure ()
99+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
100+ Left err -> expectationFailure (" Parse failed: " ++ show err)
101+
102+ it " handles comments before from" $ do
103+ case parseModule " export * from /* comment */ 'module';" " test" of
104+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
105+ pure ()
106+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
107+ Left err -> expectationFailure (" Parse failed: " ++ show err)
108+
109+ describe " multiple export statements" $ do
110+ it " parses multiple export * statements" $ do
111+ let input = unlines
112+ [ " export * from 'module1';"
113+ , " export * from 'module2';"
114+ , " export * from 'module3';"
115+ ]
116+ case parseModule input " test" of
117+ Right (AST. JSAstModule stmts _) -> do
118+ length stmts `shouldBe` 3
119+ -- Verify all are export declarations
120+ let isExportStar (AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)) = True
121+ isExportStar _ = False
122+ all isExportStar stmts `shouldBe` True
123+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
124+ Left err -> expectationFailure (" Parse failed: " ++ show err)
125+
126+ it " parses mixed export types" $ do
127+ let input = unlines
128+ [ " export * from 'all';"
129+ , " export { specific } from 'named';"
130+ , " export const local = 42;"
131+ ]
132+ case parseModule input " test" of
133+ Right (AST. JSAstModule stmts _) -> do
134+ length stmts `shouldBe` 3
135+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
136+ Left err -> expectationFailure (" Parse failed: " ++ show err)
137+
138+ describe " complex module names" $ do
139+ it " handles Unicode in module names" $ do
140+ case parseModule " export * from './файл';" " test" of
141+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
142+ pure ()
143+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
144+ Left err -> expectationFailure (" Parse failed: " ++ show err)
145+
146+ it " handles special characters" $ do
147+ case parseModule " export * from './file-with-dashes_and_underscores.module.js';" " test" of
148+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
149+ pure ()
150+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
151+ Left err -> expectationFailure (" Parse failed: " ++ show err)
152+
153+ it " handles empty string (edge case)" $ do
154+ case parseModule " export * from '';" " test" of
155+ Right (AST. JSAstModule [AST. JSModuleExportDeclaration _ (AST. JSExportAllFrom _ _ _)] _) ->
156+ pure ()
157+ Right other -> expectationFailure (" Unexpected AST: " ++ show other)
158+ Left err -> expectationFailure (" Parse failed: " ++ show err)
159+
160+ describe " error conditions" $ do
161+ it " rejects missing 'from' keyword" $ do
162+ case parseModule " export * 'module';" " test" of
163+ Left _ -> pure () -- Should fail
164+ Right _ -> expectationFailure " Expected parse error for missing 'from'"
165+
166+ it " rejects missing module specifier" $ do
167+ case parseModule " export * from;" " test" of
168+ Left _ -> pure () -- Should fail
169+ Right _ -> expectationFailure " Expected parse error for missing module specifier"
170+
171+ it " rejects non-string module specifier" $ do
172+ case parseModule " export * from identifier;" " test" of
173+ Left _ -> pure () -- Should fail
174+ Right _ -> expectationFailure " Expected parse error for non-string module specifier"
175+
176+ it " rejects numeric module specifier" $ do
177+ case parseModule " export * from 123;" " test" of
178+ Left _ -> pure () -- Should fail
179+ Right _ -> expectationFailure " Expected parse error for numeric module specifier"
0 commit comments