1{-# LANGUAGE DeriveDataTypeable, FlexibleInstances #-}
2
3module Language.JavaScript.Parser.AST
4    ( JSExpression (..)
5    , JSAnnot (..)
6    , JSBinOp (..)
7    , JSUnaryOp (..)
8    , JSSemi (..)
9    , JSAssignOp (..)
10    , JSTryCatch (..)
11    , JSTryFinally (..)
12    , JSStatement (..)
13    , JSBlock (..)
14    , JSSwitchParts (..)
15    , JSAST (..)
16    , JSObjectProperty (..)
17    , JSPropertyName (..)
18    , JSObjectPropertyList
19    , JSAccessor (..)
20    , JSMethodDefinition (..)
21    , JSIdent (..)
22    , JSVarInitializer (..)
23    , JSArrayElement (..)
24    , JSCommaList (..)
25    , JSCommaTrailingList (..)
26    , JSArrowParameterList (..)
27    , JSTemplatePart (..)
28    , JSClassHeritage (..)
29    , JSClassElement (..)
30
31    -- Modules
32    , JSModuleItem (..)
33    , JSImportDeclaration (..)
34    , JSImportClause (..)
35    , JSFromClause (..)
36    , JSImportNameSpace (..)
37    , JSImportsNamed (..)
38    , JSImportSpecifier (..)
39    , JSExportDeclaration (..)
40    , JSExportClause (..)
41    , JSExportSpecifier (..)
42
43    , binOpEq
44    , showStripped
45    ) where
46
47import Data.Data
48import Data.List
49import Language.JavaScript.Parser.SrcLocation (TokenPosn (..))
50import Language.JavaScript.Parser.Token
51
52-- ---------------------------------------------------------------------
53
54data JSAnnot
55    = JSAnnot !TokenPosn ![CommentAnnotation] -- ^Annotation: position and comment/whitespace information
56    | JSAnnotSpace -- ^A single space character
57    | JSNoAnnot -- ^No annotation
58    deriving (Data, Eq, Show, Typeable)
59
60
61data JSAST
62    = JSAstProgram ![JSStatement] !JSAnnot -- ^source elements, trailing whitespace
63    | JSAstModule ![JSModuleItem] !JSAnnot
64    | JSAstStatement !JSStatement !JSAnnot
65    | JSAstExpression !JSExpression !JSAnnot
66    | JSAstLiteral !JSExpression !JSAnnot
67    deriving (Data, Eq, Show, Typeable)
68
69-- Shift AST
70-- https://github.com/shapesecurity/shift-spec/blob/83498b92c436180cc0e2115b225a68c08f43c53e/spec.idl#L229-L234
71data JSModuleItem
72    = JSModuleImportDeclaration !JSAnnot !JSImportDeclaration -- ^import,decl
73    | JSModuleExportDeclaration !JSAnnot !JSExportDeclaration -- ^export,decl
74    | JSModuleStatementListItem !JSStatement
75    deriving (Data, Eq, Show, Typeable)
76
77data JSImportDeclaration
78    = JSImportDeclaration !JSImportClause !JSFromClause !JSSemi -- ^imports, module, semi
79    | JSImportDeclarationBare !JSAnnot !String !JSSemi -- ^module, module, semi
80    deriving (Data, Eq, Show, Typeable)
81
82data JSImportClause
83    = JSImportClauseDefault !JSIdent -- ^default
84    | JSImportClauseNameSpace !JSImportNameSpace -- ^namespace
85    | JSImportClauseNamed !JSImportsNamed -- ^named imports
86    | JSImportClauseDefaultNameSpace !JSIdent !JSAnnot !JSImportNameSpace -- ^default, comma, namespace
87    | JSImportClauseDefaultNamed !JSIdent !JSAnnot !JSImportsNamed -- ^default, comma, named imports
88    deriving (Data, Eq, Show, Typeable)
89
90data JSFromClause
91    = JSFromClause !JSAnnot !JSAnnot !String -- ^ from, string literal, string literal contents
92    deriving (Data, Eq, Show, Typeable)
93
94-- | Import namespace, e.g. '* as whatever'
95data JSImportNameSpace
96    = JSImportNameSpace !JSBinOp !JSAnnot !JSIdent -- ^ *, as, ident
97    deriving (Data, Eq, Show, Typeable)
98
99-- | Named imports, e.g. '{ foo, bar, baz as quux }'
100data JSImportsNamed
101    = JSImportsNamed !JSAnnot !(JSCommaList JSImportSpecifier) !JSAnnot -- ^lb, specifiers, rb
102    deriving (Data, Eq, Show, Typeable)
103
104-- |
105-- Note that this data type is separate from ExportSpecifier because the
106-- grammar is slightly different (e.g. in handling of reserved words).
107data JSImportSpecifier
108    = JSImportSpecifier !JSIdent -- ^ident
109    | JSImportSpecifierAs !JSIdent !JSAnnot !JSIdent -- ^ident, as, ident
110    deriving (Data, Eq, Show, Typeable)
111
112data JSExportDeclaration
113    -- = JSExportAllFrom
114    = JSExportFrom JSExportClause JSFromClause !JSSemi -- ^exports, module, semi
115    | JSExportLocals JSExportClause !JSSemi -- ^exports, autosemi
116    | JSExport !JSStatement !JSSemi -- ^body, autosemi
117    -- | JSExportDefault
118    deriving (Data, Eq, Show, Typeable)
119
120data JSExportClause
121    = JSExportClause !JSAnnot !(JSCommaList JSExportSpecifier) !JSAnnot -- ^lb, specifiers, rb
122    deriving (Data, Eq, Show, Typeable)
123
124data JSExportSpecifier
125    = JSExportSpecifier !JSIdent -- ^ident
126    | JSExportSpecifierAs !JSIdent !JSAnnot !JSIdent -- ^ident1, as, ident2
127    deriving (Data, Eq, Show, Typeable)
128
129data JSStatement
130    = JSStatementBlock !JSAnnot ![JSStatement] !JSAnnot !JSSemi     -- ^lbrace, stmts, rbrace, autosemi
131    | JSBreak !JSAnnot !JSIdent !JSSemi        -- ^break,optional identifier, autosemi
132    | JSLet   !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^const, decl, autosemi
133    | JSClass !JSAnnot !JSIdent !JSClassHeritage !JSAnnot ![JSClassElement] !JSAnnot !JSSemi -- ^class, name, optional extends clause, lb, body, rb, autosemi
134    | JSConstant !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^const, decl, autosemi
135    | JSContinue !JSAnnot !JSIdent !JSSemi     -- ^continue, optional identifier,autosemi
136    | JSDoWhile !JSAnnot !JSStatement !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSSemi -- ^do,stmt,while,lb,expr,rb,autosemi
137    | JSFor !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,expr,semi,expr,semi,expr,rb.stmt
138    | JSForIn !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,expr,in,expr,rb,stmt
139    | JSForVar !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt
140    | JSForVarIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
141    | JSForLet !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt
142    | JSForLetIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
143    | JSForLetOf !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
144    | JSForConst !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt
145    | JSForConstIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
146    | JSForConstOf !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
147    | JSForOf !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,expr,in,expr,rb,stmt
148    | JSForVarOf !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
149    | JSFunction !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock !JSSemi  -- ^fn,name, lb,parameter list,rb,block,autosemi
150    | JSGenerator !JSAnnot !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock !JSSemi  -- ^fn,*,name, lb,parameter list,rb,block,autosemi
151    | JSIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement -- ^if,(,expr,),stmt
152    | JSIfElse !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSAnnot !JSStatement -- ^if,(,expr,),stmt,else,rest
153    | JSLabelled !JSIdent !JSAnnot !JSStatement -- ^identifier,colon,stmt
154    | JSEmptyStatement !JSAnnot
155    | JSExpressionStatement !JSExpression !JSSemi
156    | JSAssignStatement !JSExpression !JSAssignOp !JSExpression !JSSemi -- ^lhs, assignop, rhs, autosemi
157    | JSMethodCall !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSSemi
158    | JSReturn !JSAnnot !(Maybe JSExpression) !JSSemi -- ^optional expression,autosemi
159    | JSSwitch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSAnnot ![JSSwitchParts] !JSAnnot !JSSemi -- ^switch,lb,expr,rb,caseblock,autosemi
160    | JSThrow !JSAnnot !JSExpression !JSSemi -- ^throw val autosemi
161    | JSTry !JSAnnot !JSBlock ![JSTryCatch] !JSTryFinally -- ^try,block,catches,finally
162    | JSVariable !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^var, decl, autosemi
163    | JSWhile !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement -- ^while,lb,expr,rb,stmt
164    | JSWith !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSSemi -- ^with,lb,expr,rb,stmt list
165    deriving (Data, Eq, Show, Typeable)
166
167data JSExpression
168    -- | Terminals
169    = JSIdentifier !JSAnnot !String
170    | JSDecimal !JSAnnot !String
171    | JSLiteral !JSAnnot !String
172    | JSHexInteger !JSAnnot !String
173    | JSOctal !JSAnnot !String
174    | JSStringLiteral !JSAnnot !String
175    | JSRegEx !JSAnnot !String
176
177    -- | Non Terminals
178    | JSArrayLiteral !JSAnnot ![JSArrayElement] !JSAnnot -- ^lb, contents, rb
179    | JSAssignExpression !JSExpression !JSAssignOp !JSExpression -- ^lhs, assignop, rhs
180    | JSCallExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot  -- ^expr, bl, args, rb
181    | JSCallExpressionDot !JSExpression !JSAnnot !JSExpression  -- ^expr, dot, expr
182    | JSCallExpressionSquare !JSExpression !JSAnnot !JSExpression !JSAnnot  -- ^expr, [, expr, ]
183    | JSClassExpression !JSAnnot !JSIdent !JSClassHeritage !JSAnnot ![JSClassElement] !JSAnnot -- ^class, optional identifier, optional extends clause, lb, body, rb
184    | JSCommaExpression !JSExpression !JSAnnot !JSExpression          -- ^expression components
185    | JSExpressionBinary !JSExpression !JSBinOp !JSExpression -- ^lhs, op, rhs
186    | JSExpressionParen !JSAnnot !JSExpression !JSAnnot -- ^lb,expression,rb
187    | JSExpressionPostfix !JSExpression !JSUnaryOp -- ^expression, operator
188    | JSExpressionTernary !JSExpression !JSAnnot !JSExpression !JSAnnot !JSExpression -- ^cond, ?, trueval, :, falseval
189    | JSArrowExpression !JSArrowParameterList !JSAnnot !JSStatement -- ^parameter list,arrow,block`
190    | JSFunctionExpression !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^fn,name,lb, parameter list,rb,block`
191    | JSGeneratorExpression !JSAnnot !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^fn,*,name,lb, parameter list,rb,block`
192    | JSMemberDot !JSExpression !JSAnnot !JSExpression -- ^firstpart, dot, name
193    | JSMemberExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot -- expr, lb, args, rb
194    | JSMemberNew !JSAnnot !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot -- ^new, name, lb, args, rb
195    | JSMemberSquare !JSExpression !JSAnnot !JSExpression !JSAnnot -- ^firstpart, lb, expr, rb
196    | JSNewExpression !JSAnnot !JSExpression -- ^new, expr
197    | JSObjectLiteral !JSAnnot !JSObjectPropertyList !JSAnnot -- ^lbrace contents rbrace
198    | JSSpreadExpression !JSAnnot !JSExpression
199    | JSTemplateLiteral !(Maybe JSExpression) !JSAnnot !String ![JSTemplatePart] -- ^optional tag, lquot, head, parts
200    | JSUnaryExpression !JSUnaryOp !JSExpression
201    | JSVarInitExpression !JSExpression !JSVarInitializer -- ^identifier, initializer
202    | JSYieldExpression !JSAnnot !(Maybe JSExpression) -- ^yield, optional expr
203    | JSYieldFromExpression !JSAnnot !JSAnnot !JSExpression -- ^yield, *, expr
204    deriving (Data, Eq, Show, Typeable)
205
206data JSArrowParameterList
207    = JSUnparenthesizedArrowParameter !JSIdent
208    | JSParenthesizedArrowParameterList !JSAnnot !(JSCommaList JSExpression) !JSAnnot
209    deriving (Data, Eq, Show, Typeable)
210
211data JSBinOp
212    = JSBinOpAnd !JSAnnot
213    | JSBinOpBitAnd !JSAnnot
214    | JSBinOpBitOr !JSAnnot
215    | JSBinOpBitXor !JSAnnot
216    | JSBinOpDivide !JSAnnot
217    | JSBinOpEq !JSAnnot
218    | JSBinOpGe !JSAnnot
219    | JSBinOpGt !JSAnnot
220    | JSBinOpIn !JSAnnot
221    | JSBinOpInstanceOf !JSAnnot
222    | JSBinOpLe !JSAnnot
223    | JSBinOpLsh !JSAnnot
224    | JSBinOpLt !JSAnnot
225    | JSBinOpMinus !JSAnnot
226    | JSBinOpMod !JSAnnot
227    | JSBinOpNeq !JSAnnot
228    | JSBinOpOf !JSAnnot
229    | JSBinOpOr !JSAnnot
230    | JSBinOpPlus !JSAnnot
231    | JSBinOpRsh !JSAnnot
232    | JSBinOpStrictEq !JSAnnot
233    | JSBinOpStrictNeq !JSAnnot
234    | JSBinOpTimes !JSAnnot
235    | JSBinOpUrsh !JSAnnot
236    deriving (Data, Eq, Show, Typeable)
237
238data JSUnaryOp
239    = JSUnaryOpDecr !JSAnnot
240    | JSUnaryOpDelete !JSAnnot
241    | JSUnaryOpIncr !JSAnnot
242    | JSUnaryOpMinus !JSAnnot
243    | JSUnaryOpNot !JSAnnot
244    | JSUnaryOpPlus !JSAnnot
245    | JSUnaryOpTilde !JSAnnot
246    | JSUnaryOpTypeof !JSAnnot
247    | JSUnaryOpVoid !JSAnnot
248    deriving (Data, Eq, Show, Typeable)
249
250data JSSemi
251    = JSSemi !JSAnnot
252    | JSSemiAuto
253    deriving (Data, Eq, Show, Typeable)
254
255data JSAssignOp
256    = JSAssign !JSAnnot
257    | JSTimesAssign !JSAnnot
258    | JSDivideAssign !JSAnnot
259    | JSModAssign !JSAnnot
260    | JSPlusAssign !JSAnnot
261    | JSMinusAssign !JSAnnot
262    | JSLshAssign !JSAnnot
263    | JSRshAssign !JSAnnot
264    | JSUrshAssign !JSAnnot
265    | JSBwAndAssign !JSAnnot
266    | JSBwXorAssign !JSAnnot
267    | JSBwOrAssign !JSAnnot
268    deriving (Data, Eq, Show, Typeable)
269
270data JSTryCatch
271    = JSCatch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSBlock -- ^catch,lb,ident,rb,block
272    | JSCatchIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSExpression !JSAnnot !JSBlock -- ^catch,lb,ident,if,expr,rb,block
273    deriving (Data, Eq, Show, Typeable)
274
275data JSTryFinally
276    = JSFinally !JSAnnot !JSBlock -- ^finally,block
277    | JSNoFinally
278    deriving (Data, Eq, Show, Typeable)
279
280data JSBlock
281    = JSBlock !JSAnnot ![JSStatement] !JSAnnot -- ^lbrace, stmts, rbrace
282    deriving (Data, Eq, Show, Typeable)
283
284data JSSwitchParts
285    = JSCase !JSAnnot !JSExpression !JSAnnot ![JSStatement]    -- ^expr,colon,stmtlist
286    | JSDefault !JSAnnot !JSAnnot ![JSStatement] -- ^colon,stmtlist
287    deriving (Data, Eq, Show, Typeable)
288
289data JSVarInitializer
290    = JSVarInit !JSAnnot !JSExpression -- ^ assignop, initializer
291    | JSVarInitNone
292    deriving (Data, Eq, Show, Typeable)
293
294data JSObjectProperty
295    = JSPropertyNameandValue !JSPropertyName !JSAnnot ![JSExpression] -- ^name, colon, value
296    | JSPropertyIdentRef !JSAnnot !String
297    | JSObjectMethod !JSMethodDefinition
298    deriving (Data, Eq, Show, Typeable)
299
300data JSMethodDefinition
301    = JSMethodDefinition !JSPropertyName !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- name, lb, params, rb, block
302    | JSGeneratorMethodDefinition !JSAnnot !JSPropertyName !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^*, name, lb, params, rb, block
303    | JSPropertyAccessor !JSAccessor !JSPropertyName !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^get/set, name, lb, params, rb, block
304    deriving (Data, Eq, Show, Typeable)
305
306data JSPropertyName
307    = JSPropertyIdent !JSAnnot !String
308    | JSPropertyString !JSAnnot !String
309    | JSPropertyNumber !JSAnnot !String
310    | JSPropertyComputed !JSAnnot !JSExpression !JSAnnot -- ^lb, expr, rb
311    deriving (Data, Eq, Show, Typeable)
312
313type JSObjectPropertyList = JSCommaTrailingList JSObjectProperty
314
315-- | Accessors for JSObjectProperty is either 'get' or 'set'.
316data JSAccessor
317    = JSAccessorGet !JSAnnot
318    | JSAccessorSet !JSAnnot
319    deriving (Data, Eq, Show, Typeable)
320
321data JSIdent
322    = JSIdentName !JSAnnot !String
323    | JSIdentNone
324    deriving (Data, Eq, Show, Typeable)
325
326data JSArrayElement
327    = JSArrayElement !JSExpression
328    | JSArrayComma !JSAnnot
329    deriving (Data, Eq, Show, Typeable)
330
331data JSCommaList a
332    = JSLCons !(JSCommaList a) !JSAnnot !a -- ^head, comma, a
333    | JSLOne !a -- ^ single element (no comma)
334    | JSLNil
335    deriving (Data, Eq, Show, Typeable)
336
337data JSCommaTrailingList a
338    = JSCTLComma !(JSCommaList a) !JSAnnot -- ^list, trailing comma
339    | JSCTLNone !(JSCommaList a) -- ^list
340    deriving (Data, Eq, Show, Typeable)
341
342data JSTemplatePart
343    = JSTemplatePart !JSExpression !JSAnnot !String -- ^expr, rb, suffix
344    deriving (Data, Eq, Show, Typeable)
345
346data JSClassHeritage
347    = JSExtends !JSAnnot !JSExpression
348    | JSExtendsNone
349    deriving (Data, Eq, Show, Typeable)
350
351data JSClassElement
352    = JSClassInstanceMethod !JSMethodDefinition
353    | JSClassStaticMethod !JSAnnot !JSMethodDefinition
354    | JSClassSemi !JSAnnot
355    deriving (Data, Eq, Show, Typeable)
356
357-- -----------------------------------------------------------------------------
358-- | Show the AST elements stripped of their JSAnnot data.
359
360-- Strip out the location info
361showStripped :: JSAST -> String
362showStripped (JSAstProgram xs _) = "JSAstProgram " ++ ss xs
363showStripped (JSAstModule xs _) = "JSAstModule " ++ ss xs
364showStripped (JSAstStatement s _) = "JSAstStatement (" ++ ss s ++ ")"
365showStripped (JSAstExpression e _) = "JSAstExpression (" ++ ss e ++ ")"
366showStripped (JSAstLiteral s _)  = "JSAstLiteral (" ++ ss s ++ ")"
367
368
369class ShowStripped a where
370    ss :: a -> String
371
372instance ShowStripped JSStatement where
373    ss (JSStatementBlock _ xs _ _) = "JSStatementBlock " ++ ss xs
374    ss (JSBreak _ JSIdentNone s) = "JSBreak" ++ commaIf (ss s)
375    ss (JSBreak _ (JSIdentName _ n) s) = "JSBreak " ++ singleQuote n ++ commaIf (ss s)
376    ss (JSClass _ n h _lb xs _rb _) = "JSClass " ++ ssid n ++ " (" ++ ss h ++ ") " ++ ss xs
377    ss (JSContinue _ JSIdentNone s) = "JSContinue" ++ commaIf (ss s)
378    ss (JSContinue _ (JSIdentName _ n) s) = "JSContinue " ++ singleQuote n ++ commaIf (ss s)
379    ss (JSConstant _ xs _as) = "JSConstant " ++ ss xs
380    ss (JSDoWhile _d x1 _w _lb x2 _rb x3) = "JSDoWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
381    ss (JSFor _ _lb x1s _s1 x2s _s2 x3s _rb x4) = "JSFor " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
382    ss (JSForIn _ _lb x1s _i x2 _rb x3) = "JSForIn " ++ ss x1s ++ " (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
383    ss (JSForVar _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForVar " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
384    ss (JSForVarIn _ _lb _v x1 _i x2 _rb x3) = "JSForVarIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
385    ss (JSForLet _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForLet " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
386    ss (JSForLetIn _ _lb _v x1 _i x2 _rb x3) = "JSForLetIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
387    ss (JSForLetOf _ _lb _v x1 _i x2 _rb x3) = "JSForLetOf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
388    ss (JSForConst _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForConst " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
389    ss (JSForConstIn _ _lb _v x1 _i x2 _rb x3) = "JSForConstIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
390    ss (JSForConstOf _ _lb _v x1 _i x2 _rb x3) = "JSForConstOf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
391    ss (JSForOf _ _lb x1s _i x2 _rb x3) = "JSForOf " ++ ss x1s ++ " (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
392    ss (JSForVarOf _ _lb _v x1 _i x2 _rb x3) = "JSForVarOf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
393    ss (JSFunction _ n _lb pl _rb x3 _) = "JSFunction " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
394    ss (JSGenerator _ _ n _lb pl _rb x3 _) = "JSGenerator " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
395    ss (JSIf _ _lb x1 _rb x2) = "JSIf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
396    ss (JSIfElse _ _lb x1 _rb x2 _e x3) = "JSIfElse (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
397    ss (JSLabelled x1 _c x2) = "JSLabelled (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
398    ss (JSLet _ xs _as) = "JSLet " ++ ss xs
399    ss (JSEmptyStatement _) = "JSEmptyStatement"
400    ss (JSExpressionStatement l s) = ss l ++ (let x = ss s in if not (null x) then ',':x else "")
401    ss (JSAssignStatement lhs op rhs s) ="JSOpAssign (" ++ ss op ++ "," ++ ss lhs ++ "," ++ ss rhs ++ (let x = ss s in if not (null x) then "),"++x else ")")
402    ss (JSMethodCall e _ a _ s) = "JSMethodCall (" ++ ss e ++ ",JSArguments " ++ ss a ++ (let x = ss s in if not (null x) then "),"++x else ")")
403    ss (JSReturn _ (Just me) s) = "JSReturn " ++ ss me ++ " " ++ ss s
404    ss (JSReturn _ Nothing s) = "JSReturn " ++ ss s
405    ss (JSSwitch _ _lp x _rp _lb x2 _rb _) = "JSSwitch (" ++ ss x ++ ") " ++ ss x2
406    ss (JSThrow _ x _) = "JSThrow (" ++ ss x ++ ")"
407    ss (JSTry _ xt1 xtc xtf) = "JSTry (" ++ ss xt1 ++ "," ++ ss xtc ++ "," ++ ss xtf ++ ")"
408    ss (JSVariable _ xs _as) = "JSVariable " ++ ss xs
409    ss (JSWhile _ _lb x1 _rb x2) = "JSWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
410    ss (JSWith _ _lb x1 _rb x _) = "JSWith (" ++ ss x1 ++ ") (" ++ ss x ++ ")"
411
412instance ShowStripped JSExpression where
413    ss (JSArrayLiteral _lb xs _rb) = "JSArrayLiteral " ++ ss xs
414    ss (JSAssignExpression lhs op rhs) = "JSOpAssign (" ++ ss op ++ "," ++ ss lhs ++ "," ++ ss rhs ++ ")"
415    ss (JSCallExpression ex _ xs _) = "JSCallExpression ("++ ss ex ++ ",JSArguments " ++ ss xs ++ ")"
416    ss (JSCallExpressionDot ex _os xs) = "JSCallExpressionDot (" ++ ss ex ++ "," ++ ss xs ++ ")"
417    ss (JSCallExpressionSquare ex _os xs _cs) = "JSCallExpressionSquare (" ++ ss ex ++ "," ++ ss xs ++ ")"
418    ss (JSClassExpression _ n h _lb xs _rb) = "JSClassExpression " ++ ssid n ++ " (" ++ ss h ++ ") " ++ ss xs
419    ss (JSDecimal _ s) = "JSDecimal " ++ singleQuote s
420    ss (JSCommaExpression l _ r) = "JSExpression [" ++ ss l ++ "," ++ ss r ++ "]"
421    ss (JSExpressionBinary x2 op x3) = "JSExpressionBinary (" ++ ss op ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
422    ss (JSExpressionParen _lp x _rp) = "JSExpressionParen (" ++ ss x ++ ")"
423    ss (JSExpressionPostfix xs op) = "JSExpressionPostfix (" ++ ss op ++ "," ++ ss xs ++ ")"
424    ss (JSExpressionTernary x1 _q x2 _c x3) = "JSExpressionTernary (" ++ ss x1 ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
425    ss (JSArrowExpression ps _ e) = "JSArrowExpression (" ++ ss ps ++ ") => " ++ ss e
426    ss (JSFunctionExpression _ n _lb pl _rb x3) = "JSFunctionExpression " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
427    ss (JSGeneratorExpression _ _ n _lb pl _rb x3) = "JSGeneratorExpression " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
428    ss (JSHexInteger _ s) = "JSHexInteger " ++ singleQuote s
429    ss (JSOctal _ s) = "JSOctal " ++ singleQuote s
430    ss (JSIdentifier _ s) = "JSIdentifier " ++ singleQuote s
431    ss (JSLiteral _ []) = "JSLiteral ''"
432    ss (JSLiteral _ s) = "JSLiteral " ++ singleQuote s
433    ss (JSMemberDot x1s _d x2 ) = "JSMemberDot (" ++ ss x1s ++ "," ++ ss x2 ++ ")"
434    ss (JSMemberExpression e _ a _) = "JSMemberExpression (" ++ ss e ++ ",JSArguments " ++ ss a ++ ")"
435    ss (JSMemberNew _a n _ s _) = "JSMemberNew (" ++ ss n ++ ",JSArguments " ++ ss s ++ ")"
436    ss (JSMemberSquare x1s _lb x2 _rb) = "JSMemberSquare (" ++ ss x1s ++ "," ++ ss x2 ++ ")"
437    ss (JSNewExpression _n e) = "JSNewExpression " ++ ss e
438    ss (JSObjectLiteral _lb xs _rb) = "JSObjectLiteral " ++ ss xs
439    ss (JSRegEx _ s) = "JSRegEx " ++ singleQuote s
440    ss (JSStringLiteral _ s) = "JSStringLiteral " ++ s
441    ss (JSUnaryExpression op x) = "JSUnaryExpression (" ++ ss op ++ "," ++ ss x ++ ")"
442    ss (JSVarInitExpression x1 x2) = "JSVarInitExpression (" ++ ss x1 ++ ") " ++ ss x2
443    ss (JSYieldExpression _ Nothing) = "JSYieldExpression ()"
444    ss (JSYieldExpression _ (Just x)) = "JSYieldExpression (" ++ ss x ++ ")"
445    ss (JSYieldFromExpression _ _ x) = "JSYieldFromExpression (" ++ ss x ++ ")"
446    ss (JSSpreadExpression _ x1) = "JSSpreadExpression (" ++ ss x1 ++ ")"
447    ss (JSTemplateLiteral Nothing _ s ps) = "JSTemplateLiteral (()," ++ singleQuote s ++ "," ++ ss ps ++ ")"
448    ss (JSTemplateLiteral (Just t) _ s ps) = "JSTemplateLiteral ((" ++ ss t ++ ")," ++ singleQuote s ++ "," ++ ss ps ++ ")"
449
450instance ShowStripped JSArrowParameterList where
451    ss (JSUnparenthesizedArrowParameter x) = ss x
452    ss (JSParenthesizedArrowParameterList _ xs _) = ss xs
453
454instance ShowStripped JSModuleItem where
455    ss (JSModuleExportDeclaration _ x1) = "JSModuleExportDeclaration (" ++ ss x1 ++ ")"
456    ss (JSModuleImportDeclaration _ x1) = "JSModuleImportDeclaration (" ++ ss x1 ++ ")"
457    ss (JSModuleStatementListItem x1) = "JSModuleStatementListItem (" ++ ss x1 ++ ")"
458
459instance ShowStripped JSImportDeclaration where
460    ss (JSImportDeclaration imp from _) = "JSImportDeclaration (" ++ ss imp ++ "," ++ ss from ++ ")"
461    ss (JSImportDeclarationBare _ m _) = "JSImportDeclarationBare (" ++ singleQuote m ++ ")"
462
463instance ShowStripped JSImportClause where
464    ss (JSImportClauseDefault x) = "JSImportClauseDefault (" ++ ss x ++ ")"
465    ss (JSImportClauseNameSpace x) = "JSImportClauseNameSpace (" ++ ss x ++ ")"
466    ss (JSImportClauseNamed x) = "JSImportClauseNameSpace (" ++ ss x ++ ")"
467    ss (JSImportClauseDefaultNameSpace x1 _ x2) = "JSImportClauseDefaultNameSpace (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
468    ss (JSImportClauseDefaultNamed x1 _ x2) = "JSImportClauseDefaultNamed (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
469
470instance ShowStripped JSFromClause where
471    ss (JSFromClause _ _ m) = "JSFromClause " ++ singleQuote m
472
473instance ShowStripped JSImportNameSpace where
474    ss (JSImportNameSpace _ _ x) = "JSImportNameSpace (" ++ ss x ++ ")"
475
476instance ShowStripped JSImportsNamed where
477    ss (JSImportsNamed _ xs _) = "JSImportsNamed (" ++ ss xs ++ ")"
478
479instance ShowStripped JSImportSpecifier where
480    ss (JSImportSpecifier x1) = "JSImportSpecifier (" ++ ss x1 ++ ")"
481    ss (JSImportSpecifierAs x1 _ x2) = "JSImportSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
482
483instance ShowStripped JSExportDeclaration where
484    ss (JSExportFrom xs from _) = "JSExportFrom (" ++ ss xs ++ "," ++ ss from ++ ")"
485    ss (JSExportLocals xs _) = "JSExportLocals (" ++ ss xs ++ ")"
486    ss (JSExport x1 _) = "JSExport (" ++ ss x1 ++ ")"
487
488instance ShowStripped JSExportClause where
489    ss (JSExportClause _ xs _) = "JSExportClause (" ++ ss xs ++ ")"
490
491instance ShowStripped JSExportSpecifier where
492    ss (JSExportSpecifier x1) = "JSExportSpecifier (" ++ ss x1 ++ ")"
493    ss (JSExportSpecifierAs x1 _ x2) = "JSExportSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
494
495instance ShowStripped JSTryCatch where
496    ss (JSCatch _ _lb x1 _rb x3) = "JSCatch (" ++ ss x1 ++ "," ++ ss x3 ++ ")"
497    ss (JSCatchIf _ _lb x1 _ ex _rb x3) = "JSCatch (" ++ ss x1 ++ ") if " ++ ss ex ++ " (" ++ ss x3 ++ ")"
498
499instance ShowStripped JSTryFinally where
500    ss (JSFinally _ x) = "JSFinally (" ++ ss x ++ ")"
501    ss JSNoFinally = "JSFinally ()"
502
503instance ShowStripped JSIdent where
504    ss (JSIdentName _ s) = "JSIdentifier " ++ singleQuote s
505    ss JSIdentNone = "JSIdentNone"
506
507instance ShowStripped JSObjectProperty where
508    ss (JSPropertyNameandValue x1 _colon x2s) = "JSPropertyNameandValue (" ++ ss x1 ++ ") " ++ ss x2s
509    ss (JSPropertyIdentRef _ s) = "JSPropertyIdentRef " ++ singleQuote s
510    ss (JSObjectMethod m) = ss m
511
512instance ShowStripped JSMethodDefinition where
513    ss (JSMethodDefinition x1 _lb1 x2s _rb1 x3) = "JSMethodDefinition (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
514    ss (JSPropertyAccessor s x1 _lb1 x2s _rb1 x3) = "JSPropertyAccessor " ++ ss s ++ " (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
515    ss (JSGeneratorMethodDefinition _ x1 _lb1 x2s _rb1 x3) = "JSGeneratorMethodDefinition (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
516
517instance ShowStripped JSPropertyName where
518    ss (JSPropertyIdent _ s) = "JSIdentifier " ++ singleQuote s
519    ss (JSPropertyString _ s) = "JSIdentifier " ++ singleQuote s
520    ss (JSPropertyNumber _ s) = "JSIdentifier " ++ singleQuote s
521    ss (JSPropertyComputed _ x _) = "JSPropertyComputed (" ++ ss x ++ ")"
522
523instance ShowStripped JSAccessor where
524    ss (JSAccessorGet _) = "JSAccessorGet"
525    ss (JSAccessorSet _) = "JSAccessorSet"
526
527instance ShowStripped JSBlock where
528    ss (JSBlock _ xs _) = "JSBlock " ++ ss xs
529
530instance ShowStripped JSSwitchParts where
531    ss (JSCase _ x1 _c x2s) = "JSCase (" ++ ss x1 ++ ") (" ++ ss x2s ++ ")"
532    ss (JSDefault _ _c xs) = "JSDefault (" ++ ss xs ++ ")"
533
534instance ShowStripped JSBinOp where
535    ss (JSBinOpAnd _) = "'&&'"
536    ss (JSBinOpBitAnd _) = "'&'"
537    ss (JSBinOpBitOr _) = "'|'"
538    ss (JSBinOpBitXor _) = "'^'"
539    ss (JSBinOpDivide _) = "'/'"
540    ss (JSBinOpEq _) = "'=='"
541    ss (JSBinOpGe _) = "'>='"
542    ss (JSBinOpGt _) = "'>'"
543    ss (JSBinOpIn _) = "'in'"
544    ss (JSBinOpInstanceOf _) = "'instanceof'"
545    ss (JSBinOpLe _) = "'<='"
546    ss (JSBinOpLsh _) = "'<<'"
547    ss (JSBinOpLt _) = "'<'"
548    ss (JSBinOpMinus _) = "'-'"
549    ss (JSBinOpMod _) = "'%'"
550    ss (JSBinOpNeq _) = "'!='"
551    ss (JSBinOpOf _) = "'of'"
552    ss (JSBinOpOr _) = "'||'"
553    ss (JSBinOpPlus _) = "'+'"
554    ss (JSBinOpRsh _) = "'>>'"
555    ss (JSBinOpStrictEq _) = "'==='"
556    ss (JSBinOpStrictNeq _) = "'!=='"
557    ss (JSBinOpTimes _) = "'*'"
558    ss (JSBinOpUrsh _) = "'>>>'"
559
560instance ShowStripped JSUnaryOp where
561    ss (JSUnaryOpDecr _) = "'--'"
562    ss (JSUnaryOpDelete _) = "'delete'"
563    ss (JSUnaryOpIncr _) = "'++'"
564    ss (JSUnaryOpMinus _) = "'-'"
565    ss (JSUnaryOpNot _) = "'!'"
566    ss (JSUnaryOpPlus _) = "'+'"
567    ss (JSUnaryOpTilde _) = "'~'"
568    ss (JSUnaryOpTypeof _) = "'typeof'"
569    ss (JSUnaryOpVoid _) = "'void'"
570
571instance ShowStripped JSAssignOp where
572    ss (JSAssign _) = "'='"
573    ss (JSTimesAssign _) = "'*='"
574    ss (JSDivideAssign _) = "'/='"
575    ss (JSModAssign _) = "'%='"
576    ss (JSPlusAssign _) = "'+='"
577    ss (JSMinusAssign _) = "'-='"
578    ss (JSLshAssign _) = "'<<='"
579    ss (JSRshAssign _) = "'>>='"
580    ss (JSUrshAssign _) = "'>>>='"
581    ss (JSBwAndAssign _) = "'&='"
582    ss (JSBwXorAssign _) = "'^='"
583    ss (JSBwOrAssign _) = "'|='"
584
585instance ShowStripped JSVarInitializer where
586    ss (JSVarInit _ n) = "[" ++ ss n ++ "]"
587    ss JSVarInitNone = ""
588
589instance ShowStripped JSSemi where
590    ss (JSSemi _) = "JSSemicolon"
591    ss JSSemiAuto = ""
592
593instance ShowStripped JSArrayElement where
594    ss (JSArrayElement e) = ss e
595    ss (JSArrayComma _) = "JSComma"
596
597instance ShowStripped JSTemplatePart where
598    ss (JSTemplatePart e _ s) = "(" ++ ss e ++ "," ++ singleQuote s ++ ")"
599
600instance ShowStripped JSClassHeritage where
601    ss JSExtendsNone = ""
602    ss (JSExtends _ x) = ss x
603
604instance ShowStripped JSClassElement where
605    ss (JSClassInstanceMethod m) = ss m
606    ss (JSClassStaticMethod _ m) = "JSClassStaticMethod (" ++ ss m ++ ")"
607    ss (JSClassSemi _) = "JSClassSemi"
608
609instance ShowStripped a => ShowStripped (JSCommaList a) where
610    ss xs = "(" ++ commaJoin (map ss $ fromCommaList xs) ++ ")"
611
612instance ShowStripped a => ShowStripped (JSCommaTrailingList a) where
613    ss (JSCTLComma xs _) = "[" ++ commaJoin (map ss $ fromCommaList xs) ++ ",JSComma]"
614    ss (JSCTLNone xs)    = "[" ++ commaJoin (map ss $ fromCommaList xs) ++ "]"
615
616instance ShowStripped a => ShowStripped [a] where
617    ss xs = "[" ++ commaJoin (map ss xs) ++ "]"
618
619-- -----------------------------------------------------------------------------
620-- Helpers.
621
622commaJoin :: [String] -> String
623commaJoin s = intercalate "," $ filter (not . null) s
624
625fromCommaList :: JSCommaList a -> [a]
626fromCommaList (JSLCons l _ i) = fromCommaList l ++ [i]
627fromCommaList (JSLOne i)      = [i]
628fromCommaList JSLNil = []
629
630singleQuote :: String -> String
631singleQuote s = '\'' : (s ++ "'")
632
633ssid :: JSIdent -> String
634ssid (JSIdentName _ s) = singleQuote s
635ssid JSIdentNone = "''"
636
637commaIf :: String -> String
638commaIf "" = ""
639commaIf xs = ',' : xs
640
641
642deAnnot :: JSBinOp -> JSBinOp
643deAnnot (JSBinOpAnd _) = JSBinOpAnd JSNoAnnot
644deAnnot (JSBinOpBitAnd _) = JSBinOpBitAnd JSNoAnnot
645deAnnot (JSBinOpBitOr _) = JSBinOpBitOr JSNoAnnot
646deAnnot (JSBinOpBitXor _) = JSBinOpBitXor JSNoAnnot
647deAnnot (JSBinOpDivide _) = JSBinOpDivide JSNoAnnot
648deAnnot (JSBinOpEq _) = JSBinOpEq JSNoAnnot
649deAnnot (JSBinOpGe _) = JSBinOpGe JSNoAnnot
650deAnnot (JSBinOpGt _) = JSBinOpGt JSNoAnnot
651deAnnot (JSBinOpIn _) = JSBinOpIn JSNoAnnot
652deAnnot (JSBinOpInstanceOf _) = JSBinOpInstanceOf JSNoAnnot
653deAnnot (JSBinOpLe _) = JSBinOpLe JSNoAnnot
654deAnnot (JSBinOpLsh _) = JSBinOpLsh JSNoAnnot
655deAnnot (JSBinOpLt _) = JSBinOpLt JSNoAnnot
656deAnnot (JSBinOpMinus _) = JSBinOpMinus JSNoAnnot
657deAnnot (JSBinOpMod _) = JSBinOpMod JSNoAnnot
658deAnnot (JSBinOpNeq _) = JSBinOpNeq JSNoAnnot
659deAnnot (JSBinOpOf _) = JSBinOpOf JSNoAnnot
660deAnnot (JSBinOpOr _) = JSBinOpOr JSNoAnnot
661deAnnot (JSBinOpPlus _) = JSBinOpPlus JSNoAnnot
662deAnnot (JSBinOpRsh _) = JSBinOpRsh JSNoAnnot
663deAnnot (JSBinOpStrictEq _) = JSBinOpStrictEq JSNoAnnot
664deAnnot (JSBinOpStrictNeq _) = JSBinOpStrictNeq JSNoAnnot
665deAnnot (JSBinOpTimes _) = JSBinOpTimes JSNoAnnot
666deAnnot (JSBinOpUrsh _) = JSBinOpUrsh JSNoAnnot
667
668binOpEq :: JSBinOp -> JSBinOp -> Bool
669binOpEq a b = deAnnot a == deAnnot b
670