1
+ {-# LANGUAGE BangPatterns #-}
2
+ module Test.Language.Javascript.Generic
3
+ ( testGenericNFData
4
+ ) where
5
+
6
+ import Control.DeepSeq (rnf )
7
+ import GHC.Generics (from , to )
8
+ import Test.Hspec
9
+
10
+ import Language.JavaScript.Parser.Grammar7
11
+ import Language.JavaScript.Parser.Parser
12
+ import qualified Language.JavaScript.Parser.AST as AST
13
+
14
+ testGenericNFData :: Spec
15
+ testGenericNFData = describe " Generic and NFData instances" $ do
16
+ describe " NFData instances" $ do
17
+ it " can deep evaluate simple expressions" $ do
18
+ case parseUsing parseExpression " 42" " test" of
19
+ Right ast -> do
20
+ -- Test that NFData deep evaluation completes without exception
21
+ let ! evaluated = rnf ast `seq` ast
22
+ -- Verify the AST structure is preserved after deep evaluation
23
+ case evaluated of
24
+ AST. JSAstExpression (AST. JSDecimal _ " 42" ) _ -> pure ()
25
+ _ -> expectationFailure " NFData evaluation altered AST structure"
26
+ Left _ -> expectationFailure " Parse failed"
27
+
28
+ it " can deep evaluate complex expressions" $ do
29
+ case parseUsing parseExpression " foo.bar[baz](arg1, arg2)" " test" of
30
+ Right ast -> do
31
+ -- Test that NFData handles complex nested structures
32
+ let ! evaluated = rnf ast `seq` ast
33
+ -- Verify complex expression maintains structure (any valid expression)
34
+ case evaluated of
35
+ AST. JSAstExpression _ _ -> pure ()
36
+ _ -> expectationFailure " NFData failed to preserve expression structure"
37
+ Left _ -> expectationFailure " Parse failed"
38
+
39
+ it " can deep evaluate object literals" $ do
40
+ case parseUsing parseExpression " {a: 1, b: 2, ...obj}" " test" of
41
+ Right ast -> do
42
+ -- Test NFData with object literal containing spread syntax
43
+ let ! evaluated = rnf ast `seq` ast
44
+ -- Verify object literal structure is preserved
45
+ case evaluated of
46
+ AST. JSAstExpression (AST. JSObjectLiteral {}) _ -> pure ()
47
+ _ -> expectationFailure " NFData failed to preserve object literal structure"
48
+ Left _ -> expectationFailure " Parse failed"
49
+
50
+ it " can deep evaluate arrow functions" $ do
51
+ case parseUsing parseExpression " (x, y) => x + y" " test" of
52
+ Right ast -> do
53
+ -- Test NFData with arrow function expressions
54
+ let ! evaluated = rnf ast `seq` ast
55
+ -- Verify arrow function structure is maintained
56
+ case evaluated of
57
+ AST. JSAstExpression (AST. JSArrowExpression {}) _ -> pure ()
58
+ _ -> expectationFailure " NFData failed to preserve arrow function structure"
59
+ Left _ -> expectationFailure " Parse failed"
60
+
61
+ it " can deep evaluate statements" $ do
62
+ case parseUsing parseStatement " function foo(x) { return x * 2; }" " test" of
63
+ Right ast -> do
64
+ -- Test NFData with function declaration statements
65
+ let ! evaluated = rnf ast `seq` ast
66
+ -- Verify function statement structure is preserved
67
+ case evaluated of
68
+ AST. JSAstStatement (AST. JSFunction {}) _ -> pure ()
69
+ _ -> expectationFailure " NFData failed to preserve function statement structure"
70
+ Left _ -> expectationFailure " Parse failed"
71
+
72
+ it " can deep evaluate complete programs" $ do
73
+ case parseUsing parseProgram " var x = 42; function add(a, b) { return a + b; }" " test" of
74
+ Right ast -> do
75
+ -- Test NFData with complete program ASTs
76
+ let ! evaluated = rnf ast `seq` ast
77
+ -- Verify program structure contains expected elements
78
+ case evaluated of
79
+ AST. JSAstProgram stmts _ -> do
80
+ length stmts `shouldSatisfy` (>= 2 )
81
+ _ -> expectationFailure " NFData failed to preserve program structure"
82
+ Left _ -> expectationFailure " Parse failed"
83
+
84
+ it " can deep evaluate AST components" $ do
85
+ let annotation = AST. JSNoAnnot
86
+ let identifier = AST. JSIdentifier annotation " test"
87
+ let literal = AST. JSDecimal annotation " 42"
88
+ -- Test NFData on individual AST components
89
+ let ! evalAnnot = rnf annotation `seq` annotation
90
+ let ! evalIdent = rnf identifier `seq` identifier
91
+ let ! evalLiteral = rnf literal `seq` literal
92
+ -- Verify components maintain their values after evaluation
93
+ case (evalAnnot, evalIdent, evalLiteral) of
94
+ (AST. JSNoAnnot , AST. JSIdentifier _ " test" , AST. JSDecimal _ " 42" ) -> pure ()
95
+ _ -> expectationFailure " NFData evaluation altered AST component values"
96
+
97
+ describe " Generic instances" $ do
98
+ it " supports generic operations on expressions" $ do
99
+ let expr = AST. JSIdentifier AST. JSNoAnnot " test"
100
+ let generic = from expr
101
+ let reconstructed = to generic
102
+ reconstructed `shouldBe` expr
103
+
104
+ it " supports generic operations on statements" $ do
105
+ let stmt = AST. JSExpressionStatement (AST. JSIdentifier AST. JSNoAnnot " x" ) AST. JSSemiAuto
106
+ let generic = from stmt
107
+ let reconstructed = to generic
108
+ reconstructed `shouldBe` stmt
109
+
110
+ it " supports generic operations on annotations" $ do
111
+ let annot = AST. JSNoAnnot
112
+ let generic = from annot
113
+ let reconstructed = to generic
114
+ reconstructed `shouldBe` annot
115
+
116
+ it " generic instances compile correctly" $ do
117
+ -- Test that Generic instances are well-formed and functional
118
+ let expr = AST. JSDecimal AST. JSNoAnnot " 123"
119
+ let generic = from expr
120
+ let reconstructed = to generic
121
+ -- Verify Generic round-trip preserves exact structure
122
+ case (expr, reconstructed) of
123
+ (AST. JSDecimal _ " 123" , AST. JSDecimal _ " 123" ) -> pure ()
124
+ _ -> expectationFailure " Generic round-trip failed to preserve structure"
125
+ -- Verify Generic representation is meaningful (non-empty and contains structure)
126
+ let genericStr = show generic
127
+ case genericStr of
128
+ s | length s > 5 -> pure ()
129
+ _ -> expectationFailure (" Generic representation too simple: " ++ genericStr)
130
+
131
+ describe " NFData performance benefits" $ do
132
+ it " enables complete evaluation for benchmarking" $ do
133
+ case parseUsing parseProgram complexJavaScript " test" of
134
+ Right ast -> do
135
+ -- Test that NFData enables complete evaluation for performance testing
136
+ let ! evaluated = rnf ast `seq` ast
137
+ -- Verify the complex AST maintains its essential structure
138
+ case evaluated of
139
+ AST. JSAstProgram stmts _ -> do
140
+ -- Should contain class, const, and function declarations
141
+ length stmts `shouldSatisfy` (> 5 )
142
+ _ -> expectationFailure " NFData failed to preserve complex program structure"
143
+ Left _ -> expectationFailure " Parse failed"
144
+
145
+ it " prevents space leaks in large ASTs" $ do
146
+ case parseUsing parseProgram largeJavaScript " test" of
147
+ Right ast -> do
148
+ -- Test that NFData prevents space leaks in large, nested ASTs
149
+ let ! evaluated = rnf ast `seq` ast
150
+ -- Verify large nested object structure is preserved
151
+ case evaluated of
152
+ AST. JSAstProgram [AST. JSVariable {}] _ -> pure ()
153
+ AST. JSAstProgram [AST. JSLet {}] _ -> pure ()
154
+ AST. JSAstProgram [AST. JSConstant {}] _ -> pure ()
155
+ _ -> expectationFailure " NFData failed to preserve large AST structure"
156
+ Left _ -> expectationFailure " Parse failed"
157
+
158
+ -- Test data for complex JavaScript
159
+ complexJavaScript :: String
160
+ complexJavaScript = unlines
161
+ [ " class Calculator {"
162
+ , " constructor(name) {"
163
+ , " this.name = name;"
164
+ , " }"
165
+ , " "
166
+ , " add(a, b) {"
167
+ , " return a + b;"
168
+ , " }"
169
+ , " "
170
+ , " multiply(a, b) {"
171
+ , " return a * b;"
172
+ , " }"
173
+ , " }"
174
+ , " "
175
+ , " const calc = new Calculator('MyCalc');"
176
+ , " const result = calc.add(calc.multiply(2, 3), 4);"
177
+ , " "
178
+ , " function processArray(arr) {"
179
+ , " return arr"
180
+ , " .filter(x => x > 0)"
181
+ , " .map(x => x * 2)"
182
+ , " .reduce((a, b) => a + b, 0);"
183
+ , " }"
184
+ , " "
185
+ , " const numbers = [1, -2, 3, -4, 5];"
186
+ , " const processed = processArray(numbers);"
187
+ ]
188
+
189
+ -- Test data for large JavaScript (nested structures)
190
+ largeJavaScript :: String
191
+ largeJavaScript = unlines
192
+ [ " const config = {"
193
+ , " database: {"
194
+ , " host: 'localhost',"
195
+ , " port: 5432,"
196
+ , " credentials: {"
197
+ , " username: 'admin',"
198
+ , " password: 'secret'"
199
+ , " },"
200
+ , " options: {"
201
+ , " ssl: true,"
202
+ , " timeout: 30000,"
203
+ , " retries: 3"
204
+ , " }"
205
+ , " },"
206
+ , " api: {"
207
+ , " endpoints: {"
208
+ , " users: '/api/users',"
209
+ , " posts: '/api/posts',"
210
+ , " comments: '/api/comments'"
211
+ , " },"
212
+ , " middleware: ["
213
+ , " 'cors',"
214
+ , " 'auth',"
215
+ , " 'validation'"
216
+ , " ]"
217
+ , " },"
218
+ , " features: {"
219
+ , " experimental: {"
220
+ , " newParser: true,"
221
+ , " betaUI: false"
222
+ , " }"
223
+ , " }"
224
+ , " };"
225
+ ]
0 commit comments