--- /dev/null
+-- Startup commands for the GHC interpreter
+:set -hide-package monads-tf
+:set -hide-package monads-fd
+:set -i./src
+:set -i./dist/build
--- /dev/null
+# ChangeLog for `language-javascript`
+
+## 0.7.1.0 -- 2020-03-22
++ Add support for `async` function specifiers and `await` keyword.
+
+## 0.7.0.0 -- 2019-10-10
+
++ Add support for (Ryan Hendrickson):
+ - Destructuring in var declarations
+ - `const` in for statements
+ - ES6 property shorthand syntax
+ - Template literals
+ - Computed property names
+ - Bare import declarations
+ - Exotic parameter syntaxes
+ - Generators and `yield`
+ - Method definitions
+ - classes
+ `- super` keyword
+
+## 0.6.0.13 -- 2019-06-17
+
++ Add support for (Cyril Sobierajewicz):
+ - Unparenthesized arrow functions of one parameter
+ - Export from declarations
+ - Add back support for identifiers named `as`
+
+## 0.6.0.12 -- 2019-05-03
+
++ Add support for for..of and friends (Franco Bulgarelli)
--- /dev/null
+Copyright (c)2010, Alan Zimmerman
+
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions are met:
+
+ * Redistributions of source code must retain the above copyright
+ notice, this list of conditions and the following disclaimer.
+
+ * Redistributions in binary form must reproduce the above
+ copyright notice, this list of conditions and the following
+ disclaimer in the documentation and/or other materials provided
+ with the distribution.
+
+ * Neither the name of Alan Zimmerman nor the names of other
+ contributors may be used to endorse or promote products derived
+ from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
+A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
+OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
+SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
+LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
+OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
--- /dev/null
+Parser for JavaScript
+---------------------
+
+[](http://travis-ci.org/erikd/language-javascript)
+
+Based (loosely) on language-python
+
+Two Versions
+------------
+
+There are currently two versions:
+
+* 0.5 series : Is a continuation of the 0.5.X.Y series, from the [master]
+(https://github.com/erikd/language-javascript/tree/master) branch of this
+github repository.
+
+* 0.6 and 0.7 series : This has a vastly different and improved AST which makes if far
+more difficult to build an non-sensical Javascript AST. This code is in the
+[new-ast](https://github.com/erikd/language-javascript/tree/new-ast) branch of
+this github repository.
+
+
+How to build
+------------
+
+Make sure your locale supports UTF-8. For example, on most Unix-like platforms,
+you can type:
+
+ export LC_ALL=en_US.UTF-8
+
+Library:
+
+ cabal clean && cabal configure && cabal build
+
+Tests:
+
+ cabal clean && cabal configure -fbuildtests && cabal build
+
+Running the tests
+
+ ./dist/build/runtests/runtests
+
+
+To debug the grammar
+
+ happy -iparse.txt -g -a -d src/Language/JavaScript/Parser/Grammar5.y
+
+This generates src/Language/JavaScript/Parser/Grammar5.hs, delete this
+when done with the debug version
+
+
+UTF8/Unicode version
+--------------------
+
+Alex 3.0 now supports unicode natively, and has been included as a
+dependency in the cabal file.
+
+Note: The generation of the lexical analyser has been separated out,
+ to remove the install-time dependency on Alex. If any changes
+ need to be made to the lexer, the Lexer.x source lies in
+ src-dev, and the runalex.sh script will invoke Alex with the
+ appropriate directories.
--- /dev/null
+import Distribution.Simple
+main = defaultMain
--- /dev/null
+Name: language-javascript
+Version: 0.7.1.0
+Synopsis: Parser for JavaScript
+Description: Parses Javascript into an Abstract Syntax Tree (AST). Initially intended as frontend to hjsmin.
+ .
+ Note: Version 0.5.0 breaks compatibility with prior versions, the AST has been reworked to allow
+ round trip processing of JavaScript.
+License: BSD3
+License-file: LICENSE
+Author: Alan Zimmerman
+Maintainer: Erik de Castro Lopo <erikd@mega-nerd.com>
+Copyright: (c) 2010-2015 Alan Zimmerman
+ (c) 2015-2019 Erik de Castro Lopo
+ (c) 2018 Daniel Gasienica
+Category: Language
+Build-type: Simple
+homepage: https://github.com/erikd/language-javascript
+bug-reports: https://github.com/erikd/language-javascript/issues
+Extra-source-files: README.md
+ ChangeLog.md
+ .ghci
+ test/Unicode.js
+ test/k.js
+ test/unicode.txt
+ src/Language/JavaScript/Parser/Lexer.x
+
+-- Version requirement upped for test support in later Cabal
+Cabal-version: >= 1.9.2
+
+
+Library
+ Build-depends: base >= 4 && < 5
+ , array >= 0.3
+ , mtl >= 1.1
+ , containers >= 0.2
+ , blaze-builder >= 0.2
+ , bytestring >= 0.9.1
+ , text >= 1.2
+ , utf8-string >= 0.3.7 && < 2
+ if !impl(ghc>=8.0)
+ build-depends: semigroups >= 0.16.1
+
+ if impl(ghc >= 7.10)
+ build-tools: happy >= 1.19, alex >= 3.1.4
+ else
+ if impl(ghc >= 7.8)
+ build-tools: happy >= 1.19, alex >= 3.1
+ else
+ build-tools: happy >= 1.18.5, alex >= 3.0.5
+ hs-source-dirs: src
+ Exposed-modules: Language.JavaScript.Parser
+ Language.JavaScript.Parser.AST
+ Language.JavaScript.Parser.Grammar7
+ Language.JavaScript.Parser.Lexer
+ Language.JavaScript.Parser.Parser
+ Language.JavaScript.Parser.SrcLocation
+ Language.JavaScript.Pretty.Printer
+ Language.JavaScript.Process.Minify
+ Other-modules: Language.JavaScript.Parser.LexerUtils
+ Language.JavaScript.Parser.ParseError
+ Language.JavaScript.Parser.ParserMonad
+ Language.JavaScript.Parser.Token
+ ghc-options: -Wall -fwarn-tabs
+
+Test-Suite testsuite
+ Type: exitcode-stdio-1.0
+ Main-is: testsuite.hs
+ hs-source-dirs: test
+ ghc-options: -Wall -fwarn-tabs
+ build-depends: base, Cabal >= 1.9.2
+ , QuickCheck >= 2
+ , hspec
+ , array >= 0.3
+ , utf8-light >= 0.4
+ , containers >= 0.2
+ , mtl >= 1.1
+ , utf8-string >= 0.3.7 && < 2
+ , bytestring >= 0.9.1
+ , blaze-builder >= 0.2
+ , language-javascript
+
+ Other-modules: Test.Language.Javascript.ExpressionParser
+ Test.Language.Javascript.Lexer
+ Test.Language.Javascript.LiteralParser
+ Test.Language.Javascript.Minify
+ Test.Language.Javascript.ModuleParser
+ Test.Language.Javascript.ProgramParser
+ Test.Language.Javascript.RoundTrip
+ Test.Language.Javascript.StatementParser
+
+source-repository head
+ type: git
+ location: https://github.com/erikd/language-javascript.git
--- /dev/null
+module Language.JavaScript.Parser
+ (
+ PA.parse
+ , PA.parseModule
+ , PA.readJs
+ , PA.readJsModule
+ , PA.parseFile
+ , PA.parseFileUtf8
+ , PA.showStripped
+ , PA.showStrippedMaybe
+ -- * AST elements
+ , JSExpression (..)
+ , JSAnnot (..)
+ , JSBinOp (..)
+ , JSBlock (..)
+ , JSUnaryOp (..)
+ , JSSemi (..)
+ , JSAssignOp (..)
+ , JSTryCatch (..)
+ , JSTryFinally (..)
+ , JSStatement (..)
+ , JSSwitchParts (..)
+ , JSAST(..)
+
+
+ , CommentAnnotation(..)
+ -- , ParseError(..)
+ -- Source locations
+ , TokenPosn(..)
+ , tokenPosnEmpty
+ -- * Pretty Printing
+ , renderJS
+ , renderToString
+ , renderToText
+ ) where
+
+
+import Language.JavaScript.Parser.AST
+import Language.JavaScript.Parser.Token
+import qualified Language.JavaScript.Parser.Parser as PA
+import Language.JavaScript.Parser.SrcLocation
+import Language.JavaScript.Pretty.Printer
+
+-- EOF
--- /dev/null
+{-# LANGUAGE DeriveDataTypeable, FlexibleInstances #-}
+
+module Language.JavaScript.Parser.AST
+ ( JSExpression (..)
+ , JSAnnot (..)
+ , JSBinOp (..)
+ , JSUnaryOp (..)
+ , JSSemi (..)
+ , JSAssignOp (..)
+ , JSTryCatch (..)
+ , JSTryFinally (..)
+ , JSStatement (..)
+ , JSBlock (..)
+ , JSSwitchParts (..)
+ , JSAST (..)
+ , JSObjectProperty (..)
+ , JSPropertyName (..)
+ , JSObjectPropertyList
+ , JSAccessor (..)
+ , JSMethodDefinition (..)
+ , JSIdent (..)
+ , JSVarInitializer (..)
+ , JSArrayElement (..)
+ , JSCommaList (..)
+ , JSCommaTrailingList (..)
+ , JSArrowParameterList (..)
+ , JSTemplatePart (..)
+ , JSClassHeritage (..)
+ , JSClassElement (..)
+
+ -- Modules
+ , JSModuleItem (..)
+ , JSImportDeclaration (..)
+ , JSImportClause (..)
+ , JSFromClause (..)
+ , JSImportNameSpace (..)
+ , JSImportsNamed (..)
+ , JSImportSpecifier (..)
+ , JSExportDeclaration (..)
+ , JSExportClause (..)
+ , JSExportSpecifier (..)
+
+ , binOpEq
+ , showStripped
+ ) where
+
+import Data.Data
+import Data.List
+import Language.JavaScript.Parser.SrcLocation (TokenPosn (..))
+import Language.JavaScript.Parser.Token
+
+-- ---------------------------------------------------------------------
+
+data JSAnnot
+ = JSAnnot !TokenPosn ![CommentAnnotation] -- ^Annotation: position and comment/whitespace information
+ | JSAnnotSpace -- ^A single space character
+ | JSNoAnnot -- ^No annotation
+ deriving (Data, Eq, Show, Typeable)
+
+
+data JSAST
+ = JSAstProgram ![JSStatement] !JSAnnot -- ^source elements, trailing whitespace
+ | JSAstModule ![JSModuleItem] !JSAnnot
+ | JSAstStatement !JSStatement !JSAnnot
+ | JSAstExpression !JSExpression !JSAnnot
+ | JSAstLiteral !JSExpression !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+-- Shift AST
+-- https://github.com/shapesecurity/shift-spec/blob/83498b92c436180cc0e2115b225a68c08f43c53e/spec.idl#L229-L234
+data JSModuleItem
+ = JSModuleImportDeclaration !JSAnnot !JSImportDeclaration -- ^import,decl
+ | JSModuleExportDeclaration !JSAnnot !JSExportDeclaration -- ^export,decl
+ | JSModuleStatementListItem !JSStatement
+ deriving (Data, Eq, Show, Typeable)
+
+data JSImportDeclaration
+ = JSImportDeclaration !JSImportClause !JSFromClause !JSSemi -- ^imports, module, semi
+ | JSImportDeclarationBare !JSAnnot !String !JSSemi -- ^module, module, semi
+ deriving (Data, Eq, Show, Typeable)
+
+data JSImportClause
+ = JSImportClauseDefault !JSIdent -- ^default
+ | JSImportClauseNameSpace !JSImportNameSpace -- ^namespace
+ | JSImportClauseNamed !JSImportsNamed -- ^named imports
+ | JSImportClauseDefaultNameSpace !JSIdent !JSAnnot !JSImportNameSpace -- ^default, comma, namespace
+ | JSImportClauseDefaultNamed !JSIdent !JSAnnot !JSImportsNamed -- ^default, comma, named imports
+ deriving (Data, Eq, Show, Typeable)
+
+data JSFromClause
+ = JSFromClause !JSAnnot !JSAnnot !String -- ^ from, string literal, string literal contents
+ deriving (Data, Eq, Show, Typeable)
+
+-- | Import namespace, e.g. '* as whatever'
+data JSImportNameSpace
+ = JSImportNameSpace !JSBinOp !JSAnnot !JSIdent -- ^ *, as, ident
+ deriving (Data, Eq, Show, Typeable)
+
+-- | Named imports, e.g. '{ foo, bar, baz as quux }'
+data JSImportsNamed
+ = JSImportsNamed !JSAnnot !(JSCommaList JSImportSpecifier) !JSAnnot -- ^lb, specifiers, rb
+ deriving (Data, Eq, Show, Typeable)
+
+-- |
+-- Note that this data type is separate from ExportSpecifier because the
+-- grammar is slightly different (e.g. in handling of reserved words).
+data JSImportSpecifier
+ = JSImportSpecifier !JSIdent -- ^ident
+ | JSImportSpecifierAs !JSIdent !JSAnnot !JSIdent -- ^ident, as, ident
+ deriving (Data, Eq, Show, Typeable)
+
+data JSExportDeclaration
+ -- = JSExportAllFrom
+ = JSExportFrom JSExportClause JSFromClause !JSSemi -- ^exports, module, semi
+ | JSExportLocals JSExportClause !JSSemi -- ^exports, autosemi
+ | JSExport !JSStatement !JSSemi -- ^body, autosemi
+ -- | JSExportDefault
+ deriving (Data, Eq, Show, Typeable)
+
+data JSExportClause
+ = JSExportClause !JSAnnot !(JSCommaList JSExportSpecifier) !JSAnnot -- ^lb, specifiers, rb
+ deriving (Data, Eq, Show, Typeable)
+
+data JSExportSpecifier
+ = JSExportSpecifier !JSIdent -- ^ident
+ | JSExportSpecifierAs !JSIdent !JSAnnot !JSIdent -- ^ident1, as, ident2
+ deriving (Data, Eq, Show, Typeable)
+
+data JSStatement
+ = JSStatementBlock !JSAnnot ![JSStatement] !JSAnnot !JSSemi -- ^lbrace, stmts, rbrace, autosemi
+ | JSBreak !JSAnnot !JSIdent !JSSemi -- ^break,optional identifier, autosemi
+ | JSLet !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^const, decl, autosemi
+ | JSClass !JSAnnot !JSIdent !JSClassHeritage !JSAnnot ![JSClassElement] !JSAnnot !JSSemi -- ^class, name, optional extends clause, lb, body, rb, autosemi
+ | JSConstant !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^const, decl, autosemi
+ | JSContinue !JSAnnot !JSIdent !JSSemi -- ^continue, optional identifier,autosemi
+ | JSDoWhile !JSAnnot !JSStatement !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSSemi -- ^do,stmt,while,lb,expr,rb,autosemi
+ | JSFor !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,expr,semi,expr,semi,expr,rb.stmt
+ | JSForIn !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,expr,in,expr,rb,stmt
+ | JSForVar !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt
+ | JSForVarIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
+ | JSForLet !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt
+ | JSForLetIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
+ | JSForLetOf !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
+ | JSForConst !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement -- ^for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt
+ | JSForConstIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
+ | JSForConstOf !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
+ | JSForOf !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,expr,in,expr,rb,stmt
+ | JSForVarOf !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement -- ^for,lb,var,vardecl,in,expr,rb,stmt
+ | JSAsyncFunction !JSAnnot !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock !JSSemi -- ^fn,name, lb,parameter list,rb,block,autosemi
+ | JSFunction !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock !JSSemi -- ^fn,name, lb,parameter list,rb,block,autosemi
+ | JSGenerator !JSAnnot !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock !JSSemi -- ^fn,*,name, lb,parameter list,rb,block,autosemi
+ | JSIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement -- ^if,(,expr,),stmt
+ | JSIfElse !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSAnnot !JSStatement -- ^if,(,expr,),stmt,else,rest
+ | JSLabelled !JSIdent !JSAnnot !JSStatement -- ^identifier,colon,stmt
+ | JSEmptyStatement !JSAnnot
+ | JSExpressionStatement !JSExpression !JSSemi
+ | JSAssignStatement !JSExpression !JSAssignOp !JSExpression !JSSemi -- ^lhs, assignop, rhs, autosemi
+ | JSMethodCall !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSSemi
+ | JSReturn !JSAnnot !(Maybe JSExpression) !JSSemi -- ^optional expression,autosemi
+ | JSSwitch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSAnnot ![JSSwitchParts] !JSAnnot !JSSemi -- ^switch,lb,expr,rb,caseblock,autosemi
+ | JSThrow !JSAnnot !JSExpression !JSSemi -- ^throw val autosemi
+ | JSTry !JSAnnot !JSBlock ![JSTryCatch] !JSTryFinally -- ^try,block,catches,finally
+ | JSVariable !JSAnnot !(JSCommaList JSExpression) !JSSemi -- ^var, decl, autosemi
+ | JSWhile !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement -- ^while,lb,expr,rb,stmt
+ | JSWith !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSSemi -- ^with,lb,expr,rb,stmt list
+ deriving (Data, Eq, Show, Typeable)
+
+data JSExpression
+ -- | Terminals
+ = JSIdentifier !JSAnnot !String
+ | JSDecimal !JSAnnot !String
+ | JSLiteral !JSAnnot !String
+ | JSHexInteger !JSAnnot !String
+ | JSOctal !JSAnnot !String
+ | JSStringLiteral !JSAnnot !String
+ | JSRegEx !JSAnnot !String
+
+ -- | Non Terminals
+ | JSArrayLiteral !JSAnnot ![JSArrayElement] !JSAnnot -- ^lb, contents, rb
+ | JSAssignExpression !JSExpression !JSAssignOp !JSExpression -- ^lhs, assignop, rhs
+ | JSAwaitExpression !JSAnnot !JSExpression -- ^await, expr
+ | JSCallExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot -- ^expr, bl, args, rb
+ | JSCallExpressionDot !JSExpression !JSAnnot !JSExpression -- ^expr, dot, expr
+ | JSCallExpressionSquare !JSExpression !JSAnnot !JSExpression !JSAnnot -- ^expr, [, expr, ]
+ | JSClassExpression !JSAnnot !JSIdent !JSClassHeritage !JSAnnot ![JSClassElement] !JSAnnot -- ^class, optional identifier, optional extends clause, lb, body, rb
+ | JSCommaExpression !JSExpression !JSAnnot !JSExpression -- ^expression components
+ | JSExpressionBinary !JSExpression !JSBinOp !JSExpression -- ^lhs, op, rhs
+ | JSExpressionParen !JSAnnot !JSExpression !JSAnnot -- ^lb,expression,rb
+ | JSExpressionPostfix !JSExpression !JSUnaryOp -- ^expression, operator
+ | JSExpressionTernary !JSExpression !JSAnnot !JSExpression !JSAnnot !JSExpression -- ^cond, ?, trueval, :, falseval
+ | JSArrowExpression !JSArrowParameterList !JSAnnot !JSStatement -- ^parameter list,arrow,block`
+ | JSFunctionExpression !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^fn,name,lb, parameter list,rb,block`
+ | JSGeneratorExpression !JSAnnot !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^fn,*,name,lb, parameter list,rb,block`
+ | JSMemberDot !JSExpression !JSAnnot !JSExpression -- ^firstpart, dot, name
+ | JSMemberExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot -- expr, lb, args, rb
+ | JSMemberNew !JSAnnot !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot -- ^new, name, lb, args, rb
+ | JSMemberSquare !JSExpression !JSAnnot !JSExpression !JSAnnot -- ^firstpart, lb, expr, rb
+ | JSNewExpression !JSAnnot !JSExpression -- ^new, expr
+ | JSObjectLiteral !JSAnnot !JSObjectPropertyList !JSAnnot -- ^lbrace contents rbrace
+ | JSSpreadExpression !JSAnnot !JSExpression
+ | JSTemplateLiteral !(Maybe JSExpression) !JSAnnot !String ![JSTemplatePart] -- ^optional tag, lquot, head, parts
+ | JSUnaryExpression !JSUnaryOp !JSExpression
+ | JSVarInitExpression !JSExpression !JSVarInitializer -- ^identifier, initializer
+ | JSYieldExpression !JSAnnot !(Maybe JSExpression) -- ^yield, optional expr
+ | JSYieldFromExpression !JSAnnot !JSAnnot !JSExpression -- ^yield, *, expr
+ deriving (Data, Eq, Show, Typeable)
+
+data JSArrowParameterList
+ = JSUnparenthesizedArrowParameter !JSIdent
+ | JSParenthesizedArrowParameterList !JSAnnot !(JSCommaList JSExpression) !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+data JSBinOp
+ = JSBinOpAnd !JSAnnot
+ | JSBinOpBitAnd !JSAnnot
+ | JSBinOpBitOr !JSAnnot
+ | JSBinOpBitXor !JSAnnot
+ | JSBinOpDivide !JSAnnot
+ | JSBinOpEq !JSAnnot
+ | JSBinOpGe !JSAnnot
+ | JSBinOpGt !JSAnnot
+ | JSBinOpIn !JSAnnot
+ | JSBinOpInstanceOf !JSAnnot
+ | JSBinOpLe !JSAnnot
+ | JSBinOpLsh !JSAnnot
+ | JSBinOpLt !JSAnnot
+ | JSBinOpMinus !JSAnnot
+ | JSBinOpMod !JSAnnot
+ | JSBinOpNeq !JSAnnot
+ | JSBinOpOf !JSAnnot
+ | JSBinOpOr !JSAnnot
+ | JSBinOpPlus !JSAnnot
+ | JSBinOpRsh !JSAnnot
+ | JSBinOpStrictEq !JSAnnot
+ | JSBinOpStrictNeq !JSAnnot
+ | JSBinOpTimes !JSAnnot
+ | JSBinOpUrsh !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+data JSUnaryOp
+ = JSUnaryOpDecr !JSAnnot
+ | JSUnaryOpDelete !JSAnnot
+ | JSUnaryOpIncr !JSAnnot
+ | JSUnaryOpMinus !JSAnnot
+ | JSUnaryOpNot !JSAnnot
+ | JSUnaryOpPlus !JSAnnot
+ | JSUnaryOpTilde !JSAnnot
+ | JSUnaryOpTypeof !JSAnnot
+ | JSUnaryOpVoid !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+data JSSemi
+ = JSSemi !JSAnnot
+ | JSSemiAuto
+ deriving (Data, Eq, Show, Typeable)
+
+data JSAssignOp
+ = JSAssign !JSAnnot
+ | JSTimesAssign !JSAnnot
+ | JSDivideAssign !JSAnnot
+ | JSModAssign !JSAnnot
+ | JSPlusAssign !JSAnnot
+ | JSMinusAssign !JSAnnot
+ | JSLshAssign !JSAnnot
+ | JSRshAssign !JSAnnot
+ | JSUrshAssign !JSAnnot
+ | JSBwAndAssign !JSAnnot
+ | JSBwXorAssign !JSAnnot
+ | JSBwOrAssign !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+data JSTryCatch
+ = JSCatch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSBlock -- ^catch,lb,ident,rb,block
+ | JSCatchIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSExpression !JSAnnot !JSBlock -- ^catch,lb,ident,if,expr,rb,block
+ deriving (Data, Eq, Show, Typeable)
+
+data JSTryFinally
+ = JSFinally !JSAnnot !JSBlock -- ^finally,block
+ | JSNoFinally
+ deriving (Data, Eq, Show, Typeable)
+
+data JSBlock
+ = JSBlock !JSAnnot ![JSStatement] !JSAnnot -- ^lbrace, stmts, rbrace
+ deriving (Data, Eq, Show, Typeable)
+
+data JSSwitchParts
+ = JSCase !JSAnnot !JSExpression !JSAnnot ![JSStatement] -- ^expr,colon,stmtlist
+ | JSDefault !JSAnnot !JSAnnot ![JSStatement] -- ^colon,stmtlist
+ deriving (Data, Eq, Show, Typeable)
+
+data JSVarInitializer
+ = JSVarInit !JSAnnot !JSExpression -- ^ assignop, initializer
+ | JSVarInitNone
+ deriving (Data, Eq, Show, Typeable)
+
+data JSObjectProperty
+ = JSPropertyNameandValue !JSPropertyName !JSAnnot ![JSExpression] -- ^name, colon, value
+ | JSPropertyIdentRef !JSAnnot !String
+ | JSObjectMethod !JSMethodDefinition
+ deriving (Data, Eq, Show, Typeable)
+
+data JSMethodDefinition
+ = JSMethodDefinition !JSPropertyName !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- name, lb, params, rb, block
+ | JSGeneratorMethodDefinition !JSAnnot !JSPropertyName !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^*, name, lb, params, rb, block
+ | JSPropertyAccessor !JSAccessor !JSPropertyName !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSBlock -- ^get/set, name, lb, params, rb, block
+ deriving (Data, Eq, Show, Typeable)
+
+data JSPropertyName
+ = JSPropertyIdent !JSAnnot !String
+ | JSPropertyString !JSAnnot !String
+ | JSPropertyNumber !JSAnnot !String
+ | JSPropertyComputed !JSAnnot !JSExpression !JSAnnot -- ^lb, expr, rb
+ deriving (Data, Eq, Show, Typeable)
+
+type JSObjectPropertyList = JSCommaTrailingList JSObjectProperty
+
+-- | Accessors for JSObjectProperty is either 'get' or 'set'.
+data JSAccessor
+ = JSAccessorGet !JSAnnot
+ | JSAccessorSet !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+data JSIdent
+ = JSIdentName !JSAnnot !String
+ | JSIdentNone
+ deriving (Data, Eq, Show, Typeable)
+
+data JSArrayElement
+ = JSArrayElement !JSExpression
+ | JSArrayComma !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+data JSCommaList a
+ = JSLCons !(JSCommaList a) !JSAnnot !a -- ^head, comma, a
+ | JSLOne !a -- ^ single element (no comma)
+ | JSLNil
+ deriving (Data, Eq, Show, Typeable)
+
+data JSCommaTrailingList a
+ = JSCTLComma !(JSCommaList a) !JSAnnot -- ^list, trailing comma
+ | JSCTLNone !(JSCommaList a) -- ^list
+ deriving (Data, Eq, Show, Typeable)
+
+data JSTemplatePart
+ = JSTemplatePart !JSExpression !JSAnnot !String -- ^expr, rb, suffix
+ deriving (Data, Eq, Show, Typeable)
+
+data JSClassHeritage
+ = JSExtends !JSAnnot !JSExpression
+ | JSExtendsNone
+ deriving (Data, Eq, Show, Typeable)
+
+data JSClassElement
+ = JSClassInstanceMethod !JSMethodDefinition
+ | JSClassStaticMethod !JSAnnot !JSMethodDefinition
+ | JSClassSemi !JSAnnot
+ deriving (Data, Eq, Show, Typeable)
+
+-- -----------------------------------------------------------------------------
+-- | Show the AST elements stripped of their JSAnnot data.
+
+-- Strip out the location info
+showStripped :: JSAST -> String
+showStripped (JSAstProgram xs _) = "JSAstProgram " ++ ss xs
+showStripped (JSAstModule xs _) = "JSAstModule " ++ ss xs
+showStripped (JSAstStatement s _) = "JSAstStatement (" ++ ss s ++ ")"
+showStripped (JSAstExpression e _) = "JSAstExpression (" ++ ss e ++ ")"
+showStripped (JSAstLiteral s _) = "JSAstLiteral (" ++ ss s ++ ")"
+
+
+class ShowStripped a where
+ ss :: a -> String
+
+instance ShowStripped JSStatement where
+ ss (JSStatementBlock _ xs _ _) = "JSStatementBlock " ++ ss xs
+ ss (JSBreak _ JSIdentNone s) = "JSBreak" ++ commaIf (ss s)
+ ss (JSBreak _ (JSIdentName _ n) s) = "JSBreak " ++ singleQuote n ++ commaIf (ss s)
+ ss (JSClass _ n h _lb xs _rb _) = "JSClass " ++ ssid n ++ " (" ++ ss h ++ ") " ++ ss xs
+ ss (JSContinue _ JSIdentNone s) = "JSContinue" ++ commaIf (ss s)
+ ss (JSContinue _ (JSIdentName _ n) s) = "JSContinue " ++ singleQuote n ++ commaIf (ss s)
+ ss (JSConstant _ xs _as) = "JSConstant " ++ ss xs
+ ss (JSDoWhile _d x1 _w _lb x2 _rb x3) = "JSDoWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSFor _ _lb x1s _s1 x2s _s2 x3s _rb x4) = "JSFor " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
+ ss (JSForIn _ _lb x1s _i x2 _rb x3) = "JSForIn " ++ ss x1s ++ " (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForVar _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForVar " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
+ ss (JSForVarIn _ _lb _v x1 _i x2 _rb x3) = "JSForVarIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForLet _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForLet " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
+ ss (JSForLetIn _ _lb _v x1 _i x2 _rb x3) = "JSForLetIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForLetOf _ _lb _v x1 _i x2 _rb x3) = "JSForLetOf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForConst _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForConst " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
+ ss (JSForConstIn _ _lb _v x1 _i x2 _rb x3) = "JSForConstIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForConstOf _ _lb _v x1 _i x2 _rb x3) = "JSForConstOf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForOf _ _lb x1s _i x2 _rb x3) = "JSForOf " ++ ss x1s ++ " (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSForVarOf _ _lb _v x1 _i x2 _rb x3) = "JSForVarOf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSFunction _ n _lb pl _rb x3 _) = "JSFunction " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
+ ss (JSAsyncFunction _ _ n _lb pl _rb x3 _) = "JSAsyncFunction " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
+ ss (JSGenerator _ _ n _lb pl _rb x3 _) = "JSGenerator " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
+ ss (JSIf _ _lb x1 _rb x2) = "JSIf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
+ ss (JSIfElse _ _lb x1 _rb x2 _e x3) = "JSIfElse (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
+ ss (JSLabelled x1 _c x2) = "JSLabelled (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
+ ss (JSLet _ xs _as) = "JSLet " ++ ss xs
+ ss (JSEmptyStatement _) = "JSEmptyStatement"
+ ss (JSExpressionStatement l s) = ss l ++ (let x = ss s in if not (null x) then ',':x else "")
+ 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 ")")
+ ss (JSMethodCall e _ a _ s) = "JSMethodCall (" ++ ss e ++ ",JSArguments " ++ ss a ++ (let x = ss s in if not (null x) then "),"++x else ")")
+ ss (JSReturn _ (Just me) s) = "JSReturn " ++ ss me ++ " " ++ ss s
+ ss (JSReturn _ Nothing s) = "JSReturn " ++ ss s
+ ss (JSSwitch _ _lp x _rp _lb x2 _rb _) = "JSSwitch (" ++ ss x ++ ") " ++ ss x2
+ ss (JSThrow _ x _) = "JSThrow (" ++ ss x ++ ")"
+ ss (JSTry _ xt1 xtc xtf) = "JSTry (" ++ ss xt1 ++ "," ++ ss xtc ++ "," ++ ss xtf ++ ")"
+ ss (JSVariable _ xs _as) = "JSVariable " ++ ss xs
+ ss (JSWhile _ _lb x1 _rb x2) = "JSWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
+ ss (JSWith _ _lb x1 _rb x _) = "JSWith (" ++ ss x1 ++ ") (" ++ ss x ++ ")"
+
+instance ShowStripped JSExpression where
+ ss (JSArrayLiteral _lb xs _rb) = "JSArrayLiteral " ++ ss xs
+ ss (JSAssignExpression lhs op rhs) = "JSOpAssign (" ++ ss op ++ "," ++ ss lhs ++ "," ++ ss rhs ++ ")"
+ ss (JSAwaitExpression _ e) = "JSAwaitExpresson " ++ ss e
+ ss (JSCallExpression ex _ xs _) = "JSCallExpression ("++ ss ex ++ ",JSArguments " ++ ss xs ++ ")"
+ ss (JSCallExpressionDot ex _os xs) = "JSCallExpressionDot (" ++ ss ex ++ "," ++ ss xs ++ ")"
+ ss (JSCallExpressionSquare ex _os xs _cs) = "JSCallExpressionSquare (" ++ ss ex ++ "," ++ ss xs ++ ")"
+ ss (JSClassExpression _ n h _lb xs _rb) = "JSClassExpression " ++ ssid n ++ " (" ++ ss h ++ ") " ++ ss xs
+ ss (JSDecimal _ s) = "JSDecimal " ++ singleQuote s
+ ss (JSCommaExpression l _ r) = "JSExpression [" ++ ss l ++ "," ++ ss r ++ "]"
+ ss (JSExpressionBinary x2 op x3) = "JSExpressionBinary (" ++ ss op ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
+ ss (JSExpressionParen _lp x _rp) = "JSExpressionParen (" ++ ss x ++ ")"
+ ss (JSExpressionPostfix xs op) = "JSExpressionPostfix (" ++ ss op ++ "," ++ ss xs ++ ")"
+ ss (JSExpressionTernary x1 _q x2 _c x3) = "JSExpressionTernary (" ++ ss x1 ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
+ ss (JSArrowExpression ps _ e) = "JSArrowExpression (" ++ ss ps ++ ") => " ++ ss e
+ ss (JSFunctionExpression _ n _lb pl _rb x3) = "JSFunctionExpression " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
+ ss (JSGeneratorExpression _ _ n _lb pl _rb x3) = "JSGeneratorExpression " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
+ ss (JSHexInteger _ s) = "JSHexInteger " ++ singleQuote s
+ ss (JSOctal _ s) = "JSOctal " ++ singleQuote s
+ ss (JSIdentifier _ s) = "JSIdentifier " ++ singleQuote s
+ ss (JSLiteral _ []) = "JSLiteral ''"
+ ss (JSLiteral _ s) = "JSLiteral " ++ singleQuote s
+ ss (JSMemberDot x1s _d x2 ) = "JSMemberDot (" ++ ss x1s ++ "," ++ ss x2 ++ ")"
+ ss (JSMemberExpression e _ a _) = "JSMemberExpression (" ++ ss e ++ ",JSArguments " ++ ss a ++ ")"
+ ss (JSMemberNew _a n _ s _) = "JSMemberNew (" ++ ss n ++ ",JSArguments " ++ ss s ++ ")"
+ ss (JSMemberSquare x1s _lb x2 _rb) = "JSMemberSquare (" ++ ss x1s ++ "," ++ ss x2 ++ ")"
+ ss (JSNewExpression _n e) = "JSNewExpression " ++ ss e
+ ss (JSObjectLiteral _lb xs _rb) = "JSObjectLiteral " ++ ss xs
+ ss (JSRegEx _ s) = "JSRegEx " ++ singleQuote s
+ ss (JSStringLiteral _ s) = "JSStringLiteral " ++ s
+ ss (JSUnaryExpression op x) = "JSUnaryExpression (" ++ ss op ++ "," ++ ss x ++ ")"
+ ss (JSVarInitExpression x1 x2) = "JSVarInitExpression (" ++ ss x1 ++ ") " ++ ss x2
+ ss (JSYieldExpression _ Nothing) = "JSYieldExpression ()"
+ ss (JSYieldExpression _ (Just x)) = "JSYieldExpression (" ++ ss x ++ ")"
+ ss (JSYieldFromExpression _ _ x) = "JSYieldFromExpression (" ++ ss x ++ ")"
+ ss (JSSpreadExpression _ x1) = "JSSpreadExpression (" ++ ss x1 ++ ")"
+ ss (JSTemplateLiteral Nothing _ s ps) = "JSTemplateLiteral (()," ++ singleQuote s ++ "," ++ ss ps ++ ")"
+ ss (JSTemplateLiteral (Just t) _ s ps) = "JSTemplateLiteral ((" ++ ss t ++ ")," ++ singleQuote s ++ "," ++ ss ps ++ ")"
+
+instance ShowStripped JSArrowParameterList where
+ ss (JSUnparenthesizedArrowParameter x) = ss x
+ ss (JSParenthesizedArrowParameterList _ xs _) = ss xs
+
+instance ShowStripped JSModuleItem where
+ ss (JSModuleExportDeclaration _ x1) = "JSModuleExportDeclaration (" ++ ss x1 ++ ")"
+ ss (JSModuleImportDeclaration _ x1) = "JSModuleImportDeclaration (" ++ ss x1 ++ ")"
+ ss (JSModuleStatementListItem x1) = "JSModuleStatementListItem (" ++ ss x1 ++ ")"
+
+instance ShowStripped JSImportDeclaration where
+ ss (JSImportDeclaration imp from _) = "JSImportDeclaration (" ++ ss imp ++ "," ++ ss from ++ ")"
+ ss (JSImportDeclarationBare _ m _) = "JSImportDeclarationBare (" ++ singleQuote m ++ ")"
+
+instance ShowStripped JSImportClause where
+ ss (JSImportClauseDefault x) = "JSImportClauseDefault (" ++ ss x ++ ")"
+ ss (JSImportClauseNameSpace x) = "JSImportClauseNameSpace (" ++ ss x ++ ")"
+ ss (JSImportClauseNamed x) = "JSImportClauseNameSpace (" ++ ss x ++ ")"
+ ss (JSImportClauseDefaultNameSpace x1 _ x2) = "JSImportClauseDefaultNameSpace (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
+ ss (JSImportClauseDefaultNamed x1 _ x2) = "JSImportClauseDefaultNamed (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
+
+instance ShowStripped JSFromClause where
+ ss (JSFromClause _ _ m) = "JSFromClause " ++ singleQuote m
+
+instance ShowStripped JSImportNameSpace where
+ ss (JSImportNameSpace _ _ x) = "JSImportNameSpace (" ++ ss x ++ ")"
+
+instance ShowStripped JSImportsNamed where
+ ss (JSImportsNamed _ xs _) = "JSImportsNamed (" ++ ss xs ++ ")"
+
+instance ShowStripped JSImportSpecifier where
+ ss (JSImportSpecifier x1) = "JSImportSpecifier (" ++ ss x1 ++ ")"
+ ss (JSImportSpecifierAs x1 _ x2) = "JSImportSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
+
+instance ShowStripped JSExportDeclaration where
+ ss (JSExportFrom xs from _) = "JSExportFrom (" ++ ss xs ++ "," ++ ss from ++ ")"
+ ss (JSExportLocals xs _) = "JSExportLocals (" ++ ss xs ++ ")"
+ ss (JSExport x1 _) = "JSExport (" ++ ss x1 ++ ")"
+
+instance ShowStripped JSExportClause where
+ ss (JSExportClause _ xs _) = "JSExportClause (" ++ ss xs ++ ")"
+
+instance ShowStripped JSExportSpecifier where
+ ss (JSExportSpecifier x1) = "JSExportSpecifier (" ++ ss x1 ++ ")"
+ ss (JSExportSpecifierAs x1 _ x2) = "JSExportSpecifierAs (" ++ ss x1 ++ "," ++ ss x2 ++ ")"
+
+instance ShowStripped JSTryCatch where
+ ss (JSCatch _ _lb x1 _rb x3) = "JSCatch (" ++ ss x1 ++ "," ++ ss x3 ++ ")"
+ ss (JSCatchIf _ _lb x1 _ ex _rb x3) = "JSCatch (" ++ ss x1 ++ ") if " ++ ss ex ++ " (" ++ ss x3 ++ ")"
+
+instance ShowStripped JSTryFinally where
+ ss (JSFinally _ x) = "JSFinally (" ++ ss x ++ ")"
+ ss JSNoFinally = "JSFinally ()"
+
+instance ShowStripped JSIdent where
+ ss (JSIdentName _ s) = "JSIdentifier " ++ singleQuote s
+ ss JSIdentNone = "JSIdentNone"
+
+instance ShowStripped JSObjectProperty where
+ ss (JSPropertyNameandValue x1 _colon x2s) = "JSPropertyNameandValue (" ++ ss x1 ++ ") " ++ ss x2s
+ ss (JSPropertyIdentRef _ s) = "JSPropertyIdentRef " ++ singleQuote s
+ ss (JSObjectMethod m) = ss m
+
+instance ShowStripped JSMethodDefinition where
+ ss (JSMethodDefinition x1 _lb1 x2s _rb1 x3) = "JSMethodDefinition (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
+ ss (JSPropertyAccessor s x1 _lb1 x2s _rb1 x3) = "JSPropertyAccessor " ++ ss s ++ " (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
+ ss (JSGeneratorMethodDefinition _ x1 _lb1 x2s _rb1 x3) = "JSGeneratorMethodDefinition (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
+
+instance ShowStripped JSPropertyName where
+ ss (JSPropertyIdent _ s) = "JSIdentifier " ++ singleQuote s
+ ss (JSPropertyString _ s) = "JSIdentifier " ++ singleQuote s
+ ss (JSPropertyNumber _ s) = "JSIdentifier " ++ singleQuote s
+ ss (JSPropertyComputed _ x _) = "JSPropertyComputed (" ++ ss x ++ ")"
+
+instance ShowStripped JSAccessor where
+ ss (JSAccessorGet _) = "JSAccessorGet"
+ ss (JSAccessorSet _) = "JSAccessorSet"
+
+instance ShowStripped JSBlock where
+ ss (JSBlock _ xs _) = "JSBlock " ++ ss xs
+
+instance ShowStripped JSSwitchParts where
+ ss (JSCase _ x1 _c x2s) = "JSCase (" ++ ss x1 ++ ") (" ++ ss x2s ++ ")"
+ ss (JSDefault _ _c xs) = "JSDefault (" ++ ss xs ++ ")"
+
+instance ShowStripped JSBinOp where
+ ss (JSBinOpAnd _) = "'&&'"
+ ss (JSBinOpBitAnd _) = "'&'"
+ ss (JSBinOpBitOr _) = "'|'"
+ ss (JSBinOpBitXor _) = "'^'"
+ ss (JSBinOpDivide _) = "'/'"
+ ss (JSBinOpEq _) = "'=='"
+ ss (JSBinOpGe _) = "'>='"
+ ss (JSBinOpGt _) = "'>'"
+ ss (JSBinOpIn _) = "'in'"
+ ss (JSBinOpInstanceOf _) = "'instanceof'"
+ ss (JSBinOpLe _) = "'<='"
+ ss (JSBinOpLsh _) = "'<<'"
+ ss (JSBinOpLt _) = "'<'"
+ ss (JSBinOpMinus _) = "'-'"
+ ss (JSBinOpMod _) = "'%'"
+ ss (JSBinOpNeq _) = "'!='"
+ ss (JSBinOpOf _) = "'of'"
+ ss (JSBinOpOr _) = "'||'"
+ ss (JSBinOpPlus _) = "'+'"
+ ss (JSBinOpRsh _) = "'>>'"
+ ss (JSBinOpStrictEq _) = "'==='"
+ ss (JSBinOpStrictNeq _) = "'!=='"
+ ss (JSBinOpTimes _) = "'*'"
+ ss (JSBinOpUrsh _) = "'>>>'"
+
+instance ShowStripped JSUnaryOp where
+ ss (JSUnaryOpDecr _) = "'--'"
+ ss (JSUnaryOpDelete _) = "'delete'"
+ ss (JSUnaryOpIncr _) = "'++'"
+ ss (JSUnaryOpMinus _) = "'-'"
+ ss (JSUnaryOpNot _) = "'!'"
+ ss (JSUnaryOpPlus _) = "'+'"
+ ss (JSUnaryOpTilde _) = "'~'"
+ ss (JSUnaryOpTypeof _) = "'typeof'"
+ ss (JSUnaryOpVoid _) = "'void'"
+
+instance ShowStripped JSAssignOp where
+ ss (JSAssign _) = "'='"
+ ss (JSTimesAssign _) = "'*='"
+ ss (JSDivideAssign _) = "'/='"
+ ss (JSModAssign _) = "'%='"
+ ss (JSPlusAssign _) = "'+='"
+ ss (JSMinusAssign _) = "'-='"
+ ss (JSLshAssign _) = "'<<='"
+ ss (JSRshAssign _) = "'>>='"
+ ss (JSUrshAssign _) = "'>>>='"
+ ss (JSBwAndAssign _) = "'&='"
+ ss (JSBwXorAssign _) = "'^='"
+ ss (JSBwOrAssign _) = "'|='"
+
+instance ShowStripped JSVarInitializer where
+ ss (JSVarInit _ n) = "[" ++ ss n ++ "]"
+ ss JSVarInitNone = ""
+
+instance ShowStripped JSSemi where
+ ss (JSSemi _) = "JSSemicolon"
+ ss JSSemiAuto = ""
+
+instance ShowStripped JSArrayElement where
+ ss (JSArrayElement e) = ss e
+ ss (JSArrayComma _) = "JSComma"
+
+instance ShowStripped JSTemplatePart where
+ ss (JSTemplatePart e _ s) = "(" ++ ss e ++ "," ++ singleQuote s ++ ")"
+
+instance ShowStripped JSClassHeritage where
+ ss JSExtendsNone = ""
+ ss (JSExtends _ x) = ss x
+
+instance ShowStripped JSClassElement where
+ ss (JSClassInstanceMethod m) = ss m
+ ss (JSClassStaticMethod _ m) = "JSClassStaticMethod (" ++ ss m ++ ")"
+ ss (JSClassSemi _) = "JSClassSemi"
+
+instance ShowStripped a => ShowStripped (JSCommaList a) where
+ ss xs = "(" ++ commaJoin (map ss $ fromCommaList xs) ++ ")"
+
+instance ShowStripped a => ShowStripped (JSCommaTrailingList a) where
+ ss (JSCTLComma xs _) = "[" ++ commaJoin (map ss $ fromCommaList xs) ++ ",JSComma]"
+ ss (JSCTLNone xs) = "[" ++ commaJoin (map ss $ fromCommaList xs) ++ "]"
+
+instance ShowStripped a => ShowStripped [a] where
+ ss xs = "[" ++ commaJoin (map ss xs) ++ "]"
+
+-- -----------------------------------------------------------------------------
+-- Helpers.
+
+commaJoin :: [String] -> String
+commaJoin s = intercalate "," $ filter (not . null) s
+
+fromCommaList :: JSCommaList a -> [a]
+fromCommaList (JSLCons l _ i) = fromCommaList l ++ [i]
+fromCommaList (JSLOne i) = [i]
+fromCommaList JSLNil = []
+
+singleQuote :: String -> String
+singleQuote s = '\'' : (s ++ "'")
+
+ssid :: JSIdent -> String
+ssid (JSIdentName _ s) = singleQuote s
+ssid JSIdentNone = "''"
+
+commaIf :: String -> String
+commaIf "" = ""
+commaIf xs = ',' : xs
+
+
+deAnnot :: JSBinOp -> JSBinOp
+deAnnot (JSBinOpAnd _) = JSBinOpAnd JSNoAnnot
+deAnnot (JSBinOpBitAnd _) = JSBinOpBitAnd JSNoAnnot
+deAnnot (JSBinOpBitOr _) = JSBinOpBitOr JSNoAnnot
+deAnnot (JSBinOpBitXor _) = JSBinOpBitXor JSNoAnnot
+deAnnot (JSBinOpDivide _) = JSBinOpDivide JSNoAnnot
+deAnnot (JSBinOpEq _) = JSBinOpEq JSNoAnnot
+deAnnot (JSBinOpGe _) = JSBinOpGe JSNoAnnot
+deAnnot (JSBinOpGt _) = JSBinOpGt JSNoAnnot
+deAnnot (JSBinOpIn _) = JSBinOpIn JSNoAnnot
+deAnnot (JSBinOpInstanceOf _) = JSBinOpInstanceOf JSNoAnnot
+deAnnot (JSBinOpLe _) = JSBinOpLe JSNoAnnot
+deAnnot (JSBinOpLsh _) = JSBinOpLsh JSNoAnnot
+deAnnot (JSBinOpLt _) = JSBinOpLt JSNoAnnot
+deAnnot (JSBinOpMinus _) = JSBinOpMinus JSNoAnnot
+deAnnot (JSBinOpMod _) = JSBinOpMod JSNoAnnot
+deAnnot (JSBinOpNeq _) = JSBinOpNeq JSNoAnnot
+deAnnot (JSBinOpOf _) = JSBinOpOf JSNoAnnot
+deAnnot (JSBinOpOr _) = JSBinOpOr JSNoAnnot
+deAnnot (JSBinOpPlus _) = JSBinOpPlus JSNoAnnot
+deAnnot (JSBinOpRsh _) = JSBinOpRsh JSNoAnnot
+deAnnot (JSBinOpStrictEq _) = JSBinOpStrictEq JSNoAnnot
+deAnnot (JSBinOpStrictNeq _) = JSBinOpStrictNeq JSNoAnnot
+deAnnot (JSBinOpTimes _) = JSBinOpTimes JSNoAnnot
+deAnnot (JSBinOpUrsh _) = JSBinOpUrsh JSNoAnnot
+
+binOpEq :: JSBinOp -> JSBinOp -> Bool
+binOpEq a b = deAnnot a == deAnnot b
--- /dev/null
+{
+{-# LANGUAGE BangPatterns #-}
+module Language.JavaScript.Parser.Grammar7
+ ( parseProgram
+ , parseModule
+ , parseStatement
+ , parseExpression
+ , parseLiteral
+ ) where
+
+import Data.Char
+import Data.Functor (($>))
+import Language.JavaScript.Parser.Lexer
+import Language.JavaScript.Parser.ParserMonad
+import Language.JavaScript.Parser.SrcLocation
+import Language.JavaScript.Parser.Token
+import qualified Language.JavaScript.Parser.AST as AST
+
+}
+
+-- The name of the generated function to be exported from the module
+%name parseProgram Program
+%name parseModule Module
+%name parseLiteral LiteralMain
+%name parseExpression ExpressionMain
+%name parseStatement StatementMain
+
+%tokentype { Token }
+%error { parseError }
+%monad { Alex } { >>= } { return }
+%lexer { lexCont } { EOFToken {} }
+
+
+%token
+
+ ';' { SemiColonToken {} }
+ ',' { CommaToken {} }
+ '?' { HookToken {} }
+ ':' { ColonToken {} }
+ '||' { OrToken {} }
+ '&&' { AndToken {} }
+ '|' { BitwiseOrToken {} }
+ '^' { BitwiseXorToken {} }
+ '&' { BitwiseAndToken {} }
+ '=>' { ArrowToken {} }
+ '===' { StrictEqToken {} }
+ '==' { EqToken {} }
+ '*=' { TimesAssignToken {} }
+ '/=' { DivideAssignToken {} }
+ '%=' { ModAssignToken {} }
+ '+=' { PlusAssignToken {} }
+ '-=' { MinusAssignToken {} }
+ '<<=' { LshAssignToken {} }
+ '>>=' { RshAssignToken {} }
+ '>>>=' { UrshAssignToken {} }
+ '&=' { AndAssignToken {} }
+ '^=' { XorAssignToken {} }
+ '|=' { OrAssignToken {} }
+ '=' { SimpleAssignToken {} }
+ '!==' { StrictNeToken {} }
+ '!=' { NeToken {} }
+ '<<' { LshToken {} }
+ '<=' { LeToken {} }
+ '<' { LtToken {} }
+ '>>>' { UrshToken {} }
+ '>>' { RshToken {} }
+ '>=' { GeToken {} }
+ '>' { GtToken {} }
+ '++' { IncrementToken {} }
+ '--' { DecrementToken {} }
+ '+' { PlusToken {} }
+ '-' { MinusToken {} }
+ '*' { MulToken {} }
+ '/' { DivToken {} }
+ '%' { ModToken {} }
+ '!' { NotToken {} }
+ '~' { BitwiseNotToken {} }
+ '...' { SpreadToken {} }
+ '.' { DotToken {} }
+ '[' { LeftBracketToken {} }
+ ']' { RightBracketToken {} }
+ '{' { LeftCurlyToken {} }
+ '}' { RightCurlyToken {} }
+ '(' { LeftParenToken {} }
+ ')' { RightParenToken {} }
+
+ 'as' { AsToken {} }
+ 'autosemi' { AutoSemiToken {} }
+ 'async' { AsyncToken {} }
+ 'await' { AwaitToken {} }
+ 'break' { BreakToken {} }
+ 'case' { CaseToken {} }
+ 'catch' { CatchToken {} }
+ 'class' { ClassToken {} }
+ 'const' { ConstToken {} }
+ 'continue' { ContinueToken {} }
+ 'debugger' { DebuggerToken {} }
+ 'default' { DefaultToken {} }
+ 'delete' { DeleteToken {} }
+ 'do' { DoToken {} }
+ 'else' { ElseToken {} }
+ 'enum' { EnumToken {} }
+ 'export' { ExportToken {} }
+ 'extends' { ExtendsToken {} }
+ 'false' { FalseToken {} }
+ 'finally' { FinallyToken {} }
+ 'for' { ForToken {} }
+ 'function' { FunctionToken {} }
+ 'from' { FromToken {} }
+ 'get' { GetToken {} }
+ 'if' { IfToken {} }
+ 'import' { ImportToken {} }
+ 'in' { InToken {} }
+ 'instanceof' { InstanceofToken {} }
+ 'let' { LetToken {} }
+ 'new' { NewToken {} }
+ 'null' { NullToken {} }
+ 'of' { OfToken {} }
+ 'return' { ReturnToken {} }
+ 'set' { SetToken {} }
+ 'static' { StaticToken {} }
+ 'super' { SuperToken {} }
+ 'switch' { SwitchToken {} }
+ 'this' { ThisToken {} }
+ 'throw' { ThrowToken {} }
+ 'true' { TrueToken {} }
+ 'try' { TryToken {} }
+ 'typeof' { TypeofToken {} }
+ 'var' { VarToken {} }
+ 'void' { VoidToken {} }
+ 'while' { WhileToken {} }
+ 'with' { WithToken {} }
+ 'yield' { YieldToken {} }
+
+
+ 'ident' { IdentifierToken {} }
+ 'decimal' { DecimalToken {} }
+ 'hexinteger' { HexIntegerToken {} }
+ 'octal' { OctalToken {} }
+ 'string' { StringToken {} }
+ 'regex' { RegExToken {} }
+ 'tmplnosub' { NoSubstitutionTemplateToken {} }
+ 'tmplhead' { TemplateHeadToken {} }
+ 'tmplmiddle' { TemplateMiddleToken {} }
+ 'tmpltail' { TemplateTailToken {} }
+
+ 'future' { FutureToken {} }
+
+ 'tail' { TailToken {} }
+
+
+%%
+
+-- ---------------------------------------------------------------------
+-- Sort out automatically inserted semi-colons.
+-- A MaybeSemi is an actual semi-colon or nothing.
+-- An AutoSemu is either an actual semi-colon or 'virtual' semi-colon inserted
+-- by the Alex lexer or nothing.
+
+MaybeSemi :: { AST.JSSemi }
+MaybeSemi : ';' { AST.JSSemi (mkJSAnnot $1) }
+ | { AST.JSSemiAuto }
+
+AutoSemi :: { AST.JSSemi }
+AutoSemi : ';' { AST.JSSemi (mkJSAnnot $1) }
+ | 'autosemi' { AST.JSSemiAuto }
+ | { AST.JSSemiAuto }
+
+-- ---------------------------------------------------------------------
+
+-- Helpers
+
+LParen :: { AST.JSAnnot }
+LParen : '(' { mkJSAnnot $1 }
+
+RParen :: { AST.JSAnnot }
+RParen : ')' { mkJSAnnot $1 }
+
+LBrace :: { AST.JSAnnot }
+LBrace : '{' { mkJSAnnot $1 }
+
+RBrace :: { AST.JSAnnot }
+RBrace : '}' { mkJSAnnot $1 }
+
+LSquare :: { AST.JSAnnot }
+LSquare : '[' { mkJSAnnot $1 }
+
+RSquare :: { AST.JSAnnot }
+RSquare : ']' { mkJSAnnot $1 }
+
+Comma :: { AST.JSAnnot }
+Comma : ',' { mkJSAnnot $1 }
+
+Colon :: { AST.JSAnnot }
+Colon : ':' { mkJSAnnot $1 }
+
+Semi :: { AST.JSAnnot }
+Semi : ';' { mkJSAnnot $1 }
+
+Arrow :: { AST.JSAnnot }
+Arrow : '=>' { mkJSAnnot $1 }
+
+Spread :: { AST.JSAnnot }
+Spread : '...' { mkJSAnnot $1 }
+
+Dot :: { AST.JSAnnot }
+Dot : '.' { mkJSAnnot $1 }
+
+As :: { AST.JSAnnot }
+As : 'as' { mkJSAnnot $1 }
+
+Increment :: { AST.JSUnaryOp }
+Increment : '++' { AST.JSUnaryOpIncr (mkJSAnnot $1) }
+
+Decrement :: { AST.JSUnaryOp }
+Decrement : '--' { AST.JSUnaryOpDecr (mkJSAnnot $1) }
+
+Delete :: { AST.JSUnaryOp }
+Delete : 'delete' { AST.JSUnaryOpDelete (mkJSAnnot $1) }
+
+Void :: { AST.JSUnaryOp }
+Void : 'void' { AST.JSUnaryOpVoid (mkJSAnnot $1) }
+
+Typeof :: { AST.JSUnaryOp }
+Typeof : 'typeof' { AST.JSUnaryOpTypeof (mkJSAnnot $1) }
+
+Plus :: { AST.JSBinOp }
+Plus : '+' { AST.JSBinOpPlus (mkJSAnnot $1) }
+
+Minus :: { AST.JSBinOp }
+Minus : '-' { AST.JSBinOpMinus (mkJSAnnot $1) }
+
+Tilde :: { AST.JSUnaryOp }
+Tilde : '~' { AST.JSUnaryOpTilde (mkJSAnnot $1) }
+
+Not :: { AST.JSUnaryOp }
+Not : '!' { AST.JSUnaryOpNot (mkJSAnnot $1) }
+
+Mul :: { AST.JSBinOp }
+Mul : '*' { AST.JSBinOpTimes (mkJSAnnot $1) }
+
+Div :: { AST.JSBinOp }
+Div : '/' { AST.JSBinOpDivide (mkJSAnnot $1) }
+
+Mod :: { AST.JSBinOp }
+Mod : '%' { AST.JSBinOpMod (mkJSAnnot $1) }
+
+Lsh :: { AST.JSBinOp }
+Lsh : '<<' { AST.JSBinOpLsh (mkJSAnnot $1) }
+
+Rsh :: { AST.JSBinOp }
+Rsh : '>>' { AST.JSBinOpRsh (mkJSAnnot $1) }
+
+Ursh :: { AST.JSBinOp }
+Ursh : '>>>' { AST.JSBinOpUrsh (mkJSAnnot $1) }
+
+Le :: { AST.JSBinOp }
+Le : '<=' { AST.JSBinOpLe (mkJSAnnot $1) }
+
+Lt :: { AST.JSBinOp }
+Lt : '<' { AST.JSBinOpLt (mkJSAnnot $1) }
+
+Ge :: { AST.JSBinOp }
+Ge : '>=' { AST.JSBinOpGe (mkJSAnnot $1) }
+
+Gt :: { AST.JSBinOp }
+Gt : '>' { AST.JSBinOpGt (mkJSAnnot $1) }
+
+In :: { AST.JSBinOp }
+In : 'in' { AST.JSBinOpIn (mkJSAnnot $1) }
+
+Instanceof :: { AST.JSBinOp }
+Instanceof : 'instanceof' { AST.JSBinOpInstanceOf (mkJSAnnot $1) }
+
+StrictEq :: { AST.JSBinOp }
+StrictEq : '===' { AST.JSBinOpStrictEq (mkJSAnnot $1) }
+
+Equal :: { AST.JSBinOp }
+Equal : '==' { AST.JSBinOpEq (mkJSAnnot $1) }
+
+StrictNe :: { AST.JSBinOp }
+StrictNe : '!==' { AST.JSBinOpStrictNeq (mkJSAnnot $1) }
+
+Ne :: { AST.JSBinOp }
+Ne : '!=' { AST.JSBinOpNeq (mkJSAnnot $1)}
+
+Of :: { AST.JSBinOp }
+Of : 'of' { AST.JSBinOpOf (mkJSAnnot $1) }
+
+Or :: { AST.JSBinOp }
+Or : '||' { AST.JSBinOpOr (mkJSAnnot $1) }
+
+And :: { AST.JSBinOp }
+And : '&&' { AST.JSBinOpAnd (mkJSAnnot $1) }
+
+BitOr :: { AST.JSBinOp }
+BitOr : '|' { AST.JSBinOpBitOr (mkJSAnnot $1) }
+
+BitAnd :: { AST.JSBinOp }
+BitAnd : '&' { AST.JSBinOpBitAnd (mkJSAnnot $1) }
+
+BitXor :: { AST.JSBinOp }
+BitXor : '^' { AST.JSBinOpBitXor (mkJSAnnot $1)}
+
+Hook :: { AST.JSAnnot }
+Hook : '?' { mkJSAnnot $1 }
+
+SimpleAssign :: { AST.JSAnnot }
+SimpleAssign : '=' { mkJSAnnot $1 }
+
+OpAssign :: { AST.JSAssignOp }
+OpAssign : '*=' { AST.JSTimesAssign (mkJSAnnot $1) }
+ | '/=' { AST.JSDivideAssign (mkJSAnnot $1) }
+ | '%=' { AST.JSModAssign (mkJSAnnot $1) }
+ | '+=' { AST.JSPlusAssign (mkJSAnnot $1) }
+ | '-=' { AST.JSMinusAssign (mkJSAnnot $1) }
+ | '<<=' { AST.JSLshAssign (mkJSAnnot $1) }
+ | '>>=' { AST.JSRshAssign (mkJSAnnot $1) }
+ | '>>>=' { AST.JSUrshAssign (mkJSAnnot $1) }
+ | '&=' { AST.JSBwAndAssign (mkJSAnnot $1) }
+ | '^=' { AST.JSBwXorAssign (mkJSAnnot $1) }
+ | '|=' { AST.JSBwOrAssign (mkJSAnnot $1) }
+
+-- IdentifierName :: See 7.6
+-- IdentifierStart
+-- IdentifierName IdentifierPart
+-- Note: This production needs to precede the productions for all keyword
+-- statements and PrimaryExpression. Contra the Happy documentation, in the
+-- case of a reduce/reduce conflict, the *later* rule takes precedence, and
+-- the ambiguity of, for example, `{break}` needs to resolve in favor of
+-- `break` as a keyword and not as an identifier in property shorthand
+-- syntax.
+-- TODO: make this include any reserved word too, including future ones
+IdentifierName :: { AST.JSExpression }
+IdentifierName : Identifier {$1}
+ | 'async' { AST.JSIdentifier (mkJSAnnot $1) "async" }
+ | 'await' { AST.JSIdentifier (mkJSAnnot $1) "await" }
+ | 'break' { AST.JSIdentifier (mkJSAnnot $1) "break" }
+ | 'case' { AST.JSIdentifier (mkJSAnnot $1) "case" }
+ | 'catch' { AST.JSIdentifier (mkJSAnnot $1) "catch" }
+ | 'class' { AST.JSIdentifier (mkJSAnnot $1) "class" }
+ | 'const' { AST.JSIdentifier (mkJSAnnot $1) "const" }
+ | 'continue' { AST.JSIdentifier (mkJSAnnot $1) "continue" }
+ | 'debugger' { AST.JSIdentifier (mkJSAnnot $1) "debugger" }
+ | 'default' { AST.JSIdentifier (mkJSAnnot $1) "default" }
+ | 'delete' { AST.JSIdentifier (mkJSAnnot $1) "delete" }
+ | 'do' { AST.JSIdentifier (mkJSAnnot $1) "do" }
+ | 'else' { AST.JSIdentifier (mkJSAnnot $1) "else" }
+ | 'enum' { AST.JSIdentifier (mkJSAnnot $1) "enum" }
+ | 'export' { AST.JSIdentifier (mkJSAnnot $1) "export" }
+ | 'extends' { AST.JSIdentifier (mkJSAnnot $1) "extends" }
+ | 'false' { AST.JSIdentifier (mkJSAnnot $1) "false" }
+ | 'finally' { AST.JSIdentifier (mkJSAnnot $1) "finally" }
+ | 'for' { AST.JSIdentifier (mkJSAnnot $1) "for" }
+ | 'function' { AST.JSIdentifier (mkJSAnnot $1) "function" }
+ | 'if' { AST.JSIdentifier (mkJSAnnot $1) "if" }
+ | 'in' { AST.JSIdentifier (mkJSAnnot $1) "in" }
+ | 'instanceof' { AST.JSIdentifier (mkJSAnnot $1) "instanceof" }
+ | 'let' { AST.JSIdentifier (mkJSAnnot $1) "let" }
+ | 'new' { AST.JSIdentifier (mkJSAnnot $1) "new" }
+ | 'null' { AST.JSIdentifier (mkJSAnnot $1) "null" }
+ | 'of' { AST.JSIdentifier (mkJSAnnot $1) "of" }
+ | 'return' { AST.JSIdentifier (mkJSAnnot $1) "return" }
+ | 'static' { AST.JSIdentifier (mkJSAnnot $1) "static" }
+ | 'super' { AST.JSIdentifier (mkJSAnnot $1) "super" }
+ | 'switch' { AST.JSIdentifier (mkJSAnnot $1) "switch" }
+ | 'this' { AST.JSIdentifier (mkJSAnnot $1) "this" }
+ | 'throw' { AST.JSIdentifier (mkJSAnnot $1) "throw" }
+ | 'true' { AST.JSIdentifier (mkJSAnnot $1) "true" }
+ | 'try' { AST.JSIdentifier (mkJSAnnot $1) "try" }
+ | 'typeof' { AST.JSIdentifier (mkJSAnnot $1) "typeof" }
+ | 'var' { AST.JSIdentifier (mkJSAnnot $1) "var" }
+ | 'void' { AST.JSIdentifier (mkJSAnnot $1) "void" }
+ | 'while' { AST.JSIdentifier (mkJSAnnot $1) "while" }
+ | 'with' { AST.JSIdentifier (mkJSAnnot $1) "with" }
+ | 'future' { AST.JSIdentifier (mkJSAnnot $1) (tokenLiteral $1) }
+
+Var :: { AST.JSAnnot }
+Var : 'var' { mkJSAnnot $1 }
+
+Let :: { AST.JSAnnot }
+Let : 'let' { mkJSAnnot $1 }
+
+Const :: { AST.JSAnnot }
+Const : 'const' { mkJSAnnot $1 }
+
+Import :: { AST.JSAnnot }
+Import : 'import' { mkJSAnnot $1 }
+
+From :: { AST.JSAnnot }
+From : 'from' { mkJSAnnot $1 }
+
+Export :: { AST.JSAnnot }
+Export : 'export' { mkJSAnnot $1 }
+
+If :: { AST.JSAnnot }
+If : 'if' { mkJSAnnot $1 }
+
+Else :: { AST.JSAnnot }
+Else : 'else' { mkJSAnnot $1 }
+
+Do :: { AST.JSAnnot }
+Do : 'do' { mkJSAnnot $1 }
+
+While :: { AST.JSAnnot }
+While : 'while' { mkJSAnnot $1 }
+
+For :: { AST.JSAnnot }
+For : 'for' { mkJSAnnot $1 }
+
+Continue :: { AST.JSAnnot }
+Continue : 'continue' { mkJSAnnot $1 }
+
+Async :: { AST.JSAnnot }
+Async : 'async' { mkJSAnnot $1 }
+
+Await :: { AST.JSAnnot }
+Await : 'await' { mkJSAnnot $1 }
+
+Break :: { AST.JSAnnot }
+Break : 'break' { mkJSAnnot $1 }
+
+Return :: { AST.JSAnnot }
+Return : 'return' { mkJSAnnot $1 }
+
+With :: { AST.JSAnnot }
+With : 'with' { mkJSAnnot $1 }
+
+Switch :: { AST.JSAnnot }
+Switch : 'switch' { mkJSAnnot $1 }
+
+Case :: { AST.JSAnnot }
+Case : 'case' { mkJSAnnot $1 }
+
+Default :: { AST.JSAnnot }
+Default : 'default' { mkJSAnnot $1 }
+
+Throw :: { AST.JSAnnot }
+Throw : 'throw' { mkJSAnnot $1 {- 'Throw' -} }
+
+Try :: { AST.JSAnnot }
+Try : 'try' { mkJSAnnot $1 }
+
+CatchL :: { AST.JSAnnot }
+CatchL : 'catch' { mkJSAnnot $1 }
+
+FinallyL :: { AST.JSAnnot }
+FinallyL : 'finally' { mkJSAnnot $1 }
+
+Function :: { AST.JSAnnot }
+Function : 'function' { mkJSAnnot $1 {- 'Function' -} }
+
+New :: { AST.JSAnnot }
+New : 'new' { mkJSAnnot $1 }
+
+Class :: { AST.JSAnnot }
+Class : 'class' { mkJSAnnot $1 }
+
+Extends :: { AST.JSAnnot }
+Extends : 'extends' { mkJSAnnot $1 }
+
+Static :: { AST.JSAnnot }
+Static : 'static' { mkJSAnnot $1 }
+
+Super :: { AST.JSExpression }
+Super : 'super' { AST.JSLiteral (mkJSAnnot $1) "super" }
+
+
+Eof :: { AST.JSAnnot }
+Eof : 'tail' { mkJSAnnot $1 {- 'Eof' -} }
+
+-- Literal :: See 7.8
+-- NullLiteral
+-- BooleanLiteral
+-- NumericLiteral
+-- StringLiteral
+Literal :: { AST.JSExpression }
+Literal : NullLiteral { $1 }
+ | BooleanLiteral { $1 }
+ | NumericLiteral { $1 }
+ | StringLiteral { $1 }
+ | RegularExpressionLiteral { $1 }
+
+NullLiteral :: { AST.JSExpression }
+NullLiteral : 'null' { AST.JSLiteral (mkJSAnnot $1) "null" }
+
+BooleanLiteral :: { AST.JSExpression }
+BooleanLiteral : 'true' { AST.JSLiteral (mkJSAnnot $1) "true" }
+ | 'false' { AST.JSLiteral (mkJSAnnot $1) "false" }
+
+-- <Numeric Literal> ::= DecimalLiteral
+-- | HexIntegerLiteral
+-- | OctalLiteral
+NumericLiteral :: { AST.JSExpression }
+NumericLiteral : 'decimal' { AST.JSDecimal (mkJSAnnot $1) (tokenLiteral $1) }
+ | 'hexinteger' { AST.JSHexInteger (mkJSAnnot $1) (tokenLiteral $1) }
+ | 'octal' { AST.JSOctal (mkJSAnnot $1) (tokenLiteral $1) }
+
+StringLiteral :: { AST.JSExpression }
+StringLiteral : 'string' { AST.JSStringLiteral (mkJSAnnot $1) (tokenLiteral $1) }
+
+-- <Regular Expression Literal> ::= RegExp
+RegularExpressionLiteral :: { AST.JSExpression }
+RegularExpressionLiteral : 'regex' { AST.JSRegEx (mkJSAnnot $1) (tokenLiteral $1) }
+
+-- PrimaryExpression : See 11.1
+-- this
+-- Identifier
+-- Literal
+-- ArrayLiteral
+-- ObjectLiteral
+-- ( Expression )
+PrimaryExpression :: { AST.JSExpression }
+PrimaryExpression : 'this' { AST.JSLiteral (mkJSAnnot $1) "this" }
+ | Identifier { $1 {- 'PrimaryExpression1' -} }
+ | Literal { $1 {- 'PrimaryExpression2' -} }
+ | ArrayLiteral { $1 {- 'PrimaryExpression3' -} }
+ | ObjectLiteral { $1 {- 'PrimaryExpression4' -} }
+ | ClassExpression { $1 }
+ | GeneratorExpression { $1 }
+ | TemplateLiteral { mkJSTemplateLiteral Nothing $1 {- 'PrimaryExpression6' -} }
+ | LParen Expression RParen { AST.JSExpressionParen $1 $2 $3 }
+
+-- Identifier :: See 7.6
+-- IdentifierName but not ReservedWord
+Identifier :: { AST.JSExpression }
+Identifier : 'ident' { AST.JSIdentifier (mkJSAnnot $1) (tokenLiteral $1) }
+ | 'as' { AST.JSIdentifier (mkJSAnnot $1) "as" }
+ | 'get' { AST.JSIdentifier (mkJSAnnot $1) "get" }
+ | 'set' { AST.JSIdentifier (mkJSAnnot $1) "set" }
+ | 'from' { AST.JSIdentifier (mkJSAnnot $1) "from" }
+ | 'yield' { AST.JSIdentifier (mkJSAnnot $1) "yield" }
+
+-- Must follow Identifier; when ambiguous, `yield` as a keyword should take
+-- precedence over `yield` as an identifier name.
+Yield :: { AST.JSAnnot }
+Yield : 'yield' { mkJSAnnot $1 }
+
+
+SpreadExpression :: { AST.JSExpression }
+SpreadExpression : Spread AssignmentExpression { AST.JSSpreadExpression $1 $2 {- 'SpreadExpression' -} }
+
+TemplateLiteral :: { JSUntaggedTemplate }
+TemplateLiteral : 'tmplnosub' { JSUntaggedTemplate (mkJSAnnot $1) (tokenLiteral $1) [] }
+ | 'tmplhead' TemplateParts { JSUntaggedTemplate (mkJSAnnot $1) (tokenLiteral $1) $2 }
+
+TemplateParts :: { [AST.JSTemplatePart] }
+TemplateParts : TemplateExpression RBrace 'tmplmiddle' TemplateParts { AST.JSTemplatePart $1 $2 ('}' : tokenLiteral $3) : $4 }
+ | TemplateExpression RBrace 'tmpltail' { AST.JSTemplatePart $1 $2 ('}' : tokenLiteral $3) : [] }
+
+-- This production only exists to ensure that inTemplate is set to True before
+-- a tmplmiddle or tmpltail token is lexed. Since the lexer is always one token
+-- ahead of the parser, setInTemplate needs to be called during a reduction
+-- that is *two* tokens behind tmplmiddle/tmpltail. Accordingly,
+-- TemplateExpression is always followed by an RBrace, which is lexed normally.
+TemplateExpression :: { AST.JSExpression }
+TemplateExpression : Expression {% setInTemplate True \$> $1 }
+
+-- ArrayLiteral : See 11.1.4
+-- [ Elisionopt ]
+-- [ ElementList ]
+-- [ ElementList , Elisionopt ]
+ArrayLiteral :: { AST.JSExpression }
+ArrayLiteral : LSquare RSquare { AST.JSArrayLiteral $1 [] $2 {- 'ArrayLiteral11' -} }
+ | LSquare Elision RSquare { AST.JSArrayLiteral $1 $2 $3 {- 'ArrayLiteral12' -} }
+ | LSquare ElementList RSquare { AST.JSArrayLiteral $1 $2 $3 {- 'ArrayLiteral13' -} }
+ | LSquare ElementList Elision RSquare { AST.JSArrayLiteral $1 ($2 ++ $3) $4 {- 'ArrayLiteral14' -} }
+
+
+-- ElementList : See 11.1.4
+-- Elisionopt AssignmentExpression
+-- ElementList , Elisionopt AssignmentExpression
+ElementList :: { [AST.JSArrayElement] }
+ElementList : Elision AssignmentExpression { $1 ++ [AST.JSArrayElement $2] {- 'ElementList1' -} }
+ | AssignmentExpression { [AST.JSArrayElement $1] {- 'ElementList2' -} }
+ | ElementList Elision AssignmentExpression { (($1)++($2 ++ [AST.JSArrayElement $3])) {- 'ElementList3' -} }
+
+
+-- Elision : See 11.1.4
+-- ,
+-- Elision ,
+Elision :: { [AST.JSArrayElement] }
+Elision : Comma { [AST.JSArrayComma $1] {- 'Elision1' -} }
+ | Comma Elision { (AST.JSArrayComma $1):$2 {- 'Elision2' -} }
+
+-- ObjectLiteral : See 11.1.5
+-- { }
+-- { PropertyNameAndValueList }
+-- { PropertyNameAndValueList , }
+ObjectLiteral :: { AST.JSExpression }
+ObjectLiteral : LBrace RBrace { AST.JSObjectLiteral $1 (AST.JSCTLNone AST.JSLNil) $2 {- 'ObjectLiteral1' -} }
+ | LBrace PropertyNameandValueList RBrace { AST.JSObjectLiteral $1 (AST.JSCTLNone $2) $3 {- 'ObjectLiteral2' -} }
+ | LBrace PropertyNameandValueList Comma RBrace { AST.JSObjectLiteral $1 (AST.JSCTLComma $2 $3) $4 {- 'ObjectLiteral3' -} }
+
+-- <Property Name and Value List> ::= <Property Name> ':' <Assignment Expression>
+-- | <Property Name and Value List> ',' <Property Name> ':' <Assignment Expression>
+
+-- Seems we can have function declarations in the value part too
+-- PropertyNameAndValueList : See 11.1.5
+-- PropertyAssignment
+-- PropertyNameAndValueList , PropertyAssignment
+PropertyNameandValueList :: { AST.JSCommaList AST.JSObjectProperty }
+PropertyNameandValueList : PropertyAssignment { AST.JSLOne $1 {- 'PropertyNameandValueList1' -} }
+ | PropertyNameandValueList Comma PropertyAssignment { AST.JSLCons $1 $2 $3 {- 'PropertyNameandValueList2' -} }
+
+-- PropertyAssignment : See 11.1.5
+-- PropertyName : AssignmentExpression
+-- get PropertyName() { FunctionBody }
+-- set PropertyName( PropertySetParameterList ) { FunctionBody }
+PropertyAssignment :: { AST.JSObjectProperty }
+PropertyAssignment : PropertyName Colon AssignmentExpression { AST.JSPropertyNameandValue $1 $2 [$3] }
+ | IdentifierName { identifierToProperty $1 }
+ | MethodDefinition { AST.JSObjectMethod $1 }
+
+-- TODO: not clear if get/set are keywords, or just used in a specific context. Puzzling.
+MethodDefinition :: { AST.JSMethodDefinition }
+MethodDefinition : PropertyName LParen RParen FunctionBody
+ { AST.JSMethodDefinition $1 $2 AST.JSLNil $3 $4 }
+ | PropertyName LParen FormalParameterList RParen FunctionBody
+ { AST.JSMethodDefinition $1 $2 $3 $4 $5 }
+ | '*' PropertyName LParen RParen FunctionBody
+ { AST.JSGeneratorMethodDefinition (mkJSAnnot $1) $2 $3 AST.JSLNil $4 $5 }
+ | '*' PropertyName LParen FormalParameterList RParen FunctionBody
+ { AST.JSGeneratorMethodDefinition (mkJSAnnot $1) $2 $3 $4 $5 $6 }
+ -- Should be "get" in next, but is not a Token
+ | 'get' PropertyName LParen RParen FunctionBody
+ { AST.JSPropertyAccessor (AST.JSAccessorGet (mkJSAnnot $1)) $2 $3 AST.JSLNil $4 $5 }
+ -- Should be "set" in next, but is not a Token
+ | 'set' PropertyName LParen PropertySetParameterList RParen FunctionBody
+ { AST.JSPropertyAccessor (AST.JSAccessorSet (mkJSAnnot $1)) $2 $3 (AST.JSLOne $4) $5 $6 }
+
+-- PropertyName : See 11.1.5
+-- IdentifierName
+-- StringLiteral
+-- NumericLiteral
+PropertyName :: { AST.JSPropertyName }
+PropertyName : IdentifierName { propName $1 {- 'PropertyName1' -} }
+ | StringLiteral { propName $1 {- 'PropertyName2' -} }
+ | NumericLiteral { propName $1 {- 'PropertyName3' -} }
+ | LSquare AssignmentExpression RSquare { AST.JSPropertyComputed $1 $2 $3 {- 'PropertyName4' -} }
+
+-- PropertySetParameterList : See 11.1.5
+-- Identifier
+PropertySetParameterList :: { AST.JSExpression }
+PropertySetParameterList : AssignmentExpression { $1 {- 'PropertySetParameterList' -} }
+
+-- MemberExpression : See 11.2
+-- PrimaryExpression
+-- FunctionExpression
+-- MemberExpression [ Expression ]
+-- MemberExpression . IdentifierName
+-- new MemberExpression Arguments
+MemberExpression :: { AST.JSExpression }
+MemberExpression : PrimaryExpression { $1 {- 'MemberExpression1' -} }
+ | FunctionExpression { $1 {- 'MemberExpression2' -} }
+ | MemberExpression LSquare Expression RSquare { AST.JSMemberSquare $1 $2 $3 $4 {- 'MemberExpression3' -} }
+ | MemberExpression Dot IdentifierName { AST.JSMemberDot $1 $2 $3 {- 'MemberExpression4' -} }
+ | MemberExpression TemplateLiteral { mkJSTemplateLiteral (Just $1) $2 }
+ | Super LSquare Expression RSquare { AST.JSMemberSquare $1 $2 $3 $4 }
+ | Super Dot IdentifierName { AST.JSMemberDot $1 $2 $3 }
+ | New MemberExpression Arguments { mkJSMemberNew $1 $2 $3 {- 'MemberExpression5' -} }
+
+-- NewExpression : See 11.2
+-- MemberExpression
+-- new NewExpression
+NewExpression :: { AST.JSExpression }
+NewExpression : MemberExpression { $1 {- 'NewExpression1' -} }
+ | New NewExpression { AST.JSNewExpression $1 $2 {- 'NewExpression2' -} }
+
+AwaitExpression :: { AST.JSExpression }
+AwaitExpression
+ : Await Expression { AST.JSAwaitExpression $1 $2 }
+
+-- CallExpression : See 11.2
+-- MemberExpression Arguments
+-- CallExpression Arguments
+-- CallExpression [ Expression ]
+-- CallExpression . IdentifierName
+CallExpression :: { AST.JSExpression }
+CallExpression : MemberExpression Arguments
+ { mkJSMemberExpression $1 $2 {- 'CallExpression1' -} }
+ | Super Arguments
+ { mkJSCallExpression $1 $2 }
+ | CallExpression Arguments
+ { mkJSCallExpression $1 $2 {- 'CallExpression2' -} }
+ | CallExpression LSquare Expression RSquare
+ { AST.JSCallExpressionSquare $1 $2 $3 $4 {- 'CallExpression3' -} }
+ | CallExpression Dot IdentifierName
+ { AST.JSCallExpressionDot $1 $2 $3 {- 'CallExpression4' -} }
+ | CallExpression TemplateLiteral
+ { mkJSTemplateLiteral (Just $1) $2 {- 'CallExpression5' -} }
+
+-- Arguments : See 11.2
+-- ()
+-- ( ArgumentList )
+Arguments :: { JSArguments }
+Arguments : LParen RParen { JSArguments $1 AST.JSLNil $2 {- 'Arguments1' -} }
+ | LParen ArgumentList RParen { JSArguments $1 $2 $3 {- 'Arguments2' -} }
+
+-- ArgumentList : See 11.2
+-- AssignmentExpression
+-- ArgumentList , AssignmentExpression
+ArgumentList :: { AST.JSCommaList AST.JSExpression }
+ArgumentList : AssignmentExpression { AST.JSLOne $1 {- 'ArgumentList1' -} }
+ | ArgumentList Comma AssignmentExpression { AST.JSLCons $1 $2 $3 {- 'ArgumentList2' -} }
+
+-- LeftHandSideExpression : See 11.2
+-- NewExpression
+-- CallExpression
+LeftHandSideExpression :: { AST.JSExpression }
+LeftHandSideExpression : NewExpression { $1 {- 'LeftHandSideExpression1' -} }
+ | CallExpression { $1 {- 'LeftHandSideExpression12' -} }
+ | AwaitExpression { $1 {- 'LeftHandSideExpression13' -} }
+
+-- PostfixExpression : See 11.3
+-- LeftHandSideExpression
+-- [no LineTerminator here]
+-- LeftHandSideExpression ++
+-- [no LineTerminator here]
+-- LeftHandSideExpression --
+PostfixExpression :: { AST.JSExpression }
+PostfixExpression : LeftHandSideExpression { $1 {- 'PostfixExpression' -} }
+ | PostfixExpression Increment { AST.JSExpressionPostfix $1 $2 }
+ | PostfixExpression Decrement { AST.JSExpressionPostfix $1 $2 }
+
+-- UnaryExpression : See 11.4
+-- PostfixExpression
+-- delete UnaryExpression
+-- void UnaryExpression
+-- typeof UnaryExpression
+-- ++ UnaryExpression
+-- -- UnaryExpression
+-- + UnaryExpression
+-- - UnaryExpression
+-- ~ UnaryExpression
+-- ! UnaryExpression
+UnaryExpression :: { AST.JSExpression }
+UnaryExpression : PostfixExpression { $1 {- 'UnaryExpression' -} }
+ | Delete UnaryExpression { AST.JSUnaryExpression $1 $2 }
+ | Void UnaryExpression { AST.JSUnaryExpression $1 $2 }
+ | Typeof UnaryExpression { AST.JSUnaryExpression $1 $2 }
+ | Increment UnaryExpression { AST.JSUnaryExpression $1 $2 }
+ | Decrement UnaryExpression { AST.JSUnaryExpression $1 $2 }
+ | Plus UnaryExpression { AST.JSUnaryExpression (mkUnary $1) $2 }
+ | Minus UnaryExpression { AST.JSUnaryExpression (mkUnary $1) $2 }
+ | Tilde UnaryExpression { AST.JSUnaryExpression $1 $2 }
+ | Not UnaryExpression { AST.JSUnaryExpression $1 $2 }
+
+-- MultiplicativeExpression : See 11.5
+-- UnaryExpression
+-- MultiplicativeExpression * UnaryExpression
+-- MultiplicativeExpression / UnaryExpression
+-- MultiplicativeExpression % UnaryExpression
+MultiplicativeExpression :: { AST.JSExpression }
+MultiplicativeExpression : UnaryExpression { $1 {- 'MultiplicativeExpression' -} }
+ | MultiplicativeExpression Mul UnaryExpression { AST.JSExpressionBinary {- '*' -} $1 $2 $3 }
+ | MultiplicativeExpression Div UnaryExpression { AST.JSExpressionBinary {- '/' -} $1 $2 $3 }
+ | MultiplicativeExpression Mod UnaryExpression { AST.JSExpressionBinary {- '%' -} $1 $2 $3 }
+
+-- AdditiveExpression : See 11.6
+-- MultiplicativeExpression
+-- AdditiveExpression + MultiplicativeExpression
+-- AdditiveExpression - MultiplicativeExpression
+AdditiveExpression :: { AST.JSExpression }
+AdditiveExpression : AdditiveExpression Plus MultiplicativeExpression { AST.JSExpressionBinary {- '+' -} $1 $2 $3 }
+ | AdditiveExpression Minus MultiplicativeExpression { AST.JSExpressionBinary {- '-' -} $1 $2 $3 }
+ | MultiplicativeExpression { $1 {- 'AdditiveExpression' -} }
+
+-- ShiftExpression : See 11.7
+-- AdditiveExpression
+-- ShiftExpression << AdditiveExpression
+-- ShiftExpression >> AdditiveExpression
+-- ShiftExpression >>> AdditiveExpression
+ShiftExpression :: { AST.JSExpression }
+ShiftExpression : ShiftExpression Lsh AdditiveExpression { AST.JSExpressionBinary {- '<<' -} $1 $2 $3 }
+ | ShiftExpression Rsh AdditiveExpression { AST.JSExpressionBinary {- '>>' -} $1 $2 $3 }
+ | ShiftExpression Ursh AdditiveExpression { AST.JSExpressionBinary {- '>>>' -} $1 $2 $3 }
+ | AdditiveExpression { $1 {- 'ShiftExpression' -} }
+
+-- RelationalExpression : See 11.8
+-- ShiftExpression
+-- RelationalExpression < ShiftExpression
+-- RelationalExpression > ShiftExpression
+-- RelationalExpression <= ShiftExpression
+-- RelationalExpression >= ShiftExpression
+-- RelationalExpression instanceof ShiftExpression
+-- RelationalExpression in ShiftExpression
+RelationalExpression :: { AST.JSExpression }
+RelationalExpression : ShiftExpression { $1 {- 'RelationalExpression' -} }
+ | RelationalExpression Lt ShiftExpression { AST.JSExpressionBinary {- '<' -} $1 $2 $3 }
+ | RelationalExpression Gt ShiftExpression { AST.JSExpressionBinary {- '>' -} $1 $2 $3 }
+ | RelationalExpression Le ShiftExpression { AST.JSExpressionBinary {- '<=' -} $1 $2 $3 }
+ | RelationalExpression Ge ShiftExpression { AST.JSExpressionBinary {- '>=' -} $1 $2 $3 }
+ | RelationalExpression Instanceof ShiftExpression { AST.JSExpressionBinary {- ' instanceof' -} $1 $2 $3 }
+ | RelationalExpression In ShiftExpression { AST.JSExpressionBinary {- ' in ' -} $1 $2 $3 }
+
+-- RelationalExpressionNoIn : See 11.8
+-- ShiftExpression
+-- RelationalExpressionNoIn < ShiftExpression
+-- RelationalExpressionNoIn > ShiftExpression
+-- RelationalExpressionNoIn <= ShiftExpression
+-- RelationalExpressionNoIn >= ShiftExpression
+-- RelationalExpressionNoIn instanceof ShiftExpression
+RelationalExpressionNoIn :: { AST.JSExpression }
+RelationalExpressionNoIn : ShiftExpression { $1 {- 'RelationalExpressionNoIn' -} }
+ | RelationalExpressionNoIn Lt ShiftExpression { AST.JSExpressionBinary {- '<' -} $1 $2 $3 }
+ | RelationalExpressionNoIn Gt ShiftExpression { AST.JSExpressionBinary {- '>' -} $1 $2 $3 }
+ | RelationalExpressionNoIn Le ShiftExpression { AST.JSExpressionBinary {- '<=' -} $1 $2 $3 }
+ | RelationalExpressionNoIn Ge ShiftExpression { AST.JSExpressionBinary {- '>=' -} $1 $2 $3 }
+ | RelationalExpressionNoIn Instanceof ShiftExpression { AST.JSExpressionBinary {- ' instanceof ' -} $1 $2 $3 }
+
+-- EqualityExpression : See 11.9
+-- RelationalExpression
+-- EqualityExpression == RelationalExpression
+-- EqualityExpression != RelationalExpression
+-- EqualityExpression === RelationalExpression
+-- EqualityExpression !== RelationalExpression
+EqualityExpression :: { AST.JSExpression }
+EqualityExpression : RelationalExpression { $1 {- 'EqualityExpression' -} }
+ | EqualityExpression Equal RelationalExpression { AST.JSExpressionBinary {- '==' -} $1 $2 $3 }
+ | EqualityExpression Ne RelationalExpression { AST.JSExpressionBinary {- '!=' -} $1 $2 $3 }
+ | EqualityExpression StrictEq RelationalExpression { AST.JSExpressionBinary {- '===' -} $1 $2 $3 }
+ | EqualityExpression StrictNe RelationalExpression { AST.JSExpressionBinary {- '!==' -} $1 $2 $3 }
+
+-- EqualityExpressionNoIn : See 11.9
+-- RelationalExpressionNoIn
+-- EqualityExpressionNoIn == RelationalExpressionNoIn
+-- EqualityExpressionNoIn != RelationalExpressionNoIn
+-- EqualityExpressionNoIn === RelationalExpressionNoIn
+-- EqualityExpressionNoIn !== RelationalExpressionNoIn
+EqualityExpressionNoIn :: { AST.JSExpression }
+EqualityExpressionNoIn : RelationalExpressionNoIn { $1 {- 'EqualityExpressionNoIn' -} }
+ | EqualityExpressionNoIn Equal RelationalExpression { AST.JSExpressionBinary {- '==' -} $1 $2 $3 }
+ | EqualityExpressionNoIn Ne RelationalExpression { AST.JSExpressionBinary {- '!=' -} $1 $2 $3 }
+ | EqualityExpressionNoIn StrictEq RelationalExpression { AST.JSExpressionBinary {- '===' -} $1 $2 $3 }
+ | EqualityExpressionNoIn StrictNe RelationalExpression { AST.JSExpressionBinary {- '!==' -} $1 $2 $3 }
+
+-- BitwiseANDExpression : See 11.10
+-- EqualityExpression
+-- BitwiseANDExpression & EqualityExpression
+BitwiseAndExpression :: { AST.JSExpression }
+BitwiseAndExpression : EqualityExpression { $1 {- 'BitwiseAndExpression' -} }
+ | BitwiseAndExpression BitAnd EqualityExpression { AST.JSExpressionBinary {- '&' -} $1 $2 $3 }
+
+-- BitwiseANDExpressionNoIn : See 11.10
+-- EqualityExpressionNoIn
+-- BitwiseANDExpressionNoIn & EqualityExpressionNoIn
+BitwiseAndExpressionNoIn :: { AST.JSExpression }
+BitwiseAndExpressionNoIn : EqualityExpressionNoIn { $1 {- 'BitwiseAndExpression' -} }
+ | BitwiseAndExpressionNoIn BitAnd EqualityExpressionNoIn { AST.JSExpressionBinary {- '&' -} $1 $2 $3 }
+
+-- BitwiseXORExpression : See 11.10
+-- BitwiseANDExpression
+-- BitwiseXORExpression ^ BitwiseANDExpression
+BitwiseXOrExpression :: { AST.JSExpression }
+BitwiseXOrExpression : BitwiseAndExpression { $1 {- 'BitwiseXOrExpression' -} }
+ | BitwiseXOrExpression BitXor BitwiseAndExpression { AST.JSExpressionBinary {- '^' -} $1 $2 $3 }
+
+-- BitwiseXORExpressionNoIn : See 11.10
+-- BitwiseANDExpressionNoIn
+-- BitwiseXORExpressionNoIn ^ BitwiseANDExpressionNoIn
+BitwiseXOrExpressionNoIn :: { AST.JSExpression }
+BitwiseXOrExpressionNoIn : BitwiseAndExpressionNoIn { $1 {- 'BitwiseXOrExpression' -} }
+ | BitwiseXOrExpressionNoIn BitXor BitwiseAndExpressionNoIn { AST.JSExpressionBinary {- '^' -} $1 $2 $3 }
+
+-- BitwiseORExpression : See 11.10
+-- BitwiseXORExpression
+-- BitwiseORExpression | BitwiseXORExpression
+BitwiseOrExpression :: { AST.JSExpression }
+BitwiseOrExpression : BitwiseXOrExpression { $1 {- 'BitwiseOrExpression' -} }
+ | BitwiseOrExpression BitOr BitwiseXOrExpression { AST.JSExpressionBinary {- '|' -} $1 $2 $3 }
+
+-- BitwiseORExpressionNoIn : See 11.10
+-- BitwiseXORExpressionNoIn
+-- BitwiseORExpressionNoIn | BitwiseXORExpressionNoIn
+BitwiseOrExpressionNoIn :: { AST.JSExpression }
+BitwiseOrExpressionNoIn : BitwiseXOrExpressionNoIn { $1 {- 'BitwiseOrExpression' -} }
+ | BitwiseOrExpressionNoIn BitOr BitwiseXOrExpressionNoIn { AST.JSExpressionBinary {- '|' -} $1 $2 $3 }
+
+-- LogicalANDExpression : See 11.11
+-- BitwiseORExpression
+-- LogicalANDExpression && BitwiseORExpression
+LogicalAndExpression :: { AST.JSExpression }
+LogicalAndExpression : BitwiseOrExpression { $1 {- 'LogicalAndExpression' -} }
+ | LogicalAndExpression And BitwiseOrExpression { AST.JSExpressionBinary {- '&&' -} $1 $2 $3 }
+
+-- LogicalANDExpressionNoIn : See 11.11
+-- BitwiseORExpressionNoIn
+-- LogicalANDExpressionNoIn && BitwiseORExpressionNoIn
+LogicalAndExpressionNoIn :: { AST.JSExpression }
+LogicalAndExpressionNoIn : BitwiseOrExpressionNoIn { $1 {- 'LogicalAndExpression' -} }
+ | LogicalAndExpressionNoIn And BitwiseOrExpressionNoIn { AST.JSExpressionBinary {- '&&' -} $1 $2 $3 }
+
+-- LogicalORExpression : See 11.11
+-- LogicalANDExpression
+-- LogicalORExpression || LogicalANDExpression
+LogicalOrExpression :: { AST.JSExpression }
+LogicalOrExpression : LogicalAndExpression { $1 {- 'LogicalOrExpression' -} }
+ | LogicalOrExpression Or LogicalAndExpression { AST.JSExpressionBinary {- '||' -} $1 $2 $3 }
+
+-- LogicalORExpressionNoIn : See 11.11
+-- LogicalANDExpressionNoIn
+-- LogicalORExpressionNoIn || LogicalANDExpressionNoIn
+LogicalOrExpressionNoIn :: { AST.JSExpression }
+LogicalOrExpressionNoIn : LogicalAndExpressionNoIn { $1 {- 'LogicalOrExpression' -} }
+ | LogicalOrExpressionNoIn Or LogicalAndExpressionNoIn { AST.JSExpressionBinary {- '||' -} $1 $2 $3 }
+
+-- ConditionalExpression : See 11.12
+-- LogicalORExpression
+-- LogicalORExpression ? AssignmentExpression : AssignmentExpression
+ConditionalExpression :: { AST.JSExpression }
+ConditionalExpression : LogicalOrExpression { $1 {- 'ConditionalExpression1' -} }
+ | LogicalOrExpression Hook AssignmentExpression Colon AssignmentExpression
+ { AST.JSExpressionTernary $1 $2 $3 $4 $5 {- 'ConditionalExpression2' -} }
+
+-- ConditionalExpressionNoIn : See 11.12
+-- LogicalORExpressionNoIn
+-- LogicalORExpressionNoIn ? AssignmentExpressionNoIn : AssignmentExpressionNoIn
+ConditionalExpressionNoIn :: { AST.JSExpression }
+ConditionalExpressionNoIn : LogicalOrExpressionNoIn { $1 {- 'ConditionalExpressionNoIn1' -} }
+ | LogicalOrExpressionNoIn Hook AssignmentExpressionNoIn Colon AssignmentExpressionNoIn
+ { AST.JSExpressionTernary $1 $2 $3 $4 $5 {- 'ConditionalExpressionNoIn2' -} }
+
+-- AssignmentExpression : See 11.13
+-- ConditionalExpression
+-- LeftHandSideExpression AssignmentOperator AssignmentExpression
+AssignmentExpression :: { AST.JSExpression }
+AssignmentExpression : ConditionalExpression { $1 {- 'AssignmentExpression1' -} }
+ | YieldExpression { $1 }
+ | LeftHandSideExpression AssignmentOperator AssignmentExpression
+ { AST.JSAssignExpression $1 $2 $3 {- 'AssignmentExpression2' -} }
+ | SpreadExpression { $1 }
+
+-- AssignmentExpressionNoIn : See 11.13
+-- ConditionalExpressionNoIn
+-- LeftHandSideExpression AssignmentOperator AssignmentExpressionNoIn
+AssignmentExpressionNoIn :: { AST.JSExpression }
+AssignmentExpressionNoIn : ConditionalExpressionNoIn { $1 {- 'AssignmentExpressionNoIn1' -} }
+ | YieldExpression { $1 }
+ | LeftHandSideExpression AssignmentOperator AssignmentExpressionNoIn
+ { AST.JSAssignExpression $1 $2 $3 {- 'AssignmentExpressionNoIn1' -} }
+
+-- AssignmentOperator : one of See 11.13
+-- '=' | '*=' | '/=' | '%=' | '+=' | '-=' | '<<=' | '>>=' | '>>>=' | '&=' | '^=' | '|='
+AssignmentOperator :: { AST.JSAssignOp }
+AssignmentOperator : OpAssign { $1 }
+ | SimpleAssign { AST.JSAssign $1 {- 'SimpleAssign' -} }
+
+-- Expression : See 11.14
+-- AssignmentExpression
+-- Expression , AssignmentExpression
+Expression :: { AST.JSExpression }
+Expression : AssignmentExpression { $1 {- 'Expression' -} }
+ | Expression Comma AssignmentExpression { AST.JSCommaExpression $1 $2 $3 {- 'Expression2' -} }
+
+-- ExpressionNoIn : See 11.14
+-- AssignmentExpressionNoIn
+-- ExpressionNoIn , AssignmentExpressionNoIn
+ExpressionNoIn :: { AST.JSExpression }
+ExpressionNoIn : AssignmentExpressionNoIn { $1 {- 'ExpressionNoIn' -} }
+ | ExpressionNoIn Comma AssignmentExpressionNoIn { AST.JSCommaExpression $1 $2 $3 {- 'ExpressionNoIn2' -} }
+
+-- TODO: still required?
+ExpressionOpt :: { AST.JSCommaList AST.JSExpression }
+ExpressionOpt : Expression { AST.JSLOne $1 {- 'ExpressionOpt1' -} }
+ | { AST.JSLNil {- 'ExpressionOpt2' -} }
+
+ExpressionNoInOpt :: { AST.JSCommaList AST.JSExpression }
+ExpressionNoInOpt : ExpressionNoIn { AST.JSLOne $1 {- 'ExpressionOpt1' -} }
+ | { AST.JSLNil {- 'ExpressionOpt2' -} }
+
+
+-- Statement : See clause 12
+-- Block
+-- VariableStatement
+-- EmptyStatement
+-- ExpressionStatement
+-- IfStatement
+-- IterationStatement
+-- ContinueStatement
+-- BreakStatement
+-- ReturnStatement
+-- WithStatement
+-- LabelledStatement
+-- SwitchStatement
+-- ThrowStatement
+-- TryStatement
+-- DebuggerStatement
+Statement :: { AST.JSStatement }
+Statement : StatementNoEmpty { $1 {- 'Statement1' -} }
+ | EmptyStatement { $1 {- 'Statement2' -} }
+
+StatementNoEmpty :: { AST.JSStatement }
+StatementNoEmpty
+ : IfStatement { $1 {- 'StatementNoEmpty5' -} }
+ | ContinueStatement { $1 {- 'StatementNoEmpty7' -} }
+ | BreakStatement { $1 {- 'StatementNoEmpty8' -} }
+ | ReturnStatement { $1 {- 'StatementNoEmpty9' -} }
+ | WithStatement { $1 {- 'StatementNoEmpty10' -} }
+ | LabelledStatement { $1 {- 'StatementNoEmpty11' -} }
+ | SwitchStatement { $1 {- 'StatementNoEmpty12' -} }
+ | ThrowStatement { $1 {- 'StatementNoEmpty13' -} }
+ | TryStatement { $1 {- 'StatementNoEmpty14' -} }
+ | StatementBlock { $1 {- 'StatementNoEmpty1' -} }
+ | VariableStatement { $1 {- 'StatementNoEmpty2' -} }
+ | IterationStatement { $1 {- 'StatementNoEmpty6' -} }
+ | ExpressionStatement { $1 {- 'StatementNoEmpty4' -} }
+ | AsyncFunctionStatement { $1 {- 'StatementNoEmpty15' -} }
+ | DebuggerStatement { $1 {- 'StatementNoEmpty15' -} }
+
+
+
+StatementBlock :: { AST.JSStatement }
+StatementBlock : Block MaybeSemi { blockToStatement $1 $2 {- 'StatementBlock1' -} }
+
+
+-- Block : See 12.1
+-- { StatementListopt }
+Block :: { AST.JSBlock }
+Block : LBrace RBrace { AST.JSBlock $1 [] $2 {- 'Block1' -} }
+ | LBrace StatementList RBrace { AST.JSBlock $1 $2 $3 {- 'Block2' -} }
+
+-- StatementList : See 12.1
+-- Statement
+-- StatementList Statement
+StatementList :: { [AST.JSStatement] }
+StatementList : Statement { [$1] {- 'StatementList1' -} }
+ | StatementList Statement { ($1++[$2]) {- 'StatementList2' -} }
+
+-- VariableStatement : See 12.2
+-- var VariableDeclarationList ;
+VariableStatement :: { AST.JSStatement }
+VariableStatement : Var VariableDeclarationList MaybeSemi { AST.JSVariable $1 $2 $3 {- 'VariableStatement1' -} }
+ | Let VariableDeclarationList MaybeSemi { AST.JSLet $1 $2 $3 {- 'VariableStatement2' -} }
+ | Const VariableDeclarationList MaybeSemi { AST.JSConstant $1 $2 $3 {- 'VariableStatement3' -} }
+
+-- VariableDeclarationList : See 12.2
+-- VariableDeclaration
+-- VariableDeclarationList , VariableDeclaration
+VariableDeclarationList :: { AST.JSCommaList AST.JSExpression }
+VariableDeclarationList : VariableDeclaration { AST.JSLOne $1 {- 'VariableDeclarationList1' -} }
+ | VariableDeclarationList Comma VariableDeclaration { AST.JSLCons $1 $2 $3 {- 'VariableDeclarationList2' -} }
+
+-- VariableDeclarationListNoIn : See 12.2
+-- VariableDeclarationNoIn
+-- VariableDeclarationListNoIn , VariableDeclarationNoIn
+VariableDeclarationListNoIn :: { AST.JSCommaList AST.JSExpression }
+VariableDeclarationListNoIn : VariableDeclarationNoIn { AST.JSLOne $1 {- 'VariableDeclarationListNoIn1' -} }
+ | VariableDeclarationListNoIn Comma VariableDeclarationNoIn { AST.JSLCons $1 $2 $3 {- 'VariableDeclarationListNoIn2' -} }
+
+-- VariableDeclaration : See 12.2
+-- Identifier Initialiseropt
+VariableDeclaration :: { AST.JSExpression }
+VariableDeclaration : PrimaryExpression SimpleAssign AssignmentExpression { AST.JSVarInitExpression $1 (AST.JSVarInit $2 $3) {- 'JSVarInitExpression1' -} }
+ | Identifier { AST.JSVarInitExpression $1 AST.JSVarInitNone {- 'JSVarInitExpression2' -} }
+
+-- VariableDeclarationNoIn : See 12.2
+-- Identifier InitialiserNoInopt
+VariableDeclarationNoIn :: { AST.JSExpression }
+VariableDeclarationNoIn : PrimaryExpression SimpleAssign AssignmentExpression { AST.JSVarInitExpression $1 (AST.JSVarInit $2 $3) {- 'JSVarInitExpressionInit2' -} }
+ | Identifier { AST.JSVarInitExpression $1 AST.JSVarInitNone {- 'JSVarInitExpression2' -} }
+
+-- EmptyStatement : See 12.3
+-- ;
+EmptyStatement :: { AST.JSStatement }
+EmptyStatement : Semi { AST.JSEmptyStatement $1 {- 'EmptyStatement' -} }
+
+-- ExpressionStatement : See 12.4
+-- [lookahead not in {{, function}] Expression ;
+-- TODO: Sort out lookahead issue. Maybe by just putting production lower to set reduce/reduce conflict
+-- According to http://sideshowbarker.github.com/es5-spec/#x12.4, the ambiguity is with
+-- Block or FunctionDeclaration
+ExpressionStatement :: { AST.JSStatement }
+ExpressionStatement : Expression MaybeSemi { expressionToStatement $1 $2 {- 'ExpressionStatement' -} }
+
+
+-- IfStatement : See 12.5
+-- if ( Expression ) Statement else Statement
+-- if ( Expression ) Statement
+IfStatement :: { AST.JSStatement } -- +++XXXX++
+IfStatement : If LParen Expression RParen EmptyStatement
+ { AST.JSIf $1 $2 $3 $4 $5 {- 'IfStatement1' -} }
+ | If LParen Expression RParen StatementNoEmpty Else Statement
+ { AST.JSIfElse $1 $2 $3 $4 $5 $6 $7 {- 'IfStatement3' -} }
+ | If LParen Expression RParen StatementNoEmpty
+ { AST.JSIf $1 $2 $3 $4 $5 {- 'IfStatement3' -} }
+ | If LParen Expression RParen EmptyStatement Else Statement
+ { AST.JSIfElse $1 $2 $3 $4 $5 $6 $7 {- 'IfStatement4' -} }
+
+-- IterationStatement : See 12.6
+-- do Statement while ( Expression );
+-- while ( Expression ) Statement
+-- for (ExpressionNoInopt; Expressionopt ; Expressionopt ) Statement
+-- for ( var VariableDeclarationListNoIn; Expressionopt ; Expressionopt ) Statement
+-- for ( LeftHandSideExpression in Expression ) Statement
+-- for ( var VariableDeclarationNoIn in Expression ) Statement
+IterationStatement :: { AST.JSStatement }
+IterationStatement : Do StatementNoEmpty While LParen Expression RParen MaybeSemi
+ { AST.JSDoWhile $1 $2 $3 $4 $5 $6 $7 {- 'IterationStatement1' -} }
+ | While LParen Expression RParen Statement
+ { AST.JSWhile $1 $2 $3 $4 $5 {- 'IterationStatement2' -} }
+ | For LParen ExpressionNoInOpt Semi ExpressionOpt Semi ExpressionOpt RParen Statement
+ { AST.JSFor $1 $2 $3 $4 $5 $6 $7 $8 $9 {- 'IterationStatement3' -} }
+ | For LParen Var VariableDeclarationListNoIn Semi ExpressionOpt Semi ExpressionOpt RParen Statement
+ { AST.JSForVar $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 {- 'IterationStatement4' -} }
+ | For LParen LeftHandSideExpression In Expression RParen Statement
+ { AST.JSForIn $1 $2 $3 $4 $5 $6 $7 {- 'IterationStatement 5' -} }
+ | For LParen Var VariableDeclarationNoIn In Expression RParen Statement
+ { AST.JSForVarIn $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement6' -} }
+ | For LParen Let VariableDeclarationListNoIn Semi ExpressionOpt Semi ExpressionOpt RParen Statement
+ { AST.JSForLet $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 {- 'IterationStatement 7' -} }
+ | For LParen Let VariableDeclarationNoIn In Expression RParen Statement
+ { AST.JSForLetIn $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 8' -} }
+ | For LParen Let VariableDeclarationNoIn Of Expression RParen Statement
+ { AST.JSForLetOf $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 9' -} }
+ | For LParen LeftHandSideExpression Of Expression RParen Statement
+ { AST.JSForOf $1 $2 $3 $4 $5 $6 $7 {- 'IterationStatement 10'-} }
+ | For LParen Var VariableDeclarationNoIn Of Expression RParen Statement
+ { AST.JSForVarOf $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 11' -} }
+ | For LParen Const VariableDeclarationListNoIn Semi ExpressionOpt Semi ExpressionOpt RParen Statement
+ { AST.JSForConst $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 {- 'IterationStatement 12' -} }
+ | For LParen Const VariableDeclarationNoIn In Expression RParen Statement
+ { AST.JSForConstIn $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 13' -} }
+ | For LParen Const VariableDeclarationNoIn Of Expression RParen Statement
+ { AST.JSForConstOf $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 14' -} }
+
+-- ContinueStatement : See 12.7
+-- continue [no LineTerminator here] Identifieropt ;
+ContinueStatement :: { AST.JSStatement }
+ContinueStatement : Continue AutoSemi { AST.JSContinue $1 AST.JSIdentNone $2 {- 'ContinueStatement1' -} }
+ | Continue Identifier MaybeSemi { AST.JSContinue $1 (identName $2) $3 {- 'ContinueStatement2' -} }
+
+-- BreakStatement : See 12.8
+-- break [no LineTerminator here] Identifieropt ;
+BreakStatement :: { AST.JSStatement }
+BreakStatement : Break AutoSemi { AST.JSBreak $1 AST.JSIdentNone $2 {- 'BreakStatement1' -} }
+ | Break Identifier MaybeSemi { AST.JSBreak $1 (identName $2) $3 {- 'BreakStatement2' -} }
+
+-- ReturnStatement : See 12.9
+-- return [no LineTerminator here] Expressionopt ;
+ReturnStatement :: { AST.JSStatement }
+ReturnStatement : Return AutoSemi { AST.JSReturn $1 Nothing $2 }
+ | Return Expression MaybeSemi { AST.JSReturn $1 (Just $2) $3 }
+
+-- WithStatement : See 12.10
+-- with ( Expression ) Statement
+WithStatement :: { AST.JSStatement }
+WithStatement : With LParen Expression RParen Statement MaybeSemi { AST.JSWith $1 $2 $3 $4 $5 $6 }
+
+-- SwitchStatement : See 12.11
+-- switch ( Expression ) CaseBlock
+SwitchStatement :: { AST.JSStatement }
+SwitchStatement : Switch LParen Expression RParen LBrace CaseBlock RBrace MaybeSemi { AST.JSSwitch $1 $2 $3 $4 $5 $6 $7 $8 }
+
+-- CaseBlock : See 12.11
+-- { CaseClausesopt }
+-- { CaseClausesopt DefaultClause CaseClausesopt }
+CaseBlock :: { [AST.JSSwitchParts] }
+CaseBlock : CaseClausesOpt { $1 {- 'CaseBlock1' -} }
+ | CaseClausesOpt DefaultClause CaseClausesOpt { $1++[$2]++$3 {- 'CaseBlock2' -} }
+
+-- CaseClauses : See 12.11
+-- CaseClause
+-- CaseClauses CaseClause
+CaseClausesOpt :: { [AST.JSSwitchParts] }
+CaseClausesOpt : CaseClause { [$1] {- 'CaseClausesOpt1' -} }
+ | CaseClausesOpt CaseClause { ($1++[$2]) {- 'CaseClausesOpt2' -} }
+ | { [] {- 'CaseClausesOpt3' -} }
+
+-- CaseClause : See 12.11
+-- case Expression : StatementListopt
+CaseClause :: { AST.JSSwitchParts }
+CaseClause : Case Expression Colon StatementList { AST.JSCase $1 $2 $3 $4 {- 'CaseClause1' -} }
+ | Case Expression Colon { AST.JSCase $1 $2 $3 [] {- 'CaseClause2' -} }
+
+-- DefaultClause : See 12.11
+-- default : StatementListopt
+DefaultClause :: { AST.JSSwitchParts }
+DefaultClause : Default Colon { AST.JSDefault $1 $2 [] {- 'DefaultClause1' -} }
+ | Default Colon StatementList { AST.JSDefault $1 $2 $3 {- 'DefaultClause2' -} }
+
+-- LabelledStatement : See 12.12
+-- Identifier : Statement
+LabelledStatement :: { AST.JSStatement }
+LabelledStatement : Identifier Colon Statement { AST.JSLabelled (identName $1) $2 $3 {- 'LabelledStatement' -} }
+
+-- ThrowStatement : See 12.13
+-- throw [no LineTerminator here] Expression ;
+ThrowStatement :: { AST.JSStatement }
+ThrowStatement : Throw Expression MaybeSemi { AST.JSThrow $1 $2 $3 {- 'ThrowStatement' -} }
+
+-- Note: worked in updated syntax as per https://developer.mozilla.org/en/JavaScript/Reference/Statements/try...catch
+-- i.e., 0 or more catches, then an optional finally
+-- TryStatement : See 12.14
+-- try Block Catch
+-- try Block Finally
+-- try Block Catch Finally
+TryStatement :: { AST.JSStatement }
+TryStatement : Try Block Catches { AST.JSTry $1 $2 $3 AST.JSNoFinally {- 'TryStatement1' -} }
+ | Try Block Finally { AST.JSTry $1 $2 [] $3 {- 'TryStatement2' -} }
+ | Try Block Catches Finally { AST.JSTry $1 $2 $3 $4 {- 'TryStatement3' -} }
+
+Catches :: { [AST.JSTryCatch] }
+Catches : Catch { [$1] {- 'Catches1' -} }
+ | Catches Catch { ($1++[$2]) {- 'Catches2' -} }
+
+-- Note: worked in updated syntax as per https://developer.mozilla.org/en/JavaScript/Reference/Statements/try...catch
+-- <Catch> ::= 'catch' '(' Identifier ')' <Block>
+-- becomes
+-- <Catch> ::= 'catch' '(' Identifier ')' <Block>
+-- | 'catch' '(' Identifier 'if' ConditionalExpression ')' <Block>
+Catch :: { AST.JSTryCatch }
+Catch : CatchL LParen Identifier RParen Block { AST.JSCatch $1 $2 $3 $4 $5 {- 'Catch1' -} }
+ | CatchL LParen Identifier If ConditionalExpression RParen Block { AST.JSCatchIf $1 $2 $3 $4 $5 $6 $7 {- 'Catch2' -} }
+
+-- Finally : See 12.14
+-- finally Block
+Finally :: { AST.JSTryFinally }
+Finally : FinallyL Block { AST.JSFinally $1 $2 {- 'Finally' -} }
+
+-- DebuggerStatement : See 12.15
+-- debugger ;
+DebuggerStatement :: { AST.JSStatement }
+DebuggerStatement : 'debugger' MaybeSemi { AST.JSExpressionStatement (AST.JSLiteral (mkJSAnnot $1) "debugger") $2 {- 'DebuggerStatement' -} }
+
+-- FunctionDeclaration : See clause 13
+-- function Identifier ( FormalParameterListopt ) { FunctionBody }
+FunctionDeclaration :: { AST.JSStatement }
+FunctionDeclaration : NamedFunctionExpression MaybeSemi { expressionToStatement $1 $2 {- 'FunctionDeclaration1' -} }
+
+AsyncFunctionStatement :: { AST.JSStatement }
+AsyncFunctionStatement : Async NamedFunctionExpression MaybeSemi { expressionToAsyncFunction $1 $2 $3 {- 'AsyncFunctionStatement1' -} }
+
+-- FunctionExpression : See clause 13
+-- function Identifieropt ( FormalParameterListopt ) { FunctionBody }
+FunctionExpression :: { AST.JSExpression }
+FunctionExpression : ArrowFunctionExpression { $1 {- 'ArrowFunctionExpression' -} }
+ | LambdaExpression { $1 {- 'FunctionExpression1' -} }
+ | NamedFunctionExpression { $1 {- 'FunctionExpression2' -} }
+
+ArrowFunctionExpression :: { AST.JSExpression }
+ArrowFunctionExpression : ArrowParameterList Arrow StatementOrBlock
+ { AST.JSArrowExpression $1 $2 $3 }
+
+ArrowParameterList :: { AST.JSArrowParameterList }
+ArrowParameterList : PrimaryExpression {%^ toArrowParameterList $1 }
+ | LParen RParen
+ { AST.JSParenthesizedArrowParameterList $1 AST.JSLNil $2 }
+
+StatementOrBlock :: { AST.JSStatement }
+StatementOrBlock : Block MaybeSemi { blockToStatement $1 $2 }
+ | Expression MaybeSemi { expressionToStatement $1 $2 }
+
+-- StatementListItem :
+-- Statement
+-- Declaration
+StatementListItem :: { AST.JSStatement }
+StatementListItem : Statement { $1 }
+
+NamedFunctionExpression :: { AST.JSExpression }
+NamedFunctionExpression : Function Identifier LParen RParen FunctionBody
+ { AST.JSFunctionExpression $1 (identName $2) $3 AST.JSLNil $4 $5 {- 'NamedFunctionExpression1' -} }
+ | Function Identifier LParen FormalParameterList RParen FunctionBody
+ { AST.JSFunctionExpression $1 (identName $2) $3 $4 $5 $6 {- 'NamedFunctionExpression2' -} }
+
+LambdaExpression :: { AST.JSExpression }
+LambdaExpression : Function LParen RParen FunctionBody
+ { AST.JSFunctionExpression $1 AST.JSIdentNone $2 AST.JSLNil $3 $4 {- 'LambdaExpression1' -} }
+ | Function LParen FormalParameterList RParen FunctionBody
+ { AST.JSFunctionExpression $1 AST.JSIdentNone $2 $3 $4 $5 {- 'LambdaExpression2' -} }
+
+-- GeneratorDeclaration :
+-- function * BindingIdentifier ( FormalParameters ) { GeneratorBody }
+-- function * ( FormalParameters ) { GeneratorBody }
+GeneratorDeclaration :: { AST.JSStatement }
+GeneratorDeclaration : NamedGeneratorExpression MaybeSemi { expressionToStatement $1 $2 }
+
+-- GeneratorExpression :
+-- function * BindingIdentifieropt ( FormalParameters ) { GeneratorBody }
+-- GeneratorBody :
+-- FunctionBody
+GeneratorExpression :: { AST.JSExpression }
+GeneratorExpression : NamedGeneratorExpression { $1 }
+ | Function '*' LParen RParen FunctionBody
+ { AST.JSGeneratorExpression $1 (mkJSAnnot $2) AST.JSIdentNone $3 AST.JSLNil $4 $5 }
+ | Function '*' LParen FormalParameterList RParen FunctionBody
+ { AST.JSGeneratorExpression $1 (mkJSAnnot $2) AST.JSIdentNone $3 $4 $5 $6 }
+
+NamedGeneratorExpression :: { AST.JSExpression }
+NamedGeneratorExpression : Function '*' Identifier LParen RParen FunctionBody
+ { AST.JSGeneratorExpression $1 (mkJSAnnot $2) (identName $3) $4 AST.JSLNil $5 $6 }
+ | Function '*' Identifier LParen FormalParameterList RParen FunctionBody
+ { AST.JSGeneratorExpression $1 (mkJSAnnot $2) (identName $3) $4 $5 $6 $7 }
+
+-- YieldExpression :
+-- yield
+-- yield [no LineTerminator here] AssignmentExpression
+-- yield [no LineTerminator here] * AssignmentExpression
+YieldExpression :: { AST.JSExpression }
+YieldExpression : Yield { AST.JSYieldExpression $1 Nothing }
+ | Yield AssignmentExpression { AST.JSYieldExpression $1 (Just $2) }
+ | Yield '*' AssignmentExpression { AST.JSYieldFromExpression $1 (mkJSAnnot $2) $3 }
+
+
+IdentifierOpt :: { AST.JSIdent }
+IdentifierOpt : Identifier { identName $1 {- 'IdentifierOpt1' -} }
+ | { AST.JSIdentNone {- 'IdentifierOpt2' -} }
+
+-- FormalParameterList : See clause 13
+-- Identifier
+-- FormalParameterList , Identifier
+FormalParameterList :: { AST.JSCommaList AST.JSExpression }
+FormalParameterList : AssignmentExpression { AST.JSLOne $1 {- 'FormalParameterList1' -} }
+ | FormalParameterList Comma AssignmentExpression { AST.JSLCons $1 $2 $3 {- 'FormalParameterList2' -} }
+
+-- FunctionBody : See clause 13
+-- SourceElementsopt
+FunctionBody :: { AST.JSBlock }
+FunctionBody : Block { $1 {- 'FunctionBody1' -} }
+
+-- ClassDeclaration :
+-- class BindingIdentifier ClassTail
+-- class ClassTail
+-- ClassExpression :
+-- class BindingIdentifieropt ClassTail
+-- ClassTail :
+-- ClassHeritageopt { ClassBodyopt }
+ClassDeclaration :: { AST.JSStatement }
+ClassDeclaration : Class Identifier ClassHeritage LBrace ClassBody RBrace { AST.JSClass $1 (identName $2) $3 $4 $5 $6 AST.JSSemiAuto }
+
+ClassExpression :: { AST.JSExpression }
+ClassExpression : Class Identifier ClassHeritage LBrace ClassBody RBrace { AST.JSClassExpression $1 (identName $2) $3 $4 $5 $6 }
+ | Class ClassHeritage LBrace ClassBody RBrace { AST.JSClassExpression $1 AST.JSIdentNone $2 $3 $4 $5 }
+
+-- ClassHeritage :
+-- extends LeftHandSideExpression
+ClassHeritage :: { AST.JSClassHeritage }
+ClassHeritage : Extends LeftHandSideExpression { AST.JSExtends $1 $2 }
+ | { AST.JSExtendsNone }
+
+-- ClassBody :
+-- ClassElementList
+-- ClassElementList :
+-- ClassElement
+-- ClassElementList ClassElement
+ClassBody :: { [AST.JSClassElement] }
+ClassBody : { [] }
+ | ClassBody ClassElement { $1 ++ [$2] }
+
+-- ClassElement :
+-- MethodDefinition
+-- static MethodDefinition
+-- ;
+ClassElement :: { AST.JSClassElement }
+ClassElement : MethodDefinition { AST.JSClassInstanceMethod $1 }
+ | Static MethodDefinition { AST.JSClassStaticMethod $1 $2 }
+ | Semi { AST.JSClassSemi $1 }
+
+-- Program : See clause 14
+-- SourceElementsopt
+
+Program :: { AST.JSAST }
+Program : StatementList Eof { AST.JSAstProgram $1 $2 {- 'Program1' -} }
+ | Eof { AST.JSAstProgram [] $1 {- 'Program2' -} }
+
+-- Module : See 15.2
+-- ModuleBody[opt]
+--
+-- ModuleBody :
+-- ModuleItemList
+Module :: { AST.JSAST }
+Module : ModuleItemList Eof { AST.JSAstModule $1 $2 {- 'Module1' -} }
+ | Eof { AST.JSAstModule [] $1 {- 'Module2' -} }
+
+-- ModuleItemList :
+-- ModuleItem
+-- ModuleItemList ModuleItem
+ModuleItemList :: { [AST.JSModuleItem] }
+ModuleItemList : ModuleItem { [$1] {- 'ModuleItemList1' -} }
+ | ModuleItemList ModuleItem { ($1++[$2]) {- 'ModuleItemList2' -} }
+
+-- ModuleItem :
+-- ImportDeclaration
+-- ExportDeclaration
+-- StatementListItem
+ModuleItem :: { AST.JSModuleItem }
+ModuleItem : Import ImportDeclaration
+ { AST.JSModuleImportDeclaration $1 $2 {- 'ModuleItem1' -} }
+ | Export ExportDeclaration
+ { AST.JSModuleExportDeclaration $1 $2 {- 'ModuleItem1' -} }
+ | StatementListItem
+ { AST.JSModuleStatementListItem $1 {- 'ModuleItem2' -} }
+
+ImportDeclaration :: { AST.JSImportDeclaration }
+ImportDeclaration : ImportClause FromClause AutoSemi
+ { AST.JSImportDeclaration $1 $2 $3 }
+ | 'string' AutoSemi
+ { AST.JSImportDeclarationBare (mkJSAnnot $1) (tokenLiteral $1) $2 }
+
+ImportClause :: { AST.JSImportClause }
+ImportClause : IdentifierName
+ { AST.JSImportClauseDefault (identName $1) }
+ | NameSpaceImport
+ { AST.JSImportClauseNameSpace $1 }
+ | NamedImports
+ { AST.JSImportClauseNamed $1 }
+ | IdentifierName ',' NameSpaceImport
+ { AST.JSImportClauseDefaultNameSpace (identName $1) (mkJSAnnot $2) $3 }
+ | IdentifierName ',' NamedImports
+ { AST.JSImportClauseDefaultNamed (identName $1) (mkJSAnnot $2) $3 }
+
+FromClause :: { AST.JSFromClause }
+FromClause : From 'string'
+ { AST.JSFromClause $1 (mkJSAnnot $2) (tokenLiteral $2) }
+
+NameSpaceImport :: { AST.JSImportNameSpace }
+NameSpaceImport : Mul As IdentifierName
+ { AST.JSImportNameSpace $1 $2 (identName $3) }
+
+NamedImports :: { AST.JSImportsNamed }
+NamedImports : LBrace ImportsList RBrace
+ { AST.JSImportsNamed $1 $2 $3 }
+
+ImportsList :: { AST.JSCommaList AST.JSImportSpecifier }
+ImportsList : ImportSpecifier
+ { AST.JSLOne $1 }
+ | ImportsList Comma ImportSpecifier
+ { AST.JSLCons $1 $2 $3 }
+
+ImportSpecifier :: { AST.JSImportSpecifier }
+ImportSpecifier : IdentifierName
+ { AST.JSImportSpecifier (identName $1) }
+ | IdentifierName As IdentifierName
+ { AST.JSImportSpecifierAs (identName $1) $2 (identName $3) }
+
+-- ExportDeclaration : See 15.2.3
+-- [ ] export * FromClause ;
+-- [x] export ExportClause FromClause ;
+-- [x] export ExportClause ;
+-- [x] export VariableStatement
+-- [ ] export Declaration
+-- [ ] Declaration :
+-- [ ] HoistableDeclaration
+-- [x] ClassDeclaration
+-- [x] LexicalDeclaration
+-- [ ] HoistableDeclaration :
+-- [x] FunctionDeclaration
+-- [x] GeneratorDeclaration
+-- [ ] AsyncFunctionDeclaration
+-- [ ] AsyncGeneratorDeclaration
+-- [ ] export default HoistableDeclaration[Default]
+-- [ ] export default ClassDeclaration[Default]
+-- [ ] export default [lookahead ∉ { function, class }] AssignmentExpression[In] ;
+ExportDeclaration :: { AST.JSExportDeclaration }
+ExportDeclaration : ExportClause FromClause AutoSemi
+ { AST.JSExportFrom $1 $2 $3 {- 'ExportDeclaration1' -} }
+ | ExportClause AutoSemi
+ { AST.JSExportLocals $1 $2 {- 'ExportDeclaration2' -} }
+ | VariableStatement AutoSemi
+ { AST.JSExport $1 $2 {- 'ExportDeclaration3' -} }
+ | FunctionDeclaration AutoSemi
+ { AST.JSExport $1 $2 {- 'ExportDeclaration4' -} }
+ | GeneratorDeclaration AutoSemi
+ { AST.JSExport $1 $2 {- 'ExportDeclaration5' -} }
+ | ClassDeclaration AutoSemi
+ { AST.JSExport $1 $2 {- 'ExportDeclaration6' -} }
+
+-- ExportClause :
+-- { }
+-- { ExportsList }
+-- { ExportsList , }
+ExportClause :: { AST.JSExportClause }
+ExportClause : LBrace RBrace
+ { AST.JSExportClause $1 AST.JSLNil $2 {- 'ExportClause1' -} }
+ | LBrace ExportsList RBrace
+ { AST.JSExportClause $1 $2 $3 {- 'ExportClause2' -} }
+
+-- ExportsList :
+-- ExportSpecifier
+-- ExportsList , ExportSpecifier
+ExportsList :: { AST.JSCommaList AST.JSExportSpecifier }
+ExportsList : ExportSpecifier
+ { AST.JSLOne $1 {- 'ExportsList1' -} }
+ | ExportsList Comma ExportSpecifier
+ { AST.JSLCons $1 $2 $3 {- 'ExportsList2' -} }
+
+-- ExportSpecifier :
+-- IdentifierName
+-- IdentifierName as IdentifierName
+ExportSpecifier :: { AST.JSExportSpecifier }
+ExportSpecifier : IdentifierName
+ { AST.JSExportSpecifier (identName $1) {- 'ExportSpecifier1' -} }
+ | IdentifierName As IdentifierName
+ { AST.JSExportSpecifierAs (identName $1) $2 (identName $3) {- 'ExportSpecifier2' -} }
+
+-- For debugging/other entry points
+LiteralMain :: { AST.JSAST }
+LiteralMain : Literal Eof { AST.JSAstLiteral $1 $2 {- 'LiteralMain' -} }
+
+ExpressionMain :: { AST.JSAST }
+ExpressionMain : Expression Eof { AST.JSAstExpression $1 $2 {- 'ExpressionMain' -} }
+
+StatementMain :: { AST.JSAST }
+StatementMain : StatementNoEmpty Eof { AST.JSAstStatement $1 $2 {- 'StatementMain' -} }
+
+{
+
+-- Need this type while build the AST, but is not actually part of the AST.
+data JSArguments = JSArguments AST.JSAnnot (AST.JSCommaList AST.JSExpression) AST.JSAnnot -- ^lb, args, rb
+data JSUntaggedTemplate = JSUntaggedTemplate !AST.JSAnnot !String ![AST.JSTemplatePart] -- lquot, head, parts
+
+blockToStatement :: AST.JSBlock -> AST.JSSemi -> AST.JSStatement
+blockToStatement (AST.JSBlock a b c) s = AST.JSStatementBlock a b c s
+
+expressionToStatement :: AST.JSExpression -> AST.JSSemi -> AST.JSStatement
+expressionToStatement (AST.JSFunctionExpression a b@(AST.JSIdentName{}) c d e f) s = AST.JSFunction a b c d e f s
+expressionToStatement (AST.JSGeneratorExpression a b c@(AST.JSIdentName{}) d e f g) s = AST.JSGenerator a b c d e f g s
+expressionToStatement (AST.JSAssignExpression lhs op rhs) s = AST.JSAssignStatement lhs op rhs s
+expressionToStatement (AST.JSMemberExpression e l a r) s = AST.JSMethodCall e l a r s
+expressionToStatement (AST.JSClassExpression a b@(AST.JSIdentName{}) c d e f) s = AST.JSClass a b c d e f s
+expressionToStatement exp s = AST.JSExpressionStatement exp s
+
+expressionToAsyncFunction :: AST.JSAnnot -> AST.JSExpression -> AST.JSSemi -> AST.JSStatement
+expressionToAsyncFunction aa (AST.JSFunctionExpression a b@(AST.JSIdentName{}) c d e f) s = AST.JSAsyncFunction aa a b c d e f s
+expressionToAsyncFunction _aa _exp _s = error "Bad async function."
+
+mkJSCallExpression :: AST.JSExpression -> JSArguments -> AST.JSExpression
+mkJSCallExpression e (JSArguments l arglist r) = AST.JSCallExpression e l arglist r
+
+mkJSMemberExpression :: AST.JSExpression -> JSArguments -> AST.JSExpression
+mkJSMemberExpression e (JSArguments l arglist r) = AST.JSMemberExpression e l arglist r
+
+mkJSMemberNew :: AST.JSAnnot -> AST.JSExpression -> JSArguments -> AST.JSExpression
+mkJSMemberNew a e (JSArguments l arglist r) = AST.JSMemberNew a e l arglist r
+
+parseError :: Token -> Alex a
+parseError = alexError . show
+
+mkJSAnnot :: Token -> AST.JSAnnot
+mkJSAnnot a = AST.JSAnnot (tokenSpan a) (tokenComment a)
+
+mkJSTemplateLiteral :: Maybe AST.JSExpression -> JSUntaggedTemplate -> AST.JSExpression
+mkJSTemplateLiteral tag (JSUntaggedTemplate a h ps) = AST.JSTemplateLiteral tag a h ps
+
+-- ---------------------------------------------------------------------
+-- | mkUnary : The parser detects '+' and '-' as the binary version of these
+-- operator. This function converts from the binary version to the unary
+-- version.
+mkUnary :: AST.JSBinOp -> AST.JSUnaryOp
+mkUnary (AST.JSBinOpMinus annot) = AST.JSUnaryOpMinus annot
+mkUnary (AST.JSBinOpPlus annot) = AST.JSUnaryOpPlus annot
+
+mkUnary x = error $ "Invalid unary op : " ++ show x
+
+identName :: AST.JSExpression -> AST.JSIdent
+identName (AST.JSIdentifier a s) = AST.JSIdentName a s
+identName x = error $ "Cannot convert '" ++ show x ++ "' to a JSIdentName."
+
+propName :: AST.JSExpression -> AST.JSPropertyName
+propName (AST.JSIdentifier a s) = AST.JSPropertyIdent a s
+propName (AST.JSDecimal a s) = AST.JSPropertyNumber a s
+propName (AST.JSHexInteger a s) = AST.JSPropertyNumber a s
+propName (AST.JSOctal a s) = AST.JSPropertyNumber a s
+propName (AST.JSStringLiteral a s) = AST.JSPropertyString a s
+propName x = error $ "Cannot convert '" ++ show x ++ "' to a JSPropertyName."
+
+identifierToProperty :: AST.JSExpression -> AST.JSObjectProperty
+identifierToProperty (AST.JSIdentifier a s) = AST.JSPropertyIdentRef a s
+identifierToProperty x = error $ "Cannot convert '" ++ show x ++ "' to a JSObjectProperty."
+
+toArrowParameterList :: AST.JSExpression -> Token -> Alex AST.JSArrowParameterList
+toArrowParameterList (AST.JSIdentifier a s) = const . return $ AST.JSUnparenthesizedArrowParameter (AST.JSIdentName a s)
+toArrowParameterList (AST.JSExpressionParen lb x rb) = const . return $ AST.JSParenthesizedArrowParameterList lb (commasToCommaList x) rb
+toArrowParameterList _ = parseError
+
+commasToCommaList :: AST.JSExpression -> AST.JSCommaList AST.JSExpression
+commasToCommaList (AST.JSCommaExpression l c r) = AST.JSLCons (commasToCommaList l) c r
+commasToCommaList x = AST.JSLOne x
+
+}
--- /dev/null
+{
+{-# LANGUAGE CPP #-}
+{-# OPTIONS_GHC -funbox-strict-fields #-}
+
+#if __GLASGOW_HASKELL__ >= 800
+-- Alex generates code with these warnings so we'll just ignore them.
+{-# OPTIONS_GHC -Wno-unused-matches #-}
+{-# OPTIONS_GHC -Wno-unused-imports #-}
+#endif
+
+module Language.JavaScript.Parser.Lexer
+ ( Token (..)
+ , Alex
+ , lexCont
+ , alexError
+ , runAlex
+ , alexTestTokeniser
+ , setInTemplate
+ ) where
+
+import Language.JavaScript.Parser.LexerUtils
+import Language.JavaScript.Parser.ParserMonad
+import Language.JavaScript.Parser.SrcLocation
+import Language.JavaScript.Parser.Token
+import qualified Data.Map as Map
+
+}
+
+-- %wrapper "basic"
+-- %wrapper "monad"
+%wrapper "monadUserState"
+-- %wrapper "monad-bytestring"
+
+-- character sets
+$lf = \n -- line feed
+$cr = \r -- carriage return
+$ht = \t -- horizontal tab
+$sq = ' -- single quote
+$dq = \" -- double quote
+$digit = 0-9 -- digits
+$oct_digit = [0-7]
+$hex_digit = [0-9a-fA-F]
+$alpha = [a-zA-Z] -- alphabetic characters
+$non_zero_digit = 1-9
+$ident_letter = [a-zA-Z_]
+@eol_pattern = $lf | $cr $lf | $cr $lf
+
+$ls = \x2028
+$ps = \x2029
+@LineTerminatorSequence = $lf | $cr | $ls | $ps | $cr $lf
+
+
+$any_char = [\x00-\xff]
+$any_unicode_char = [\x00-\x10ffff]
+
+
+$eol_char = [\x000A\x000D\x2028\x2029] -- any end of line character
+-- $eol_char = [$lf $cr] -- any end of line character
+$not_eol_char = ~$eol_char -- anything but an end of line character
+
+
+-- From GOLD Parser
+-- {ID Head} = {Letter} + [_] + [$]
+@IDHead = $alpha | [_] | [\$]
+
+-- {ID Tail} = {Alphanumeric} + [_] + [$]
+@IDTail = $alpha | $digit | [_] | [\$]
+
+-- {String Chars1} = {Printable} + {HT} - ["\]
+-- {String Chars2} = {Printable} + {HT} - [\'']
+-- $StringCharsDoubleQuote = [$printable $ht] # [$dq \\]
+-- $StringCharsSingleQuote = [$printable $ht] # [$sq \\]
+
+$string_chars = [^ \n \r ' \" \\]
+
+-- See e.g. http://es5.github.io/x7.html#x7.8.4 (Table 4)
+@sq_escapes = \\ ( \\ | ' | \" | \s | \- | b | f | n | r | t | v | 0 | x )
+@dq_escapes = \\ ( \\ | ' | \" | \s | \- | b | f | n | r | t | v | 0 | x )
+
+@unicode_escape = \\ u $hex_digit{4}
+
+@string_parts = $string_chars | \\ $digit | $ls | $ps
+
+@non_escape_char = \\ [^ \n \\ ]
+
+@stringCharsSingleQuote = @string_parts | @sq_escapes | @unicode_escape | $dq | @non_escape_char
+@stringCharsDoubleQuote = @string_parts | @dq_escapes | @unicode_escape | $sq | @non_escape_char
+
+-- Character values < 0x20.
+$low_unprintable = [\x00-\x1f]
+
+-- LineContinuation :: \ LineTerminatorSequence
+@LineContinuation = [\\] @LineTerminatorSequence
+
+
+-- {RegExp Chars} = {Letter}+{Digit}+['^']+['$']+['*']+['+']+['?']+['{']+['}']+['|']+['-']+['.']+[',']+['#']+['[']+[']']+['_']+['<']+['>']
+-- $RegExpChars = [$alpha $digit \^\$\*\+\?\{\}\|\-\.\,\#\[\]\_\<\>]
+-- $RegExpChars = [$printable] # [\\]
+-- {Non Terminator} = {String Chars1} - {CR} - {LF}
+-- $NonTerminator = $StringCharsDoubleQuote # [$cr $lf]
+$regNonTerminator = [$printable] # [$cr $lf]
+
+
+$reg_char_class_chars = [^ $cr $lf \[ \] ]
+@reg_char_class_escapes = \\ ( \[ | \] )
+@regCharClass = \[ ($reg_char_class_chars | @reg_char_class_escapes)* \]
+
+
+-- ~ (LineTerminator | MUL | BSLASH | DIV)
+$RegExpFirstChar = [$printable] # [ $cr $lf \* \\ \/]
+-- ~ ( LineTerminator | BSLASH | DIV )
+$RegExpChars = [$printable] # [ $cr $lf \\ \/]
+
+$MultiLineNotAsteriskChar = [$any_unicode_char] # [\*]
+$MultiLineNotForwardSlashOrAsteriskChar = [$any_unicode_char] # [\* \/]
+
+-- See http://blog.stevenlevithan.com/archives/javascript-regex-and-unicode
+ -- * \u0009 — Tab — \t
+ -- * \u000a — Line feed — \n — (newline character)
+ -- * \u000b — Vertical tab — \v
+ -- * \u000c — Form feed — \f
+ -- * \u000d — Carriage return — \r — (newline character)
+ -- * \u0020 — Space
+ -- * \u00a0 — No-break space
+ -- * \u1680 — Ogham space mark
+ -- * \u180e — Mongolian vowel separator
+ -- * \u2000 — En quad
+ -- * \u2001 — Em quad
+ -- * \u2002 — En space
+ -- * \u2003 — Em space
+ -- * \u2004 — Three-per-em space
+ -- * \u2005 — Four-per-em space
+ -- * \u2006 — Six-per-em space
+ -- * \u2007 — Figure space
+ -- * \u2008 — Punctuation space
+ -- * \u2009 — Thin space
+ -- * \u200a — Hair space
+ -- * \u2028 — Line separator — (newline character)
+ -- * \u2029 — Paragraph separator — (newline character)
+ -- * \u202f — Narrow no-break space
+ -- * \u205f — Medium mathematical space
+ -- * \u3000 — Ideographic space
+
+-- Note: from edition 5 the BOM (\xfeff) is also considered whitespace
+$white_char = [\x0009\x000a\x000b\x000c\x000d\x0020\x00a0\x1680\x180e\x2000\x2001\x2002\x2003\x2004\x2005\x2006\x2007\x2008\x2009\x200a\x2028\x2029\x202f\x205f\x3000\xfeff]
+
+-- Identifier characters
+-- UnicodeLetter
+-- any character in the Unicode categories “Uppercase letter (Lu)”, “Lowercase letter (Ll)”,
+-- “Titlecase letter (Lt)”, “Modifier letter (Lm)”, “Other letter (Lo)”, or “Letter number (Nl)”.
+
+-- http://www.fileformat.info/info/unicode/category/Lu/list.htm etc, see unicode/doit.sh
+$UnicodeLetter = [\x41-\x5a\x61-\x7a\xaa-\xaa\xb5-\xb5\xba-\xba\xc0-\xd6\xd8-\xf6\xf8-\x2c1\x2c6-\x2d1\x2e0-\x2e4\x2ec-\x2ec\x2ee-\x2ee\x370-\x374\x376-\x377\x37a-\x37d\x386-\x386\x388-\x38a\x38c-\x38c\x38e-\x3a1\x3a3-\x3f5\x3f7-\x481\x48a-\x527\x531-\x556\x559-\x559\x561-\x587\x5d0-\x5ea\x5f0-\x5f2\x620-\x64a\x66e-\x66f\x671-\x6d3\x6d5-\x6d5\x6e5-\x6e6\x6ee-\x6ef\x6fa-\x6fc\x6ff-\x6ff\x710-\x710\x712-\x72f\x74d-\x7a5\x7b1-\x7b1\x7ca-\x7ea\x7f4-\x7f5\x7fa-\x7fa\x800-\x815\x81a-\x81a\x824-\x824\x828-\x828\x840-\x858\x904-\x939\x93d-\x93d\x950-\x950\x958-\x961\x971-\x977\x979-\x97f\x985-\x98c\x98f-\x990\x993-\x9a8\x9aa-\x9b0\x9b2-\x9b2\x9b6-\x9b9\x9bd-\x9bd\x9ce-\x9ce\x9dc-\x9dd\x9df-\x9e1\x9f0-\x9f1\xa05-\xa0a\xa0f-\xa10\xa13-\xa28\xa2a-\xa30\xa32-\xa33\xa35-\xa36\xa38-\xa39\xa59-\xa5c\xa5e-\xa5e\xa72-\xa74\xa85-\xa8d\xa8f-\xa91\xa93-\xaa8\xaaa-\xab0\xab2-\xab3\xab5-\xab9\xabd-\xabd\xad0-\xad0\xae0-\xae1\xb05-\xb0c\xb0f-\xb10\xb13-\xb28\xb2a-\xb30\xb32-\xb33\xb35-\xb39\xb3d-\xb3d\xb5c-\xb5d\xb5f-\xb61\xb71-\xb71\xb83-\xb83\xb85-\xb8a\xb8e-\xb90\xb92-\xb95\xb99-\xb9a\xb9c-\xb9c\xb9e-\xb9f\xba3-\xba4\xba8-\xbaa\xbae-\xbb9\xbd0-\xbd0\xc05-\xc0c\xc0e-\xc10\xc12-\xc28\xc2a-\xc33\xc35-\xc39\xc3d-\xc3d\xc58-\xc59\xc60-\xc61\xc85-\xc8c\xc8e-\xc90\xc92-\xca8\xcaa-\xcb3\xcb5-\xcb9\xcbd-\xcbd\xcde-\xcde\xce0-\xce1\xcf1-\xcf2\xd05-\xd0c\xd0e-\xd10\xd12-\xd3a\xd3d-\xd3d\xd4e-\xd4e\xd60-\xd61\xd7a-\xd7f\xd85-\xd96\xd9a-\xdb1\xdb3-\xdbb\xdbd-\xdbd\xdc0-\xdc6\xe01-\xe30\xe32-\xe33\xe40-\xe46\xe81-\xe82\xe84-\xe84\xe87-\xe88\xe8a-\xe8a\xe8d-\xe8d\xe94-\xe97\xe99-\xe9f\xea1-\xea3\xea5-\xea5\xea7-\xea7\xeaa-\xeab\xead-\xeb0\xeb2-\xeb3\xebd-\xebd\xec0-\xec4\xec6-\xec6\xedc-\xedd\xf00-\xf00\xf40-\xf47\xf49-\xf6c\xf88-\xf8c\x1000-\x1000\x10000-\x1000b\x1000d-\x1000f\x1001-\x1001\x10010-\x1001f\x1002-\x1002\x10020-\x10026\x10028-\x1002f\x1003-\x1003\x10030-\x1003a\x1003c-\x1003d\x1003f-\x1003f\x1004-\x1004\x10040-\x1004d\x1005-\x1005\x10050-\x1005d\x1006-\x1008\x10080-\x1008f\x1009-\x1009\x10090-\x1009f\x100a-\x100a\x100a0-\x100af\x100b-\x100b\x100b0-\x100bf\x100c-\x100c\x100c0-\x100cf\x100d-\x100d\x100d0-\x100df\x100e-\x100e\x100e0-\x100ef\x100f-\x100f\x100f0-\x100fa\x1010-\x1014\x10140-\x1014f\x1015-\x1015\x10150-\x1015f\x1016-\x1016\x10160-\x1016f\x1017-\x1017\x10170-\x10174\x1018-\x1028\x10280-\x1028f\x1029-\x1029\x10290-\x1029c\x102a-\x102a\x102a0-\x102d0\x10300-\x1031e\x10330-\x1034a\x10380-\x1039d\x103a0-\x103c3\x103c8-\x103cf\x103d1-\x103d5\x103f-\x103f\x10400-\x1049d\x1050-\x1055\x105a-\x105d\x1061-\x1061\x1065-\x1066\x106e-\x1070\x1075-\x1080\x10800-\x10805\x10808-\x10808\x1080a-\x1080f\x1081-\x1081\x10810-\x10835\x10837-\x10838\x1083c-\x1083c\x1083f-\x10855\x108e-\x108e\x10900-\x10915\x10920-\x10939\x10a0-\x10a0\x10a00-\x10a00\x10a1-\x10a1\x10a10-\x10a13\x10a15-\x10a17\x10a19-\x10a1f\x10a2-\x10a2\x10a20-\x10a2f\x10a3-\x10a3\x10a30-\x10a33\x10a4-\x10a6\x10a60-\x10a6f\x10a7-\x10a7\x10a70-\x10a7c\x10a8-\x10b0\x10b00-\x10b0f\x10b1-\x10b1\x10b10-\x10b1f\x10b2-\x10b2\x10b20-\x10b2f\x10b3-\x10b3\x10b30-\x10b35\x10b4-\x10b4\x10b40-\x10b4f\x10b5-\x10b5\x10b50-\x10b55\x10b6-\x10b6\x10b60-\x10b6f\x10b7-\x10b7\x10b70-\x10b72\x10b8-\x10c0\x10c00-\x10c0f\x10c1-\x10c1\x10c10-\x10c1f\x10c2-\x10c2\x10c20-\x10c2f\x10c3-\x10c3\x10c30-\x10c3f\x10c4-\x10c4\x10c40-\x10c48\x10c5-\x10c5\x10d0-\x10fa\x10fc-\x10fc\x1100-\x1100\x11003-\x1100f\x1101-\x1101\x11010-\x1101f\x1102-\x1102\x11020-\x1102f\x1103-\x1103\x11030-\x11037\x1104-\x1108\x11083-\x1108f\x1109-\x1109\x11090-\x1109f\x110a-\x110a\x110a0-\x110af\x110b-\x1200\x12000-\x1200f\x1201-\x1201\x12010-\x1201f\x1202-\x1202\x12020-\x1202f\x1203-\x1203\x12030-\x1203f\x1204-\x1204\x12040-\x1204f\x1205-\x1205\x12050-\x1205f\x1206-\x1206\x12060-\x1206f\x1207-\x1207\x12070-\x1207f\x1208-\x1208\x12080-\x1208f\x1209-\x1209\x12090-\x1209f\x120a-\x120a\x120a0-\x120af\x120b-\x120b\x120b0-\x120bf\x120c-\x120c\x120c0-\x120cf\x120d-\x120d\x120d0-\x120df\x120e-\x120e\x120e0-\x120ef\x120f-\x120f\x120f0-\x120ff\x1210-\x1210\x12100-\x1210f\x1211-\x1211\x12110-\x1211f\x1212-\x1212\x12120-\x1212f\x1213-\x1213\x12130-\x1213f\x1214-\x1214\x12140-\x1214f\x1215-\x1215\x12150-\x1215f\x1216-\x1216\x12160-\x1216f\x1217-\x1217\x12170-\x1217f\x1218-\x1218\x12180-\x1218f\x1219-\x1219\x12190-\x1219f\x121a-\x121a\x121a0-\x121af\x121b-\x121b\x121b0-\x121bf\x121c-\x121c\x121c0-\x121cf\x121d-\x121d\x121d0-\x121df\x121e-\x121e\x121e0-\x121ef\x121f-\x121f\x121f0-\x121ff\x1220-\x1220\x12200-\x1220f\x1221-\x1221\x12210-\x1221f\x1222-\x1222\x12220-\x1222f\x1223-\x1223\x12230-\x1223f\x1224-\x1224\x12240-\x1224f\x1225-\x1225\x12250-\x1225f\x1226-\x1226\x12260-\x1226f\x1227-\x1227\x12270-\x1227f\x1228-\x1228\x12280-\x1228f\x1229-\x1229\x12290-\x1229f\x122a-\x122a\x122a0-\x122af\x122b-\x122b\x122b0-\x122bf\x122c-\x122c\x122c0-\x122cf\x122d-\x122d\x122d0-\x122df\x122e-\x122e\x122e0-\x122ef\x122f-\x122f\x122f0-\x122ff\x1230-\x1230\x12300-\x1230f\x1231-\x1231\x12310-\x1231f\x1232-\x1232\x12320-\x1232f\x1233-\x1233\x12330-\x1233f\x1234-\x1234\x12340-\x1234f\x1235-\x1235\x12350-\x1235f\x1236-\x1236\x12360-\x1236e\x1237-\x1240\x12400-\x1240f\x1241-\x1241\x12410-\x1241f\x1242-\x1242\x12420-\x1242f\x1243-\x1243\x12430-\x1243f\x1244-\x1244\x12440-\x1244f\x1245-\x1245\x12450-\x1245f\x1246-\x1246\x12460-\x12462\x1247-\x1248\x124a-\x124d\x1250-\x1256\x1258-\x1258\x125a-\x125d\x1260-\x1288\x128a-\x128d\x1290-\x12b0\x12b2-\x12b5\x12b8-\x12be\x12c0-\x12c0\x12c2-\x12c5\x12c8-\x12d6\x12d8-\x1300\x13000-\x1300f\x1301-\x1301\x13010-\x1301f\x1302-\x1302\x13020-\x1302f\x1303-\x1303\x13030-\x1303f\x1304-\x1304\x13040-\x1304f\x1305-\x1305\x13050-\x1305f\x1306-\x1306\x13060-\x1306f\x1307-\x1307\x13070-\x1307f\x1308-\x1308\x13080-\x1308f\x1309-\x1309\x13090-\x1309f\x130a-\x130a\x130a0-\x130af\x130b-\x130b\x130b0-\x130bf\x130c-\x130c\x130c0-\x130cf\x130d-\x130d\x130d0-\x130df\x130e-\x130e\x130e0-\x130ef\x130f-\x130f\x130f0-\x130ff\x1310-\x1310\x13100-\x1311f\x1312-\x1312\x13120-\x1312f\x1313-\x1313\x13130-\x1313f\x1314-\x1314\x13140-\x1314f\x1315-\x1315\x13150-\x1317f\x1318-\x1318\x13180-\x1318f\x1319-\x1319\x13190-\x1319f\x131a-\x131a\x131a0-\x131af\x131b-\x131b\x131b0-\x131bf\x131c-\x131c\x131c0-\x131cf\x131d-\x131d\x131d0-\x131df\x131e-\x131e\x131e0-\x131ef\x131f-\x131f\x131f0-\x131ff\x1320-\x1320\x13200-\x1320f\x1321-\x1321\x13210-\x1321f\x1322-\x1322\x13220-\x1322f\x1323-\x1323\x13230-\x1323f\x1324-\x1324\x13240-\x1324f\x1325-\x1325\x13250-\x1325f\x1326-\x1326\x13260-\x1326f\x1327-\x1327\x13270-\x1327f\x1328-\x1328\x13280-\x1328f\x1329-\x1329\x13290-\x1329f\x132a-\x132a\x132a0-\x132af\x132b-\x132b\x132b0-\x132bf\x132c-\x132c\x132c0-\x132cf\x132d-\x132d\x132d0-\x132df\x132e-\x132e\x132e0-\x132ef\x132f-\x132f\x132f0-\x132ff\x1330-\x1330\x13300-\x1330f\x1331-\x1331\x13310-\x1331f\x1332-\x1332\x13320-\x1332f\x1333-\x1333\x13330-\x1333f\x1334-\x1334\x13340-\x1334f\x1335-\x1335\x13350-\x1335f\x1336-\x1336\x13360-\x1336f\x1337-\x1337\x13370-\x1337f\x1338-\x1338\x13380-\x1338f\x1339-\x1339\x13390-\x1339f\x133a-\x133a\x133a0-\x133af\x133b-\x133b\x133b0-\x133bf\x133c-\x133c\x133c0-\x133cf\x133d-\x133d\x133d0-\x133df\x133e-\x133e\x133e0-\x133ef\x133f-\x133f\x133f0-\x133ff\x1340-\x1340\x13400-\x1340f\x1341-\x1341\x13410-\x1341f\x1342-\x1342\x13420-\x1342e\x1343-\x135a\x1380-\x138f\x13a0-\x13f4\x1401-\x166c\x166f-\x167f\x16800-\x1680f\x1681-\x1681\x16810-\x1681f\x1682-\x1682\x16820-\x1682f\x1683-\x1683\x16830-\x1683f\x1684-\x1684\x16840-\x1684f\x1685-\x1685\x16850-\x1685f\x1686-\x1686\x16860-\x1686f\x1687-\x1687\x16870-\x1687f\x1688-\x1688\x16880-\x1688f\x1689-\x1689\x16890-\x1689f\x168a-\x168a\x168a0-\x168af\x168b-\x168b\x168b0-\x168bf\x168c-\x168c\x168c0-\x168cf\x168d-\x168d\x168d0-\x168df\x168e-\x168e\x168e0-\x168ef\x168f-\x168f\x168f0-\x168ff\x1690-\x1690\x16900-\x1690f\x1691-\x1691\x16910-\x1691f\x1692-\x1692\x16920-\x1692f\x1693-\x1693\x16930-\x1693f\x1694-\x1694\x16940-\x1694f\x1695-\x1695\x16950-\x1695f\x1696-\x1696\x16960-\x1696f\x1697-\x1697\x16970-\x1697f\x1698-\x1698\x16980-\x1698f\x1699-\x1699\x16990-\x1699f\x169a-\x169a\x169a0-\x169ff\x16a0-\x16a0\x16a00-\x16a0f\x16a1-\x16a1\x16a10-\x16a1f\x16a2-\x16a2\x16a20-\x16a2f\x16a3-\x16a3\x16a30-\x16a38\x16a4-\x16ea\x16ee-\x16f0\x1700-\x170c\x170e-\x1711\x1720-\x1731\x1740-\x1751\x1760-\x176c\x176e-\x1770\x1780-\x17b3\x17d7-\x17d7\x17dc-\x17dc\x1820-\x1877\x1880-\x18a8\x18aa-\x18aa\x18b0-\x18f5\x1900-\x191c\x1950-\x196d\x1970-\x1974\x1980-\x19ab\x19c1-\x19c7\x1a00-\x1a16\x1a20-\x1a54\x1aa7-\x1aa7\x1b000-\x1b001\x1b05-\x1b33\x1b45-\x1b4b\x1b83-\x1ba0\x1bae-\x1baf\x1bc0-\x1be5\x1c00-\x1c23\x1c4d-\x1c4f\x1c5a-\x1c7d\x1ce9-\x1cec\x1cee-\x1cf1\x1d00-\x1d40\x1d400-\x1d40f\x1d41-\x1d41\x1d410-\x1d41f\x1d42-\x1d42\x1d420-\x1d42f\x1d43-\x1d43\x1d430-\x1d43f\x1d44-\x1d44\x1d440-\x1d44f\x1d45-\x1d45\x1d450-\x1d454\x1d456-\x1d45f\x1d46-\x1d46\x1d460-\x1d46f\x1d47-\x1d47\x1d470-\x1d47f\x1d48-\x1d48\x1d480-\x1d48f\x1d49-\x1d49\x1d490-\x1d49c\x1d49e-\x1d49f\x1d4a-\x1d4a\x1d4a2-\x1d4a2\x1d4a5-\x1d4a6\x1d4a9-\x1d4ac\x1d4ae-\x1d4af\x1d4b-\x1d4b\x1d4b0-\x1d4b9\x1d4bb-\x1d4bb\x1d4bd-\x1d4bf\x1d4c-\x1d4c\x1d4c0-\x1d4c3\x1d4c5-\x1d4cf\x1d4d-\x1d4d\x1d4d0-\x1d4df\x1d4e-\x1d4e\x1d4e0-\x1d4ef\x1d4f-\x1d4f\x1d4f0-\x1d4ff\x1d50-\x1d50\x1d500-\x1d505\x1d507-\x1d50a\x1d50d-\x1d50f\x1d51-\x1d51\x1d510-\x1d514\x1d516-\x1d51c\x1d51e-\x1d51f\x1d52-\x1d52\x1d520-\x1d52f\x1d53-\x1d53\x1d530-\x1d539\x1d53b-\x1d53e\x1d54-\x1d54\x1d540-\x1d544\x1d546-\x1d546\x1d54a-\x1d54f\x1d55-\x1d55\x1d550-\x1d550\x1d552-\x1d55f\x1d56-\x1d56\x1d560-\x1d56f\x1d57-\x1d57\x1d570-\x1d57f\x1d58-\x1d58\x1d580-\x1d58f\x1d59-\x1d59\x1d590-\x1d59f\x1d5a-\x1d5a\x1d5a0-\x1d5af\x1d5b-\x1d5b\x1d5b0-\x1d5bf\x1d5c-\x1d5c\x1d5c0-\x1d5cf\x1d5d-\x1d5d\x1d5d0-\x1d5df\x1d5e-\x1d5e\x1d5e0-\x1d5ef\x1d5f-\x1d5f\x1d5f0-\x1d5ff\x1d60-\x1d60\x1d600-\x1d60f\x1d61-\x1d61\x1d610-\x1d61f\x1d62-\x1d62\x1d620-\x1d62f\x1d63-\x1d63\x1d630-\x1d63f\x1d64-\x1d64\x1d640-\x1d64f\x1d65-\x1d65\x1d650-\x1d65f\x1d66-\x1d66\x1d660-\x1d66f\x1d67-\x1d67\x1d670-\x1d67f\x1d68-\x1d68\x1d680-\x1d68f\x1d69-\x1d69\x1d690-\x1d69f\x1d6a-\x1d6a\x1d6a0-\x1d6a5\x1d6a8-\x1d6af\x1d6b-\x1d6b\x1d6b0-\x1d6bf\x1d6c-\x1d6c\x1d6c0-\x1d6c0\x1d6c2-\x1d6cf\x1d6d-\x1d6d\x1d6d0-\x1d6da\x1d6dc-\x1d6df\x1d6e-\x1d6e\x1d6e0-\x1d6ef\x1d6f-\x1d6f\x1d6f0-\x1d6fa\x1d6fc-\x1d6ff\x1d70-\x1d70\x1d700-\x1d70f\x1d71-\x1d71\x1d710-\x1d714\x1d716-\x1d71f\x1d72-\x1d72\x1d720-\x1d72f\x1d73-\x1d73\x1d730-\x1d734\x1d736-\x1d73f\x1d74-\x1d74\x1d740-\x1d74e\x1d75-\x1d75\x1d750-\x1d75f\x1d76-\x1d76\x1d760-\x1d76e\x1d77-\x1d77\x1d770-\x1d77f\x1d78-\x1d78\x1d780-\x1d788\x1d78a-\x1d78f\x1d79-\x1d79\x1d790-\x1d79f\x1d7a-\x1d7a\x1d7a0-\x1d7a8\x1d7aa-\x1d7af\x1d7b-\x1d7b\x1d7b0-\x1d7bf\x1d7c-\x1d7c\x1d7c0-\x1d7c2\x1d7c4-\x1d7cb\x1d7d-\x1dbf\x1e00-\x1f15\x1f18-\x1f1d\x1f20-\x1f45\x1f48-\x1f4d\x1f50-\x1f57\x1f59-\x1f59\x1f5b-\x1f5b\x1f5d-\x1f5d\x1f5f-\x1f7d\x1f80-\x1fb4\x1fb6-\x1fbc\x1fbe-\x1fbe\x1fc2-\x1fc4\x1fc6-\x1fcc\x1fd0-\x1fd3\x1fd6-\x1fdb\x1fe0-\x1fec\x1ff2-\x1ff4\x1ff6-\x1ffc\x20000-\x20000\x2071-\x2071\x207f-\x207f\x2090-\x209c\x2102-\x2102\x2107-\x2107\x210a-\x2113\x2115-\x2115\x2119-\x211d\x2124-\x2124\x2126-\x2126\x2128-\x2128\x212a-\x212d\x212f-\x2139\x213c-\x213f\x2145-\x2149\x214e-\x214e\x2160-\x2188\x2a6d6-\x2a6d6\x2a700-\x2a700\x2b734-\x2b734\x2b740-\x2b740\x2b81d-\x2b81d\x2c00-\x2c2e\x2c30-\x2c5e\x2c60-\x2ce4\x2ceb-\x2cee\x2d00-\x2d25\x2d30-\x2d65\x2d6f-\x2d6f\x2d80-\x2d96\x2da0-\x2da6\x2da8-\x2dae\x2db0-\x2db6\x2db8-\x2dbe\x2dc0-\x2dc6\x2dc8-\x2dce\x2dd0-\x2dd6\x2dd8-\x2dde\x2e2f-\x2e2f\x2f800-\x2fa1d\x3005-\x3007\x3021-\x3029\x3031-\x3035\x3038-\x303c\x3041-\x3096\x309d-\x309f\x30a1-\x30fa\x30fc-\x30ff\x3105-\x312d\x3131-\x318e\x31a0-\x31ba\x31f0-\x31ff\x3400-\x3400\x4db5-\x4db5\x4e00-\x4e00\x9fcb-\x9fcb\xa000-\xa48c\xa4d0-\xa4fd\xa500-\xa60c\xa610-\xa61f\xa62a-\xa62b\xa640-\xa66e\xa67f-\xa697\xa6a0-\xa6ef\xa717-\xa71f\xa722-\xa788\xa78b-\xa78e\xa790-\xa791\xa7a0-\xa7a9\xa7fa-\xa801\xa803-\xa805\xa807-\xa80a\xa80c-\xa822\xa840-\xa873\xa882-\xa8b3\xa8f2-\xa8f7\xa8fb-\xa8fb\xa90a-\xa925\xa930-\xa946\xa960-\xa97c\xa984-\xa9b2\xa9cf-\xa9cf\xaa00-\xaa28\xaa40-\xaa42\xaa44-\xaa4b\xaa60-\xaa76\xaa7a-\xaa7a\xaa80-\xaaaf\xaab1-\xaab1\xaab5-\xaab6\xaab9-\xaabd\xaac0-\xaac0\xaac2-\xaac2\xaadb-\xaadd\xab01-\xab06\xab09-\xab0e\xab11-\xab16\xab20-\xab26\xab28-\xab2e\xabc0-\xabe2\xac00-\xac00\xd7a3-\xd7a3\xd7b0-\xd7c6\xd7cb-\xd7fb\xf900-\xfa2d\xfa30-\xfa6d\xfa70-\xfad9\xfb00-\xfb06\xfb13-\xfb17\xfb1d-\xfb1d\xfb1f-\xfb28\xfb2a-\xfb36\xfb38-\xfb3c\xfb3e-\xfb3e\xfb40-\xfb41\xfb43-\xfb44\xfb46-\xfbb1\xfbd3-\xfd3d\xfd50-\xfd8f\xfd92-\xfdc7\xfdf0-\xfdfb\xfe70-\xfe74\xfe76-\xfefc\xff21-\xff3a\xff41-\xff5a\xff66-\xffbe\xffc2-\xffc7\xffca-\xffcf\xffd2-\xffd7]
+
+-- UnicodeCombiningMark
+-- any character in the Unicode categories “Non-spacing mark (Mn)” or “Combining spacing mark (Mc)”
+$UnicodeCombiningMark = [\x300-\x36f\x483-\x487\x591-\x5bd\x5bf-\x5bf\x5c1-\x5c2\x5c4-\x5c5\x5c7-\x5c7\x610-\x61a\x64b-\x65f\x670-\x670\x6d6-\x6dc\x6df-\x6e4\x6e7-\x6e8\x6ea-\x6ed\x711-\x711\x730-\x74a\x7a6-\x7b0\x7eb-\x7f3\x816-\x819\x81b-\x823\x825-\x827\x829-\x82d\x859-\x85b\x900-\x903\x93a-\x93c\x93e-\x94f\x951-\x957\x962-\x963\x981-\x983\x9bc-\x9bc\x9be-\x9c4\x9c7-\x9c8\x9cb-\x9cd\x9d7-\x9d7\x9e2-\x9e3\xa01-\xa03\xa3c-\xa3c\xa3e-\xa42\xa47-\xa48\xa4b-\xa4d\xa51-\xa51\xa70-\xa71\xa75-\xa75\xa81-\xa83\xabc-\xabc\xabe-\xac5\xac7-\xac9\xacb-\xacd\xae2-\xae3\xb01-\xb03\xb3c-\xb3c\xb3e-\xb44\xb47-\xb48\xb4b-\xb4d\xb56-\xb57\xb62-\xb63\xb82-\xb82\xbbe-\xbc2\xbc6-\xbc8\xbca-\xbcd\xbd7-\xbd7\xc01-\xc03\xc3e-\xc44\xc46-\xc48\xc4a-\xc4d\xc55-\xc56\xc62-\xc63\xc82-\xc83\xcbc-\xcbc\xcbe-\xcc4\xcc6-\xcc8\xcca-\xccd\xcd5-\xcd6\xce2-\xce3\xd02-\xd03\xd3e-\xd44\xd46-\xd48\xd4a-\xd4d\xd57-\xd57\xd62-\xd63\xd82-\xd83\xdca-\xdca\xdcf-\xdd4\xdd6-\xdd6\xdd8-\xddf\xdf2-\xdf3\xe31-\xe31\xe34-\xe3a\xe47-\xe4e\xeb1-\xeb1\xeb4-\xeb9\xebb-\xebc\xec8-\xecd\xf18-\xf19\xf35-\xf35\xf37-\xf37\xf39-\xf39\xf3e-\xf3f\xf71-\xf84\xf86-\xf87\xf8d-\xf97\xf99-\xfbc\xfc6-\xfc6\x101fd-\x101fd\x102b-\x103e\x1056-\x1059\x105e-\x1060\x1062-\x1064\x1067-\x106d\x1071-\x1074\x1082-\x108d\x108f-\x108f\x109a-\x109d\x10a01-\x10a03\x10a05-\x10a06\x10a0c-\x10a0f\x10a38-\x10a3a\x10a3f-\x10a3f\x11000-\x11002\x11038-\x11046\x11080-\x11082\x110b0-\x110ba\x135d-\x135f\x1712-\x1714\x1732-\x1734\x1752-\x1753\x1772-\x1773\x17b6-\x17d3\x17dd-\x17dd\x180b-\x180d\x18a9-\x18a9\x1920-\x192b\x1930-\x193b\x19b0-\x19c0\x19c8-\x19c9\x1a17-\x1a1b\x1a55-\x1a5e\x1a60-\x1a7c\x1a7f-\x1a7f\x1b00-\x1b04\x1b34-\x1b44\x1b6b-\x1b73\x1b80-\x1b82\x1ba1-\x1baa\x1be6-\x1bf3\x1c24-\x1c37\x1cd0-\x1cd2\x1cd4-\x1ce8\x1ced-\x1ced\x1cf2-\x1cf2\x1d165-\x1d169\x1d16d-\x1d172\x1d17b-\x1d182\x1d185-\x1d18b\x1d1aa-\x1d1ad\x1d242-\x1d244\x1dc0-\x1de6\x1dfc-\x1dff\x20d0-\x20dc\x20e1-\x20e1\x20e5-\x20f0\x2cef-\x2cf1\x2d7f-\x2d7f\x2de0-\x2dff\x302a-\x302f\x3099-\x309a\xa66f-\xa66f\xa67c-\xa67d\xa6f0-\xa6f1\xa802-\xa802\xa806-\xa806\xa80b-\xa80b\xa823-\xa827\xa880-\xa881\xa8b4-\xa8c4\xa8e0-\xa8f1\xa926-\xa92d\xa947-\xa953\xa980-\xa983\xa9b3-\xa9c0\xaa29-\xaa36\xaa43-\xaa43\xaa4c-\xaa4d\xaa7b-\xaa7b\xaab0-\xaab0\xaab2-\xaab4\xaab7-\xaab8\xaabe-\xaabf\xaac1-\xaac1\xabe3-\xabea\xabec-\xabed\xe0100-\xe01ef\xfb1e-\xfb1e\xfe00-\xfe0f]
+
+-- UnicodeDigit
+-- any character in the Unicode category “Decimal number (Nd)”
+$UnicodeDigit = [\x30-\x39\x660-\x669\x6f0-\x6f9\x7c0-\x7c9\x966-\x96f\x9e6-\x9ef\xa66-\xa6f\xae6-\xaef\xb66-\xb6f\xbe6-\xbef\xc66-\xc6f\xce6-\xcef\xd66-\xd6f\xe50-\xe59\xed0-\xed9\xf20-\xf29\x1040-\x1049\x104a0-\x104a9\x1090-\x1099\x11066-\x1106f\x17e0-\x17e9\x1810-\x1819\x1946-\x194f\x19d0-\x19d9\x1a80-\x1a89\x1a90-\x1a99\x1b50-\x1b59\x1bb0-\x1bb9\x1c40-\x1c49\x1c50-\x1c59\x1d7ce-\x1d7ff\xa620-\xa629\xa8d0-\xa8d9\xa900-\xa909\xa9d0-\xa9d9\xaa50-\xaa59\xabf0-\xabf9]
+
+-- UnicodeConnectorPunctuation
+-- any character in the Unicode category “Connector punctuation (Pc)”
+$UnicodeConnectorPunctuation = [\x5f-\x5f\x203f-\x2040\x2054-\x2054\xfe33-\xfe34\xfe4d-\xfe4f]
+
+-- UnicodeEscapeSequence ::
+-- u HexDigit HexDigit HexDigit HexDigit
+$HexDigit = [0-9a-fA-F]
+@UnicodeEscapeSequence = u $HexDigit $HexDigit $HexDigit $HexDigit
+
+-- IdentifierStart ::
+-- UnicodeLetter
+-- $
+-- _
+-- \ UnicodeEscapeSequence
+@IdentifierStart = $UnicodeLetter | [\$] | [_] | [\\] @UnicodeEscapeSequence
+
+-- IdentifierPart ::
+-- IdentifierStart
+-- UnicodeCombiningMark
+-- UnicodeDigit
+-- UnicodeConnectorPunctuation
+-- \ UnicodeEscapeSequence
+
+$ZWNJ = [\x200c]
+$ZWJ = [\x200d]
+@IdentifierPart = @IdentifierStart | $UnicodeCombiningMark | $UnicodeDigit | UnicodeConnectorPunctuation
+ [\\] @UnicodeEscapeSequence | $ZWNJ | $ZWJ
+
+-- TemplateCharacter ::
+-- $ [lookahead ≠ { ]
+-- \ EscapeSequence
+-- LineContinuation
+-- LineTerminatorSequence
+-- SourceCharacter but not one of ` or \ or $ or LineTerminator
+@TemplateCharacters = (\$* ($any_unicode_char # [\$\\`\{] | \\ $any_unicode_char) | \\ $any_unicode_char | \{)* \$*
+
+-- ! ------------------------------------------------- Terminals
+tokens :-
+
+-- State: 0 is regex allowed, 1 is / or /= allowed
+-- 2 is a special state for parsing characters inside templates
+
+<0> () ; -- { registerStates lexToken reg divide template }
+
+-- Skip Whitespace
+<reg,divide> $white_char+ { adapt (mkString wsToken) }
+
+-- Skip one line comment
+<reg,divide> "//"($not_eol_char)* { adapt (mkString commentToken) }
+
+-- ---------------------------------------------------------------------
+-- Comment definition from the ECMAScript spec, ver 3
+
+-- MultiLineComment ::
+-- /* MultiLineCommentChars(opt) */
+-- MultiLineCommentChars ::
+-- MultiLineNotAsteriskChar MultiLineCommentChars(opt)
+-- * PostAsteriskCommentChars(opt)
+-- PostAsteriskCommentChars ::
+-- MultiLineNotForwardSlashOrAsteriskChar MultiLineCommentChars(opt)
+-- * PostAsteriskCommentChars(opt)
+-- MultiLineNotAsteriskChar ::
+-- SourceCharacter but not asterisk *
+-- MultiLineNotForwardSlashOrAsteriskChar ::
+-- SourceCharacter but not forward-slash / or asterisk *
+
+-- Skip multi-line comments. Note: may not nest
+-- <reg,divide> "/*"($any_char)*"*/" ;
+-- <reg,divide> "/*" (($MultiLineNotAsteriskChar)*| ("*")+ ($MultiLineNotForwardSlashOrAsteriskChar) )* ("*")+ "/" ;
+<reg,divide> "/*" (($MultiLineNotAsteriskChar)*| ("*")+ ($MultiLineNotForwardSlashOrAsteriskChar) )* ("*")+ "/" { adapt (mkString commentToken) }
+
+
+-- Identifier = {ID Head}{ID Tail}*
+-- <reg,divide> @IDHead(@IDTail)* { \loc len str -> keywordOrIdent (take len str) loc }
+<reg,divide> @IdentifierStart(@IdentifierPart)* { \ap@(loc,_,_,str) len -> keywordOrIdent (take len str) (toTokenPosn loc) }
+
+-- ECMA-262 : Section 7.8.4 String Literals
+-- StringLiteral = '"' ( {String Chars1} | '\' {Printable} )* '"'
+-- | '' ( {String Chars2} | '\' {Printable} )* ''
+<reg,divide> $dq (@stringCharsDoubleQuote *) $dq
+ | $sq (@stringCharsSingleQuote *) $sq { adapt (mkString stringToken) }
+
+-- HexIntegerLiteral = '0x' {Hex Digit}+
+<reg,divide> ("0x"|"0X") $hex_digit+ { adapt (mkString hexIntegerToken) }
+
+-- OctalLiteral = '0' {Octal Digit}+
+<reg,divide> ("0") $oct_digit+ { adapt (mkString octalToken) }
+
+-- RegExp = '/' ({RegExp Chars} | '\' {Non Terminator})+ '/' ( 'g' | 'i' | 'm' )*
+
+<reg> "/"
+ ("\" $regNonTerminator | @regCharClass | $RegExpFirstChar)
+ ("\" $regNonTerminator | @regCharClass | $RegExpChars)* "/" ("g"|"i"|"m")* { adapt (mkString regExToken) }
+
+
+
+<reg,divide> "`" @TemplateCharacters "`" { adapt (mkString' NoSubstitutionTemplateToken) }
+<reg,divide> "`" @TemplateCharacters "${" { adapt (mkString' TemplateHeadToken) }
+<template> @TemplateCharacters "${" { adapt (mkString' TemplateMiddleToken) }
+<template> @TemplateCharacters "`" { adapt (mkString' TemplateTailToken) }
+
+
+
+-- TODO: Work in SignedInteger
+
+-- DecimalLiteral= {Non Zero Digits}+ '.' {Digit}* ('e' | 'E' ) {Non Zero Digits}+ {Digit}*
+-- | {Non Zero Digits}+ '.' {Digit}*
+-- | '0' '.' {Digit}+ ('e' | 'E' ) {Non Zero Digits}+ {Digit}*
+-- | {Non Zero Digits}+ {Digit}*
+-- | '0'
+-- | '0' '.' {Digit}+
+
+-- <reg,divide> $non_zero_digit $digit* "." $digit* ("e"|"E") ("+"|"-")? $non_zero_digit+ $digit*
+-- | $non_zero_digit $digit* "." $digit*
+-- | "0." $digit+ ("e"|"E") ("+"|"-")? $non_zero_digit+ $digit*
+-- | $non_zero_digit+ $digit*
+-- | "0"
+-- | "0." $digit+ { mkString decimalToken }
+
+<reg,divide> "0" "." $digit* ("e"|"E") ("+"|"-")? $digit+
+ | $non_zero_digit $digit* "." $digit* ("e"|"E") ("+"|"-")? $digit+
+ | "." $digit+ ("e"|"E") ("+"|"-")? $digit+
+ | "0" ("e"|"E") ("+"|"-")? $digit+
+ | $non_zero_digit $digit* ("e"|"E") ("+"|"-")? $digit+
+-- ++FOO++
+ | "0" "." $digit*
+ | $non_zero_digit $digit* "." $digit*
+ | "." $digit+
+ | "0"
+ | $non_zero_digit $digit* { adapt (mkString decimalToken) }
+
+
+-- beginning of file
+<bof> {
+ @eol_pattern ;
+ -- @eol_pattern { endOfLine lexToken }
+ -- @eol_pattern { endOfLine alexMonadScan }
+}
+
+-- / or /= only allowed in state 1
+<divide> {
+ "/=" { adapt (symbolToken DivideAssignToken) }
+ "/" { adapt (symbolToken DivToken) }
+}
+
+<reg,divide> {
+ ";" { adapt (symbolToken SemiColonToken) }
+ "," { adapt (symbolToken CommaToken) }
+ "?" { adapt (symbolToken HookToken) }
+ ":" { adapt (symbolToken ColonToken) }
+ "||" { adapt (symbolToken OrToken) }
+ "&&" { adapt (symbolToken AndToken) }
+ "|" { adapt (symbolToken BitwiseOrToken) }
+ "^" { adapt (symbolToken BitwiseXorToken) }
+ "&" { adapt (symbolToken BitwiseAndToken) }
+ "=>" { adapt (symbolToken ArrowToken) }
+ "===" { adapt (symbolToken StrictEqToken) }
+ "==" { adapt (symbolToken EqToken) }
+ "*=" { adapt (symbolToken TimesAssignToken) }
+ "%=" { adapt (symbolToken ModAssignToken) }
+ "+=" { adapt (symbolToken PlusAssignToken) }
+ "-=" { adapt (symbolToken MinusAssignToken) }
+ "<<=" { adapt (symbolToken LshAssignToken) }
+ ">>=" { adapt (symbolToken RshAssignToken) }
+ ">>>=" { adapt (symbolToken UrshAssignToken) }
+ "&=" { adapt (symbolToken AndAssignToken) }
+ "^=" { adapt (symbolToken XorAssignToken) }
+ "|=" { adapt (symbolToken OrAssignToken) }
+ "=" { adapt (symbolToken SimpleAssignToken) }
+ "!==" { adapt (symbolToken StrictNeToken) }
+ "!=" { adapt (symbolToken NeToken) }
+ "<<" { adapt (symbolToken LshToken) }
+ "<=" { adapt (symbolToken LeToken) }
+ "<" { adapt (symbolToken LtToken) }
+ ">>>" { adapt (symbolToken UrshToken) }
+ ">>" { adapt (symbolToken RshToken) }
+ ">=" { adapt (symbolToken GeToken) }
+ ">" { adapt (symbolToken GtToken) }
+ "++" { adapt (symbolToken IncrementToken) }
+ "--" { adapt (symbolToken DecrementToken) }
+ "+" { adapt (symbolToken PlusToken) }
+ "-" { adapt (symbolToken MinusToken) }
+ "*" { adapt (symbolToken MulToken) }
+ "%" { adapt (symbolToken ModToken) }
+ "!" { adapt (symbolToken NotToken) }
+ "~" { adapt (symbolToken BitwiseNotToken) }
+ "..." { adapt (symbolToken SpreadToken) }
+ "." { adapt (symbolToken DotToken) }
+ "[" { adapt (symbolToken LeftBracketToken) }
+ "]" { adapt (symbolToken RightBracketToken) }
+ "{" { adapt (symbolToken LeftCurlyToken) }
+ "}" { adapt (symbolToken RightCurlyToken) }
+ "(" { adapt (symbolToken LeftParenToken) }
+ ")" { adapt (symbolToken RightParenToken) }
+}
+
+{
+
+{-
+-- The next function select between the two lex input states, as called for in
+-- secion 7 of ECMAScript Language Specification, Edition 3, 24 March 2000.
+
+The method is inspired by the lexer in http://jint.codeplex.com/
+-}
+
+classifyToken :: Token -> Int
+classifyToken aToken =
+ case aToken of
+ IdentifierToken {} -> divide
+ NullToken {} -> divide
+ TrueToken {} -> divide
+ FalseToken {} -> divide
+ ThisToken {} -> divide
+ OctalToken {} -> divide
+ DecimalToken {} -> divide
+ HexIntegerToken {} -> divide
+ StringToken {} -> divide
+ RightCurlyToken {} -> divide
+ RightParenToken {} -> divide
+ RightBracketToken {} -> divide
+ _other -> reg
+
+
+lexToken :: Alex Token
+lexToken = do
+ inp <- alexGetInput
+ lt <- getLastToken
+ case lt of
+ TailToken {} -> alexEOF
+ _other -> do
+ isInTmpl <- getInTemplate
+ let state = if isInTmpl then template else classifyToken lt
+ setInTemplate False -- the inTemplate condition only needs to last for one token
+ case alexScan inp state of
+ AlexEOF -> do
+ tok <- tailToken
+ setLastToken tok
+ return tok
+ AlexError (pos,_,_,_) ->
+ alexError ("lexical error @ line " ++ show (getLineNum(pos)) ++
+ " and column " ++ show (getColumnNum(pos)))
+ AlexSkip inp' _len -> do
+ alexSetInput inp'
+ lexToken
+ AlexToken inp' len action -> do
+ alexSetInput inp'
+ tok <- action inp len
+ setLastToken tok
+ return tok
+
+-- For tesing.
+alexTestTokeniser :: String -> Either String [Token]
+alexTestTokeniser input =
+ runAlex input $ loop []
+ where
+ loop acc = do
+ tok <- lexToken
+ case tok of
+ EOFToken {} ->
+ return $ case acc of
+ [] -> []
+ (TailToken{}:xs) -> reverse xs
+ xs -> reverse xs
+ _ -> loop (tok:acc)
+
+-- This is called by the Happy parser.
+lexCont :: (Token -> Alex a) -> Alex a
+lexCont cont =
+ lexLoop
+ where
+ lexLoop = do
+ tok <- lexToken
+ case tok of
+ CommentToken {} -> do
+ addComment tok
+ lexLoop
+ WsToken {} -> do
+ addComment tok
+ ltok <- getLastToken
+ case ltok of
+ BreakToken {} -> maybeAutoSemi tok
+ ContinueToken {} -> maybeAutoSemi tok
+ ReturnToken {} -> maybeAutoSemi tok
+ _otherwise -> lexLoop
+ _other -> do
+ cs <- getComment
+ let tok' = tok{ tokenComment=(toCommentAnnotation cs) }
+ setComment []
+ cont tok'
+
+ -- If the token is a WsToken and it contains a newline, convert it to an
+ -- AutoSemiToken and call the continuation, otherwise, just lexLoop.
+ maybeAutoSemi (WsToken sp tl cmt) =
+ if any (== '\n') tl
+ then cont $ AutoSemiToken sp tl cmt
+ else lexLoop
+ maybeAutoSemi _ = lexLoop
+
+
+toCommentAnnotation :: [Token] -> [CommentAnnotation]
+toCommentAnnotation [] = []
+toCommentAnnotation xs =
+ reverse $ map go xs
+ where
+ go tok@(CommentToken {}) = (CommentA (tokenSpan tok) (tokenLiteral tok))
+ go tok@(WsToken {}) = (WhiteSpace (tokenSpan tok) (tokenLiteral tok))
+ go _ = error "toCommentAnnotation"
+
+-- ---------------------------------------------------------------------
+
+getLineNum :: AlexPosn -> Int
+getLineNum (AlexPn _offset lineNum _colNum) = lineNum
+
+getColumnNum :: AlexPosn -> Int
+getColumnNum (AlexPn _offset _lineNum colNum) = colNum
+
+-- ---------------------------------------------------------------------
+
+getLastToken :: Alex Token
+getLastToken = Alex $ \s@AlexState{alex_ust=ust} -> Right (s, previousToken ust)
+
+setLastToken :: Token -> Alex ()
+setLastToken (WsToken {}) = Alex $ \s -> Right (s, ())
+setLastToken tok = Alex $ \s -> Right (s{alex_ust=(alex_ust s){previousToken=tok}}, ())
+
+getComment :: Alex [Token]
+getComment = Alex $ \s@AlexState{alex_ust=ust} -> Right (s, comment ust)
+
+
+addComment :: Token -> Alex ()
+addComment c = Alex $ \s -> Right (s{alex_ust=(alex_ust s){comment=c:( comment (alex_ust s) )}}, ())
+
+
+setComment :: [Token] -> Alex ()
+setComment cs = Alex $ \s -> Right (s{alex_ust=(alex_ust s){comment=cs }}, ())
+
+getInTemplate :: Alex Bool
+getInTemplate = Alex $ \s@AlexState{alex_ust=ust} -> Right (s, inTemplate ust)
+
+setInTemplate :: Bool -> Alex ()
+setInTemplate it = Alex $ \s -> Right (s{alex_ust=(alex_ust s){inTemplate=it}}, ())
+
+alexEOF :: Alex Token
+alexEOF = return (EOFToken tokenPosnEmpty [])
+
+tailToken :: Alex Token
+tailToken = return (TailToken tokenPosnEmpty [])
+
+adapt :: (TokenPosn -> Int -> String -> Alex Token) -> AlexInput -> Int -> Alex Token
+adapt f ((AlexPn offset line col),_,_,inp) len = f (TokenPn offset line col) len inp
+
+toTokenPosn :: AlexPosn -> TokenPosn
+toTokenPosn (AlexPn offset line col) = (TokenPn offset line col)
+
+-- ---------------------------------------------------------------------
+
+-- a keyword or an identifier (the syntax overlaps)
+keywordOrIdent :: String -> TokenPosn -> Alex Token
+keywordOrIdent str location =
+ return $ case Map.lookup str keywords of
+ Just symbol -> symbol location str []
+ Nothing -> IdentifierToken location str []
+
+-- mapping from strings to keywords
+keywords :: Map.Map String (TokenPosn -> String -> [CommentAnnotation] -> Token)
+keywords = Map.fromList keywordNames
+
+keywordNames :: [(String, TokenPosn -> String -> [CommentAnnotation] -> Token)]
+keywordNames =
+ [ ( "async", AsyncToken )
+ , ( "await", AwaitToken )
+ , ( "break", BreakToken )
+ , ( "case", CaseToken )
+ , ( "catch", CatchToken )
+
+ , ( "class", ClassToken )
+ , ( "const", ConstToken ) -- not a keyword, nominally a future reserved word, but actually in use
+
+ , ( "continue", ContinueToken )
+ , ( "debugger", DebuggerToken )
+ , ( "default", DefaultToken )
+ , ( "delete", DeleteToken )
+ , ( "do", DoToken )
+ , ( "else", ElseToken )
+
+ , ( "enum", EnumToken ) -- not a keyword, nominally a future reserved word, but actually in use
+ , ( "export", ExportToken )
+ , ( "extends", ExtendsToken )
+
+ , ( "false", FalseToken ) -- boolean literal
+
+ , ( "finally", FinallyToken )
+ , ( "for", ForToken )
+ , ( "function", FunctionToken )
+ , ( "from", FromToken )
+ , ( "if", IfToken )
+ , ( "import", ImportToken )
+ , ( "in", InToken )
+ , ( "instanceof", InstanceofToken )
+ , ( "let", LetToken )
+ , ( "new", NewToken )
+
+ , ( "null", NullToken ) -- null literal
+
+ , ( "of", OfToken )
+ , ( "return", ReturnToken )
+ , ( "static", StaticToken )
+ , ( "super", SuperToken )
+ , ( "switch", SwitchToken )
+ , ( "this", ThisToken )
+ , ( "throw", ThrowToken )
+ , ( "true", TrueToken )
+ , ( "try", TryToken )
+ , ( "typeof", TypeofToken )
+ , ( "var", VarToken )
+ , ( "void", VoidToken )
+ , ( "while", WhileToken )
+ , ( "with", WithToken )
+ , ( "yield", YieldToken )
+ -- TODO: no idea if these are reserved or not, but they are needed
+ -- handled in parser, in the Identifier rule
+ , ( "as", AsToken ) -- not reserved
+ , ( "get", GetToken )
+ , ( "set", SetToken )
+ {- Come from Table 6 of ECMASCRIPT 5.1, Attributes of a Named Accessor Property
+ Also include
+
+ Enumerable
+ Configurable
+
+ Table 7 includes
+
+ Value
+ -}
+
+
+ -- Future Reserved Words
+ -- ( "class", FutureToken ) **** an actual token, used in productions
+ -- ( "code", FutureToken ) **** not any more
+ -- ( "const", FutureToken ) **** an actual token, used in productions
+ -- enum **** an actual token, used in productions
+ -- ( "extends", FutureToken ) **** an actual token, used in productions
+ -- ( "super", FutureToken ) **** an actual token, used in productions
+
+
+ -- Strict mode FutureReservedWords
+ , ( "implements", FutureToken )
+ , ( "interface", FutureToken )
+ -- ( "mode", FutureToken ) **** not any more
+ -- ( "of", FutureToken ) **** not any more
+ -- ( "one", FutureToken ) **** not any more
+ -- ( "or", FutureToken ) **** not any more
+
+ , ( "package", FutureToken )
+ , ( "private", FutureToken )
+ , ( "protected", FutureToken )
+ , ( "public", FutureToken )
+ -- ( "static", FutureToken ) **** an actual token, used in productions
+ -- ( "strict", FutureToken ) *** not any more
+ -- ( "yield", FutureToken) **** an actual token, used in productions
+ ]
+}
+
+
+-- -- Edition 5.1 of ECMASCRIPT
+
+-- 7.6.1.1 Keywords
+
+-- The following tokens are ECMAScript keywords and may not be used as Identifiers in ECMAScript programs.
+
+-- Syntax
+-- Keyword :: one of
+-- break
+-- case
+-- catch
+-- continue
+-- debugger
+-- default
+-- delete
+-- do
+-- else
+-- finally
+-- for
+-- function
+-- if
+-- in
+-- instanceof
+-- new
+-- return
+-- switch
+-- this
+-- throw
+-- try
+-- typeof
+-- var
+-- void
+-- while
+-- with
+
+-- 7.6.1.2 Future Reserved Words
+
+-- The following words are used as keywords in proposed extensions and
+-- are therefore reserved to allow for the possibility of future adoption
+-- of those extensions.
+
+-- Syntax
+-- FutureReservedWord :: one of
+-- class
+-- const
+-- enum
+-- export
+-- extends
+-- import
+-- super
+
+-- The following tokens are also considered to be FutureReservedWords
+-- when they occur within strict mode code (see 10.1.1). The occurrence
+-- of any of these tokens within strict mode code in any context where
+-- the occurrence of a FutureReservedWord would produce an error must
+-- also produce an equivalent error:
+
+-- implements
+-- interface
+-- let
+-- package
+-- private
+-- protected
+-- public
+-- static
+-- yield
--- /dev/null
+-----------------------------------------------------------------------------
+-- |
+-- Module : Language.JavaScript.LexerUtils
+-- Based on language-python version by Bernie Pope
+-- Copyright : (c) 2009 Bernie Pope
+-- License : BSD-style
+-- Stability : experimental
+-- Portability : ghc
+--
+-- Various utilities to support the JavaScript lexer.
+-----------------------------------------------------------------------------
+
+module Language.JavaScript.Parser.LexerUtils
+ ( StartCode
+ , symbolToken
+ , mkString
+ , mkString'
+ , commentToken
+ , wsToken
+ , regExToken
+ , decimalToken
+ , hexIntegerToken
+ , octalToken
+ , stringToken
+ ) where
+
+import Language.JavaScript.Parser.Token as Token
+import Language.JavaScript.Parser.SrcLocation
+import Prelude hiding (span)
+
+-- Functions for building tokens
+
+type StartCode = Int
+
+symbolToken :: Monad m => (TokenPosn -> [CommentAnnotation] -> Token) -> TokenPosn -> Int -> String -> m Token
+symbolToken mkToken location _ _ = return (mkToken location [])
+
+mkString :: (Monad m) => (TokenPosn -> String -> Token) -> TokenPosn -> Int -> String -> m Token
+mkString toToken loc len str = return (toToken loc (take len str))
+
+mkString' :: (Monad m) => (TokenPosn -> String -> [CommentAnnotation] -> Token) -> TokenPosn -> Int -> String -> m Token
+mkString' toToken loc len str = return (toToken loc (take len str) [])
+
+decimalToken :: TokenPosn -> String -> Token
+decimalToken loc str = DecimalToken loc str []
+
+hexIntegerToken :: TokenPosn -> String -> Token
+hexIntegerToken loc str = HexIntegerToken loc str []
+
+octalToken :: TokenPosn -> String -> Token
+octalToken loc str = OctalToken loc str []
+
+regExToken :: TokenPosn -> String -> Token
+regExToken loc str = RegExToken loc str []
+
+stringToken :: TokenPosn -> String -> Token
+stringToken loc str = StringToken loc str []
+
+commentToken :: TokenPosn -> String -> Token
+commentToken loc str = CommentToken loc str []
+
+wsToken :: TokenPosn -> String -> Token
+wsToken loc str = WsToken loc str []
--- /dev/null
+-----------------------------------------------------------------------------
+-- |
+-- Module : Language.JavaScript.ParseError
+-- Based on language-python version by Bernie Pope
+-- Copyright : (c) 2009 Bernie Pope
+-- License : BSD-style
+-- Stability : experimental
+-- Portability : ghc
+--
+-- Error values for the lexer and parser.
+-----------------------------------------------------------------------------
+
+module Language.JavaScript.Parser.ParseError
+ ( Error (..)
+ , ParseError (..)
+ ) where
+
+--import Language.JavaScript.Parser.Pretty
+-- import Control.Monad.Error.Class -- Control.Monad.Trans.Except
+import Language.JavaScript.Parser.Lexer
+import Language.JavaScript.Parser.SrcLocation (TokenPosn)
+-- import Language.JavaScript.Parser.Token (Token)
+
+data ParseError
+ = UnexpectedToken Token
+ -- ^ An error from the parser. Token found where it should not be.
+ -- Note: tokens contain their own source span.
+ | UnexpectedChar Char TokenPosn
+ -- ^ An error from the lexer. Character found where it should not be.
+ | StrError String
+ -- ^ A generic error containing a string message. No source location.
+ deriving (Eq, {- Ord,-} Show)
+
+class Error a where
+ -- | Creates an exception without a message.
+ -- The default implementation is @'strMsg' \"\"@.
+ noMsg :: a
+ -- | Creates an exception with a message.
+ -- The default implementation of @'strMsg' s@ is 'noMsg'.
+ strMsg :: String -> a
+
+instance Error ParseError where
+ noMsg = StrError ""
+ strMsg = StrError
+
--- /dev/null
+module Language.JavaScript.Parser.Parser (
+ -- * Parsing
+ parse
+ , parseModule
+ , readJs
+ , readJsModule
+ -- , readJsKeepComments
+ , parseFile
+ , parseFileUtf8
+ -- * Parsing expressions
+ -- parseExpr
+ , parseUsing
+ , showStripped
+ , showStrippedMaybe
+ ) where
+
+import qualified Language.JavaScript.Parser.Grammar7 as P
+import Language.JavaScript.Parser.Lexer
+import qualified Language.JavaScript.Parser.AST as AST
+import System.IO
+
+-- | Parse JavaScript Program (Script)
+-- Parse one compound statement, or a sequence of simple statements.
+-- Generally used for interactive input, such as from the command line of an interpreter.
+-- Return comments in addition to the parsed statements.
+parse :: String -- ^ The input stream (Javascript source code).
+ -> String -- ^ The name of the Javascript source (filename or input device).
+ -> Either String AST.JSAST
+ -- ^ An error or maybe the abstract syntax tree (AST) of zero
+ -- or more Javascript statements, plus comments.
+parse = parseUsing P.parseProgram
+
+-- | Parse JavaScript module
+parseModule :: String -- ^ The input stream (JavaScript source code).
+ -> String -- ^ The name of the JavaScript source (filename or input device).
+ -> Either String AST.JSAST
+ -- ^ An error or maybe the abstract syntax tree (AST) of zero
+ -- or more JavaScript statements, plus comments.
+parseModule = parseUsing P.parseModule
+
+readJsWith :: (String -> String -> Either String AST.JSAST)
+ -> String
+ -> AST.JSAST
+readJsWith f input =
+ case f input "src" of
+ Left msg -> error (show msg)
+ Right p -> p
+
+readJs :: String -> AST.JSAST
+readJs = readJsWith parse
+
+readJsModule :: String -> AST.JSAST
+readJsModule = readJsWith parseModule
+
+-- | Parse the given file.
+-- For UTF-8 support, make sure your locale is set such that
+-- "System.IO.localeEncoding" returns "utf8"
+parseFile :: FilePath -> IO AST.JSAST
+parseFile filename =
+ do
+ x <- readFile filename
+ return $ readJs x
+
+-- | Parse the given file, explicitly setting the encoding to UTF8
+-- when reading it
+parseFileUtf8 :: FilePath -> IO AST.JSAST
+parseFileUtf8 filename =
+ do
+ h <- openFile filename ReadMode
+ hSetEncoding h utf8
+ x <- hGetContents h
+ return $ readJs x
+
+showStripped :: AST.JSAST -> String
+showStripped = AST.showStripped
+
+showStrippedMaybe :: Show a => Either a AST.JSAST -> String
+showStrippedMaybe maybeAst =
+ case maybeAst of
+ Left msg -> "Left (" ++ show msg ++ ")"
+ Right p -> "Right (" ++ AST.showStripped p ++ ")"
+
+-- | Parse one compound statement, or a sequence of simple statements.
+-- Generally used for interactive input, such as from the command line of an interpreter.
+-- Return comments in addition to the parsed statements.
+parseUsing ::
+ Alex AST.JSAST -- ^ The parser to be used
+ -> String -- ^ The input stream (Javascript source code).
+ -> String -- ^ The name of the Javascript source (filename or input device).
+ -> Either String AST.JSAST
+ -- ^ An error or maybe the abstract syntax tree (AST) of zero
+ -- or more Javascript statements, plus comments.
+
+parseUsing p input _srcName = runAlex input p
--- /dev/null
+{-# OPTIONS #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : Language.JavaScript.ParserMonad
+-- Copyright : (c) 2012 Alan Zimmerman
+-- License : BSD-style
+-- Stability : experimental
+-- Portability : ghc
+--
+-- Monad support for JavaScript parser and lexer.
+-----------------------------------------------------------------------------
+
+module Language.JavaScript.Parser.ParserMonad
+ ( AlexUserState(..)
+ , alexInitUserState
+ ) where
+
+import Language.JavaScript.Parser.Token
+import Language.JavaScript.Parser.SrcLocation
+
+data AlexUserState = AlexUserState
+ { previousToken :: !Token -- ^the previous token
+ , comment :: [Token] -- ^the previous comment, if any
+ , inTemplate :: Bool -- ^whether the parser is expecting template characters
+ }
+
+alexInitUserState :: AlexUserState
+alexInitUserState = AlexUserState
+ { previousToken = initToken
+ , comment = []
+ , inTemplate = False
+ }
+
+initToken :: Token
+initToken = CommentToken tokenPosnEmpty "" []
--- /dev/null
+{-# LANGUAGE DeriveDataTypeable #-}
+module Language.JavaScript.Parser.SrcLocation (
+ TokenPosn(..)
+ , tokenPosnEmpty
+ ) where
+
+import Data.Data
+
+-- | `TokenPosn' records the location of a token in the input text. It has three
+-- fields: the address (number of characters preceding the token), line number
+-- and column of a token within the file.
+-- Note: The lexer assumes the usual eight character tab stops.
+
+data TokenPosn = TokenPn !Int -- address (number of characters preceding the token)
+ !Int -- line number
+ !Int -- column
+ deriving (Eq,Show, Read, Data, Typeable)
+
+tokenPosnEmpty :: TokenPosn
+tokenPosnEmpty = TokenPn 0 0 0
+
--- /dev/null
+{-# LANGUAGE CPP, DeriveDataTypeable #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : Language.Python.Common.Token
+-- Copyright : (c) 2009 Bernie Pope
+-- License : BSD-style
+-- Maintainer : bjpop@csse.unimelb.edu.au
+-- Stability : experimental
+-- Portability : ghc
+--
+-- Lexical tokens for the Python lexer. Contains the superset of tokens from
+-- version 2 and version 3 of Python (they are mostly the same).
+-----------------------------------------------------------------------------
+
+module Language.JavaScript.Parser.Token
+ (
+ -- * The tokens
+ Token (..)
+ , CommentAnnotation (..)
+ -- * String conversion
+ , debugTokenString
+ -- * Classification
+ -- TokenClass (..),
+ ) where
+
+import Data.Data
+import Language.JavaScript.Parser.SrcLocation
+
+data CommentAnnotation
+ = CommentA TokenPosn String
+ | WhiteSpace TokenPosn String
+ | NoComment
+ deriving (Eq, Show, Typeable, Data, Read)
+
+-- | Lexical tokens.
+-- Each may be annotated with any comment occurring between the prior token and this one
+data Token
+ -- Comment
+ = CommentToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] } -- ^ Single line comment.
+ | WsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] } -- ^ White space, for preservation.
+
+ -- Identifiers
+ | IdentifierToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] } -- ^ Identifier.
+
+ -- Javascript Literals
+
+ | DecimalToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- ^ Literal: Decimal
+ | HexIntegerToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- ^ Literal: Hexadecimal Integer
+ | OctalToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- ^ Literal: Octal Integer
+ | StringToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- ^ Literal: string, delimited by either single or double quotes
+ | RegExToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- ^ Literal: Regular Expression
+
+ -- Keywords
+ | AsyncToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | AwaitToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | BreakToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | CaseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | CatchToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ClassToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ConstToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | LetToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ContinueToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | DebuggerToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | DefaultToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | DeleteToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | DoToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ElseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | EnumToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ExtendsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | FalseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | FinallyToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ForToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | FunctionToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | FromToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | IfToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | InToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | InstanceofToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | NewToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | NullToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | OfToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ReturnToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | StaticToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | SuperToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | SwitchToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ThisToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ThrowToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TrueToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TryToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TypeofToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | VarToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | VoidToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | WhileToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | YieldToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ImportToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | WithToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | ExportToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- Future reserved words
+ | FutureToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ -- Needed, not sure what they are though.
+ | GetToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | SetToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+
+ -- Delimiters
+ -- Operators
+ | AutoSemiToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | SemiColonToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | CommaToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | HookToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | ColonToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | OrToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | AndToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | BitwiseOrToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | BitwiseXorToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | BitwiseAndToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | StrictEqToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | EqToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | TimesAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | DivideAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | ModAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | PlusAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | MinusAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LshAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | RshAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | UrshAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | AndAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | XorAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | OrAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | SimpleAssignToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | StrictNeToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | NeToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LshToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LeToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LtToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | UrshToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | RshToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | GeToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | GtToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | IncrementToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | DecrementToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | PlusToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | MinusToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | MulToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | DivToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | ModToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | NotToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | BitwiseNotToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | ArrowToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | SpreadToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | DotToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LeftBracketToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | RightBracketToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LeftCurlyToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | RightCurlyToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | LeftParenToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | RightParenToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+ | CondcommentEndToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] }
+
+ -- Template literal lexical components
+ | NoSubstitutionTemplateToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TemplateHeadToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TemplateMiddleToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TemplateTailToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+
+ -- Special cases
+ | AsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, tokenComment :: ![CommentAnnotation] }
+ | TailToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] } -- ^ Stuff between last JS and EOF
+ | EOFToken { tokenSpan :: !TokenPosn, tokenComment :: ![CommentAnnotation] } -- ^ End of file
+ deriving (Eq, Show, Typeable)
+
+
+-- | Produce a string from a token containing detailed information. Mainly intended for debugging.
+debugTokenString :: Token -> String
+debugTokenString = takeWhile (/= ' ') . show
--- /dev/null
+
+{-# LANGUAGE CPP, FlexibleInstances, NoOverloadedStrings, TypeSynonymInstances #-}
+
+module Language.JavaScript.Pretty.Printer
+ ( -- * Printing
+ renderJS
+ , renderToString
+ , renderToText
+ ) where
+
+import Blaze.ByteString.Builder (Builder, toLazyByteString)
+import Data.List
+#if ! MIN_VERSION_base(4,13,0)
+import Data.Monoid (mempty)
+import Data.Semigroup ((<>))
+#endif
+import Data.Text.Lazy (Text)
+import Language.JavaScript.Parser.AST
+import Language.JavaScript.Parser.SrcLocation
+import Language.JavaScript.Parser.Token
+import qualified Blaze.ByteString.Builder.Char.Utf8 as BS
+import qualified Data.ByteString.Lazy as LB
+import qualified Data.Text.Lazy.Encoding as LT
+import qualified Codec.Binary.UTF8.String as US
+
+-- ---------------------------------------------------------------------
+
+data PosAccum = PosAccum (Int, Int) Builder
+
+-- ---------------------------------------------------------------------
+-- Pretty printer stuff via blaze-builder
+
+str :: String -> Builder
+str = BS.fromString
+
+-- ---------------------------------------------------------------------
+
+renderJS :: JSAST -> Builder
+renderJS node = bb
+ where
+ PosAccum _ bb = PosAccum (1,1) mempty |> node
+
+
+renderToString :: JSAST -> String
+-- need to be careful to not lose the unicode encoding on output
+renderToString js = US.decode $ LB.unpack $ toLazyByteString $ renderJS js
+
+renderToText :: JSAST -> Text
+-- need to be careful to not lose the unicode encoding on output
+renderToText = LT.decodeUtf8 . toLazyByteString . renderJS
+
+
+class RenderJS a where
+ -- Render node.
+ (|>) :: PosAccum -> a -> PosAccum
+
+
+instance RenderJS JSAST where
+ (|>) pacc (JSAstProgram xs a) = pacc |> xs |> a
+ (|>) pacc (JSAstModule xs a) = pacc |> xs |> a
+ (|>) pacc (JSAstStatement s a) = pacc |> s |> a
+ (|>) pacc (JSAstExpression e a) = pacc |> e |> a
+ (|>) pacc (JSAstLiteral x a) = pacc |> x |> a
+
+instance RenderJS JSExpression where
+ -- Terminals
+ (|>) pacc (JSIdentifier annot s) = pacc |> annot |> s
+ (|>) pacc (JSDecimal annot i) = pacc |> annot |> i
+ (|>) pacc (JSLiteral annot l) = pacc |> annot |> l
+ (|>) pacc (JSHexInteger annot i) = pacc |> annot |> i
+ (|>) pacc (JSOctal annot i) = pacc |> annot |> i
+ (|>) pacc (JSStringLiteral annot s) = pacc |> annot |> s
+ (|>) pacc (JSRegEx annot s) = pacc |> annot |> s
+
+ -- Non-Terminals
+ (|>) pacc (JSArrayLiteral als xs ars) = pacc |> als |> "[" |> xs |> ars |> "]"
+ (|>) pacc (JSArrowExpression xs a x) = pacc |> xs |> a |> "=>" |> x
+ (|>) pacc (JSAssignExpression lhs op rhs) = pacc |> lhs |> op |> rhs
+ (|>) pacc (JSAwaitExpression a e) = pacc |> a |> "await" |> e
+ (|>) pacc (JSCallExpression ex lb xs rb) = pacc |> ex |> lb |> "(" |> xs |> rb |> ")"
+ (|>) pacc (JSCallExpressionDot ex os xs) = pacc |> ex |> os |> "." |> xs
+ (|>) pacc (JSCallExpressionSquare ex als xs ars) = pacc |> ex |> als |> "[" |> xs |> ars |> "]"
+ (|>) pacc (JSClassExpression annot n h lb xs rb) = pacc |> annot |> "class" |> n |> h |> lb |> "{" |> xs |> rb |> "}"
+ (|>) pacc (JSCommaExpression le c re) = pacc |> le |> c |> "," |> re
+ (|>) pacc (JSExpressionBinary lhs op rhs) = pacc |> lhs |> op |> rhs
+ (|>) pacc (JSExpressionParen alp e arp) = pacc |> alp |> "(" |> e |> arp |> ")"
+ (|>) pacc (JSExpressionPostfix xs op) = pacc |> xs |> op
+ (|>) pacc (JSExpressionTernary cond h v1 c v2) = pacc |> cond |> h |> "?" |> v1 |> c |> ":" |> v2
+ (|>) pacc (JSFunctionExpression annot n lb x2s rb x3) = pacc |> annot |> "function" |> n |> lb |> "(" |> x2s |> rb |> ")" |> x3
+ (|>) pacc (JSGeneratorExpression annot s n lb x2s rb x3) = pacc |> annot |> "function" |> s |> "*" |> n |> lb |> "(" |> x2s |> rb |> ")" |> x3
+ (|>) pacc (JSMemberDot xs dot n) = pacc |> xs |> "." |> dot |> n
+ (|>) pacc (JSMemberExpression e lb a rb) = pacc |> e |> lb |> "(" |> a |> rb |> ")"
+ (|>) pacc (JSMemberNew a lb n rb s) = pacc |> a |> "new" |> lb |> "(" |> n |> rb |> ")" |> s
+ (|>) pacc (JSMemberSquare xs als e ars) = pacc |> xs |> als |> "[" |> e |> ars |> "]"
+ (|>) pacc (JSNewExpression n e) = pacc |> n |> "new" |> e
+ (|>) pacc (JSObjectLiteral alb xs arb) = pacc |> alb |> "{" |> xs |> arb |> "}"
+ (|>) pacc (JSTemplateLiteral t a h ps) = pacc |> t |> a |> h |> ps
+ (|>) pacc (JSUnaryExpression op x) = pacc |> op |> x
+ (|>) pacc (JSVarInitExpression x1 x2) = pacc |> x1 |> x2
+ (|>) pacc (JSYieldExpression y x) = pacc |> y |> "yield" |> x
+ (|>) pacc (JSYieldFromExpression y s x) = pacc |> y |> "yield" |> s |> "*" |> x
+ (|>) pacc (JSSpreadExpression a e) = pacc |> a |> "..." |> e
+
+instance RenderJS JSArrowParameterList where
+ (|>) pacc (JSUnparenthesizedArrowParameter p) = pacc |> p
+ (|>) pacc (JSParenthesizedArrowParameterList lb ps rb) = pacc |> lb |> "(" |> ps |> ")" |> rb
+-- -----------------------------------------------------------------------------
+-- Need an instance of RenderJS for every component of every JSExpression or JSAnnot
+-- constuctor.
+-- -----------------------------------------------------------------------------
+
+instance RenderJS JSAnnot where
+ (|>) pacc (JSAnnot p cs) = pacc |> cs |> p
+ (|>) pacc JSNoAnnot = pacc
+ (|>) pacc JSAnnotSpace = pacc |> " "
+
+instance RenderJS String where
+ (|>) (PosAccum (r,c) bb) s = PosAccum (r',c') (bb <> str s)
+ where
+ (r',c') = foldl' (\(row,col) ch -> go (row,col) ch) (r,c) s
+
+ go (rx,_) '\n' = (rx+1,1)
+ go (rx,cx) '\t' = (rx,cx+8)
+ go (rx,cx) _ = (rx,cx+1)
+
+
+instance RenderJS TokenPosn where
+ (|>) (PosAccum (lcur,ccur) bb) (TokenPn _ ltgt ctgt) = PosAccum (lnew,cnew) (bb <> bb')
+ where
+ (bbline,ccur') = if lcur < ltgt then (str (replicate (ltgt - lcur) '\n'),1) else (mempty,ccur)
+ bbcol = if ccur' < ctgt then str (replicate (ctgt - ccur') ' ') else mempty
+ bb' = bbline <> bbcol
+ lnew = if lcur < ltgt then ltgt else lcur
+ cnew = if ccur' < ctgt then ctgt else ccur'
+
+
+instance RenderJS [CommentAnnotation] where
+ (|>) = foldl' (|>)
+
+
+instance RenderJS CommentAnnotation where
+ (|>) pacc NoComment = pacc
+ (|>) pacc (CommentA p s) = pacc |> p |> s
+ (|>) pacc (WhiteSpace p s) = pacc |> p |> s
+
+
+instance RenderJS [JSExpression] where
+ (|>) = foldl' (|>)
+
+
+instance RenderJS JSBinOp where
+ (|>) pacc (JSBinOpAnd annot) = pacc |> annot |> "&&"
+ (|>) pacc (JSBinOpBitAnd annot) = pacc |> annot |> "&"
+ (|>) pacc (JSBinOpBitOr annot) = pacc |> annot |> "|"
+ (|>) pacc (JSBinOpBitXor annot) = pacc |> annot |> "^"
+ (|>) pacc (JSBinOpDivide annot) = pacc |> annot |> "/"
+ (|>) pacc (JSBinOpEq annot) = pacc |> annot |> "=="
+ (|>) pacc (JSBinOpGe annot) = pacc |> annot |> ">="
+ (|>) pacc (JSBinOpGt annot) = pacc |> annot |> ">"
+ (|>) pacc (JSBinOpIn annot) = pacc |> annot |> "in"
+ (|>) pacc (JSBinOpInstanceOf annot) = pacc |> annot |> "instanceof"
+ (|>) pacc (JSBinOpLe annot) = pacc |> annot |> "<="
+ (|>) pacc (JSBinOpLsh annot) = pacc |> annot |> "<<"
+ (|>) pacc (JSBinOpLt annot) = pacc |> annot |> "<"
+ (|>) pacc (JSBinOpMinus annot) = pacc |> annot |> "-"
+ (|>) pacc (JSBinOpMod annot) = pacc |> annot |> "%"
+ (|>) pacc (JSBinOpNeq annot) = pacc |> annot |> "!="
+ (|>) pacc (JSBinOpOf annot) = pacc |> annot |> "of"
+ (|>) pacc (JSBinOpOr annot) = pacc |> annot |> "||"
+ (|>) pacc (JSBinOpPlus annot) = pacc |> annot |> "+"
+ (|>) pacc (JSBinOpRsh annot) = pacc |> annot |> ">>"
+ (|>) pacc (JSBinOpStrictEq annot) = pacc |> annot |> "==="
+ (|>) pacc (JSBinOpStrictNeq annot) = pacc |> annot |> "!=="
+ (|>) pacc (JSBinOpTimes annot) = pacc |> annot |> "*"
+ (|>) pacc (JSBinOpUrsh annot) = pacc |> annot |> ">>>"
+
+
+instance RenderJS JSUnaryOp where
+ (|>) pacc (JSUnaryOpDecr annot) = pacc |> annot |> "--"
+ (|>) pacc (JSUnaryOpDelete annot) = pacc |> annot |> "delete"
+ (|>) pacc (JSUnaryOpIncr annot) = pacc |> annot |> "++"
+ (|>) pacc (JSUnaryOpMinus annot) = pacc |> annot |> "-"
+ (|>) pacc (JSUnaryOpNot annot) = pacc |> annot |> "!"
+ (|>) pacc (JSUnaryOpPlus annot) = pacc |> annot |> "+"
+ (|>) pacc (JSUnaryOpTilde annot) = pacc |> annot |> "~"
+ (|>) pacc (JSUnaryOpTypeof annot) = pacc |> annot |> "typeof"
+ (|>) pacc (JSUnaryOpVoid annot) = pacc |> annot |> "void"
+
+
+instance RenderJS JSAssignOp where
+ (|>) pacc (JSAssign annot) = pacc |> annot |> "="
+ (|>) pacc (JSTimesAssign annot) = pacc |> annot |> "*="
+ (|>) pacc (JSDivideAssign annot) = pacc |> annot |> "/="
+ (|>) pacc (JSModAssign annot) = pacc |> annot |> "%="
+ (|>) pacc (JSPlusAssign annot) = pacc |> annot |> "+="
+ (|>) pacc (JSMinusAssign annot) = pacc |> annot |> "-="
+ (|>) pacc (JSLshAssign annot) = pacc |> annot |> "<<="
+ (|>) pacc (JSRshAssign annot) = pacc |> annot |> ">>="
+ (|>) pacc (JSUrshAssign annot) = pacc |> annot |> ">>>="
+ (|>) pacc (JSBwAndAssign annot) = pacc |> annot |> "&="
+ (|>) pacc (JSBwXorAssign annot) = pacc |> annot |> "^="
+ (|>) pacc (JSBwOrAssign annot) = pacc |> annot |> "|="
+
+
+instance RenderJS JSSemi where
+ (|>) pacc (JSSemi annot) = pacc |> annot |> ";"
+ (|>) pacc JSSemiAuto = pacc
+
+
+instance RenderJS JSTryCatch where
+ (|>) pacc (JSCatch anc alb x1 arb x3) = pacc |> anc |> "catch" |> alb |> "(" |> x1 |> arb |> ")" |> x3
+ (|>) pacc (JSCatchIf anc alb x1 aif ex arb x3) = pacc |> anc |> "catch" |> alb |> "(" |> x1 |> aif |> "if" |> ex |> arb |> ")" |> x3
+
+instance RenderJS [JSTryCatch] where
+ (|>) = foldl' (|>)
+
+instance RenderJS JSTryFinally where
+ (|>) pacc (JSFinally annot x) = pacc |> annot |> "finally" |> x
+ (|>) pacc JSNoFinally = pacc
+
+instance RenderJS JSSwitchParts where
+ (|>) pacc (JSCase annot x1 c x2s) = pacc |> annot |> "case" |> x1 |> c |> ":" |> x2s
+ (|>) pacc (JSDefault annot c xs) = pacc |> annot |> "default" |> c |> ":" |> xs
+
+instance RenderJS [JSSwitchParts] where
+ (|>) = foldl' (|>)
+
+instance RenderJS JSStatement where
+ (|>) pacc (JSStatementBlock alb blk arb s) = pacc |> alb |> "{" |> blk |> arb |> "}" |> s
+ (|>) pacc (JSBreak annot mi s) = pacc |> annot |> "break" |> mi |> s
+ (|>) pacc (JSClass annot n h lb xs rb s) = pacc |> annot |> "class" |> n |> h |> lb |> "{" |> xs |> rb |> "}" |> s
+ (|>) pacc (JSContinue annot mi s) = pacc |> annot |> "continue" |> mi |> s
+ (|>) pacc (JSConstant annot xs s) = pacc |> annot |> "const" |> xs |> s
+ (|>) pacc (JSDoWhile ad x1 aw alb x2 arb x3) = pacc |> ad |> "do" |> x1 |> aw |> "while" |> alb |> "(" |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSEmptyStatement a) = pacc |> a |> ";"
+ (|>) pacc (JSFor af alb x1s s1 x2s s2 x3s arb x4) = pacc |> af |> "for" |> alb |> "(" |> x1s |> s1 |> ";" |> x2s |> s2 |> ";" |> x3s |> arb |> ")" |> x4
+ (|>) pacc (JSForIn af alb x1s i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> x1s |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForVar af alb v x1s s1 x2s s2 x3s arb x4) = pacc |> af |> "for" |> alb |> "(" |> "var" |> v |> x1s |> s1 |> ";" |> x2s |> s2 |> ";" |> x3s |> arb |> ")" |> x4
+ (|>) pacc (JSForVarIn af alb v x1 i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> "var" |> v |> x1 |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForLet af alb v x1s s1 x2s s2 x3s arb x4) = pacc |> af |> "for" |> alb |> "(" |> "let" |> v |> x1s |> s1 |> ";" |> x2s |> s2 |> ";" |> x3s |> arb |> ")" |> x4
+ (|>) pacc (JSForLetIn af alb v x1 i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> "let" |> v |> x1 |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForLetOf af alb v x1 i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> "let" |> v |> x1 |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForConst af alb v x1s s1 x2s s2 x3s arb x4) = pacc |> af |> "for" |> alb |> "(" |> "const" |> v |> x1s |> s1 |> ";" |> x2s |> s2 |> ";" |> x3s |> arb |> ")" |> x4
+ (|>) pacc (JSForConstIn af alb v x1 i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> "const" |> v |> x1 |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForConstOf af alb v x1 i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> "const" |> v |> x1 |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForOf af alb x1s i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> x1s |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSForVarOf af alb v x1 i x2 arb x3) = pacc |> af |> "for" |> alb |> "(" |> "var" |> v |> x1 |> i |> x2 |> arb |> ")" |> x3
+ (|>) pacc (JSAsyncFunction aa af n alb x2s arb x3 s) = pacc |> aa |> "async" |> af |> "function" |> n |> alb |> "(" |> x2s |> arb |> ")" |> x3 |> s
+ (|>) pacc (JSFunction af n alb x2s arb x3 s) = pacc |> af |> "function" |> n |> alb |> "(" |> x2s |> arb |> ")" |> x3 |> s
+ (|>) pacc (JSGenerator af as n alb x2s arb x3 s) = pacc |> af |> "function" |> as |> "*" |> n |> alb |> "(" |> x2s |> arb |> ")" |> x3 |> s
+ (|>) pacc (JSIf annot alb x1 arb x2s) = pacc |> annot |> "if" |> alb |> "(" |> x1 |> arb |> ")" |> x2s
+ (|>) pacc (JSIfElse annot alb x1 arb x2s ea x3s) = pacc |> annot |> "if" |> alb |> "(" |> x1 |> arb |> ")" |> x2s |> ea |> "else" |> x3s
+ (|>) pacc (JSLabelled l c v) = pacc |> l |> c |> ":" |> v
+ (|>) pacc (JSLet annot xs s) = pacc |> annot |> "let" |> xs |> s
+ (|>) pacc (JSExpressionStatement l s) = pacc |> l |> s
+ (|>) pacc (JSAssignStatement lhs op rhs s) = pacc |> lhs |> op |> rhs |> s
+ (|>) pacc (JSMethodCall e lp a rp s) = pacc |> e |> lp |> "(" |> a |> rp |> ")" |> s
+ (|>) pacc (JSReturn annot me s) = pacc |> annot |> "return" |> me |> s
+ (|>) pacc (JSSwitch annot alp x arp alb x2 arb s) = pacc |> annot |> "switch" |> alp |> "(" |> x |> arp |> ")" |> alb |> "{" |> x2 |> arb |> "}" |> s
+ (|>) pacc (JSThrow annot x s) = pacc |> annot |> "throw" |> x |> s
+ (|>) pacc (JSTry annot tb tcs tf) = pacc |> annot |> "try" |> tb |> tcs |> tf
+ (|>) pacc (JSVariable annot xs s) = pacc |> annot |> "var" |> xs |> s
+ (|>) pacc (JSWhile annot alp x1 arp x2) = pacc |> annot |> "while" |> alp |> "(" |> x1 |> arp |> ")" |> x2
+ (|>) pacc (JSWith annot alp x1 arp x s) = pacc |> annot |> "with" |> alp |> "(" |> x1 |> arp |> ")" |> x |> s
+
+instance RenderJS [JSStatement] where
+ (|>) = foldl' (|>)
+
+instance RenderJS [JSModuleItem] where
+ (|>) = foldl' (|>)
+
+instance RenderJS JSModuleItem where
+ (|>) pacc (JSModuleImportDeclaration annot decl) = pacc |> annot |> "import" |> decl
+ (|>) pacc (JSModuleExportDeclaration annot decl) = pacc |> annot |> "export" |> decl
+ (|>) pacc (JSModuleStatementListItem s) = pacc |> s
+
+instance RenderJS JSBlock where
+ (|>) pacc (JSBlock alb ss arb) = pacc |> alb |> "{" |> ss |> arb |> "}"
+
+instance RenderJS JSObjectProperty where
+ (|>) pacc (JSPropertyNameandValue n c vs) = pacc |> n |> c |> ":" |> vs
+ (|>) pacc (JSPropertyIdentRef a s) = pacc |> a |> s
+ (|>) pacc (JSObjectMethod m) = pacc |> m
+
+instance RenderJS JSMethodDefinition where
+ (|>) pacc (JSMethodDefinition n alp ps arp b) = pacc |> n |> alp |> "(" |> ps |> arp |> ")" |> b
+ (|>) pacc (JSGeneratorMethodDefinition s n alp ps arp b) = pacc |> s |> "*" |> n |> alp |> "(" |> ps |> arp |> ")" |> b
+ (|>) pacc (JSPropertyAccessor s n alp ps arp b) = pacc |> s |> n |> alp |> "(" |> ps |> arp |> ")" |> b
+
+instance RenderJS JSPropertyName where
+ (|>) pacc (JSPropertyIdent a s) = pacc |> a |> s
+ (|>) pacc (JSPropertyString a s) = pacc |> a |> s
+ (|>) pacc (JSPropertyNumber a s) = pacc |> a |> s
+ (|>) pacc (JSPropertyComputed lb x rb) = pacc |> lb |> "[" |> x |> rb |> "]"
+
+instance RenderJS JSAccessor where
+ (|>) pacc (JSAccessorGet annot) = pacc |> annot |> "get"
+ (|>) pacc (JSAccessorSet annot) = pacc |> annot |> "set"
+
+instance RenderJS JSArrayElement where
+ (|>) pacc (JSArrayElement e) = pacc |> e
+ (|>) pacc (JSArrayComma a) = pacc |> a |> ","
+
+instance RenderJS [JSArrayElement] where
+ (|>) = foldl' (|>)
+
+instance RenderJS JSImportDeclaration where
+ (|>) pacc (JSImportDeclaration imp from annot) = pacc |> imp |> from |> annot
+ (|>) pacc (JSImportDeclarationBare annot m s) = pacc |> annot |> m |> s
+
+instance RenderJS JSImportClause where
+ (|>) pacc (JSImportClauseDefault x) = pacc |> x
+ (|>) pacc (JSImportClauseNameSpace x) = pacc |> x
+ (|>) pacc (JSImportClauseNamed x) = pacc |> x
+ (|>) pacc (JSImportClauseDefaultNameSpace x1 annot x2) = pacc |> x1 |> annot |> "," |> x2
+ (|>) pacc (JSImportClauseDefaultNamed x1 annot x2) = pacc |> x1 |> annot |> "," |> x2
+
+instance RenderJS JSFromClause where
+ (|>) pacc (JSFromClause from annot m) = pacc |> from |> "from" |> annot |> m
+
+instance RenderJS JSImportNameSpace where
+ (|>) pacc (JSImportNameSpace star annot x) = pacc |> star |> annot |> "as" |> x
+
+instance RenderJS JSImportsNamed where
+ (|>) pacc (JSImportsNamed lb xs rb) = pacc |> lb |> "{" |> xs |> rb |> "}"
+
+instance RenderJS JSImportSpecifier where
+ (|>) pacc (JSImportSpecifier x1) = pacc |> x1
+ (|>) pacc (JSImportSpecifierAs x1 annot x2) = pacc |> x1 |> annot |> "as" |> x2
+
+instance RenderJS JSExportDeclaration where
+ (|>) pacc (JSExport x1 s) = pacc |> x1 |> s
+ (|>) pacc (JSExportLocals xs semi) = pacc |> xs |> semi
+ (|>) pacc (JSExportFrom xs from semi) = pacc |> xs |> from |> semi
+
+instance RenderJS JSExportClause where
+ (|>) pacc (JSExportClause alb JSLNil arb) = pacc |> alb |> "{" |> arb |> "}"
+ (|>) pacc (JSExportClause alb s arb) = pacc |> alb |> "{" |> s |> arb |> "}"
+
+instance RenderJS JSExportSpecifier where
+ (|>) pacc (JSExportSpecifier i) = pacc |> i
+ (|>) pacc (JSExportSpecifierAs x1 annot x2) = pacc |> x1 |> annot |> "as" |> x2
+
+instance RenderJS a => RenderJS (JSCommaList a) where
+ (|>) pacc (JSLCons pl a i) = pacc |> pl |> a |> "," |> i
+ (|>) pacc (JSLOne i) = pacc |> i
+ (|>) pacc JSLNil = pacc
+
+instance RenderJS a => RenderJS (JSCommaTrailingList a) where
+ (|>) pacc (JSCTLComma xs a) = pacc |> xs |> a |> ","
+ (|>) pacc (JSCTLNone xs) = pacc |> xs
+
+instance RenderJS JSIdent where
+ (|>) pacc (JSIdentName a s) = pacc |> a |> s
+ (|>) pacc JSIdentNone = pacc
+
+instance RenderJS (Maybe JSExpression) where
+ (|>) pacc (Just e) = pacc |> e
+ (|>) pacc Nothing = pacc
+
+instance RenderJS JSVarInitializer where
+ (|>) pacc (JSVarInit a x) = pacc |> a |> "=" |> x
+ (|>) pacc JSVarInitNone = pacc
+
+instance RenderJS [JSTemplatePart] where
+ (|>) = foldl' (|>)
+
+instance RenderJS JSTemplatePart where
+ (|>) pacc (JSTemplatePart e a s) = pacc |> e |> a |> s
+
+instance RenderJS JSClassHeritage where
+ (|>) pacc (JSExtends a e) = pacc |> a |> "extends" |> e
+ (|>) pacc JSExtendsNone = pacc
+
+instance RenderJS [JSClassElement] where
+ (|>) = foldl' (|>)
+
+instance RenderJS JSClassElement where
+ (|>) pacc (JSClassInstanceMethod m) = pacc |> m
+ (|>) pacc (JSClassStaticMethod a m) = pacc |> a |> "static" |> m
+ (|>) pacc (JSClassSemi a) = pacc |> a |> ";"
+
+-- EOF
--- /dev/null
+{-# LANGUAGE CPP, FlexibleInstances #-}
+
+module Language.JavaScript.Process.Minify
+ ( -- * Minify
+ minifyJS
+ ) where
+
+#if ! MIN_VERSION_base(4,13,0)
+import Control.Applicative ((<$>))
+#endif
+
+import Language.JavaScript.Parser.AST
+import Language.JavaScript.Parser.SrcLocation
+import Language.JavaScript.Parser.Token
+
+-- ---------------------------------------------------------------------
+
+minifyJS :: JSAST -> JSAST
+minifyJS (JSAstProgram xs _) = JSAstProgram (fixStatementList noSemi xs) emptyAnnot
+minifyJS (JSAstModule xs _) = JSAstModule (map (fix emptyAnnot) xs) emptyAnnot
+minifyJS (JSAstStatement (JSStatementBlock _ [s] _ _) _) = JSAstStatement (fixStmtE noSemi s) emptyAnnot
+minifyJS (JSAstStatement s _) = JSAstStatement (fixStmtE noSemi s) emptyAnnot
+minifyJS (JSAstExpression e _) = JSAstExpression (fixEmpty e) emptyAnnot
+minifyJS (JSAstLiteral s _) = JSAstLiteral (fixEmpty s) emptyAnnot
+
+-- ---------------------------------------------------------------------
+
+class MinifyJS a where
+ fix :: JSAnnot -> a -> a
+
+
+fixEmpty :: MinifyJS a => a -> a
+fixEmpty = fix emptyAnnot
+
+fixSpace :: MinifyJS a => a -> a
+fixSpace = fix spaceAnnot
+
+-- -----------------------------------------------------------------------------
+-- During minification, Javascript statements may need to have explicit
+-- semicolons inserted between them, so that simply adding a JSStatement
+-- instance for the MinifyJS typeclass would not be sufficient.
+
+fixStmt :: JSAnnot -> JSSemi -> JSStatement -> JSStatement
+fixStmt a s (JSStatementBlock _lb ss _rb _) = fixStatementBlock a s ss
+fixStmt a s (JSBreak _ i _) = JSBreak a (fixSpace i) s
+fixStmt a s (JSClass _ n h _ ms _ _) = JSClass a (fixSpace n) (fixSpace h) emptyAnnot (fixEmpty ms) emptyAnnot s
+fixStmt a s (JSConstant _ ss _) = JSConstant a (fixVarList ss) s
+fixStmt a s (JSContinue _ i _) = JSContinue a (fixSpace i) s
+fixStmt a s (JSDoWhile _ st _ _ e _ _) = JSDoWhile a (mkStatementBlock noSemi st) emptyAnnot emptyAnnot (fixEmpty e) emptyAnnot s
+fixStmt a s (JSFor _ _ el1 _ el2 _ el3 _ st) = JSFor a emptyAnnot (fixEmpty el1) emptyAnnot (fixEmpty el2) emptyAnnot (fixEmpty el3) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForIn _ _ e1 op e2 _ st) = JSForIn a emptyAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForVar _ _ _ el1 _ el2 _ el3 _ st) = JSForVar a emptyAnnot spaceAnnot (fixEmpty el1) emptyAnnot (fixEmpty el2) emptyAnnot (fixEmpty el3) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForVarIn _ _ _ e1 op e2 _ st) = JSForVarIn a emptyAnnot spaceAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForLet _ _ _ el1 _ el2 _ el3 _ st) = JSForLet a emptyAnnot spaceAnnot (fixEmpty el1) emptyAnnot (fixEmpty el2) emptyAnnot (fixEmpty el3) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForLetIn _ _ _ e1 op e2 _ st) = JSForLetIn a emptyAnnot spaceAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForLetOf _ _ _ e1 op e2 _ st) = JSForLetOf a emptyAnnot spaceAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForConst _ _ _ el1 _ el2 _ el3 _ st) = JSForConst a emptyAnnot spaceAnnot (fixEmpty el1) emptyAnnot (fixEmpty el2) emptyAnnot (fixEmpty el3) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForConstIn _ _ _ e1 op e2 _ st) = JSForConstIn a emptyAnnot spaceAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForConstOf _ _ _ e1 op e2 _ st) = JSForConstOf a emptyAnnot spaceAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForOf _ _ e1 op e2 _ st) = JSForOf a emptyAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSForVarOf _ _ _ e1 op e2 _ st) = JSForVarOf a emptyAnnot spaceAnnot (fixEmpty e1) (fixSpace op) (fixSpace e2) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSAsyncFunction _ _ n _ ps _ blk _) = JSAsyncFunction a spaceAnnot (fixSpace n) emptyAnnot (fixEmpty ps) emptyAnnot (fixEmpty blk) s
+fixStmt a s (JSFunction _ n _ ps _ blk _) = JSFunction a (fixSpace n) emptyAnnot (fixEmpty ps) emptyAnnot (fixEmpty blk) s
+fixStmt a s (JSGenerator _ _ n _ ps _ blk _) = JSGenerator a emptyAnnot (fixEmpty n) emptyAnnot (fixEmpty ps) emptyAnnot (fixEmpty blk) s
+fixStmt a s (JSIf _ _ e _ st) = JSIf a emptyAnnot (fixEmpty e) emptyAnnot (fixIfElseBlock emptyAnnot s st)
+fixStmt a s (JSIfElse _ _ e _ (JSEmptyStatement _) _ sf) = JSIfElse a emptyAnnot (fixEmpty e) emptyAnnot (JSEmptyStatement emptyAnnot) emptyAnnot (fixStmt spaceAnnot s sf)
+fixStmt a s (JSIfElse _ _ e _ st _ sf) = JSIfElse a emptyAnnot (fixEmpty e) emptyAnnot (mkStatementBlock noSemi st) emptyAnnot (fixIfElseBlock spaceAnnot s sf)
+fixStmt a s (JSLabelled e _ st) = JSLabelled (fix a e) emptyAnnot (fixStmtE s st)
+fixStmt a s (JSLet _ xs _) = JSLet a (fixVarList xs) s
+fixStmt _ _ (JSEmptyStatement _) = JSEmptyStatement emptyAnnot
+fixStmt a s (JSExpressionStatement e _) = JSExpressionStatement (fix a e) s
+fixStmt a s (JSAssignStatement lhs op rhs _) = JSAssignStatement (fix a lhs) (fixEmpty op) (fixEmpty rhs) s
+fixStmt a s (JSMethodCall e _ args _ _) = JSMethodCall (fix a e) emptyAnnot (fixEmpty args) emptyAnnot s
+fixStmt a s (JSReturn _ me _) = JSReturn a (fixSpace me) s
+fixStmt a s (JSSwitch _ _ e _ _ sps _ _) = JSSwitch a emptyAnnot (fixEmpty e) emptyAnnot emptyAnnot (fixSwitchParts sps) emptyAnnot s
+fixStmt a s (JSThrow _ e _) = JSThrow a (fixSpace e) s
+fixStmt a _ (JSTry _ b tc tf) = JSTry a (fixEmpty b) (map fixEmpty tc) (fixEmpty tf)
+fixStmt a s (JSVariable _ ss _) = JSVariable a (fixVarList ss) s
+fixStmt a s (JSWhile _ _ e _ st) = JSWhile a emptyAnnot (fixEmpty e) emptyAnnot (fixStmt a s st)
+fixStmt a s (JSWith _ _ e _ st _) = JSWith a emptyAnnot (fixEmpty e) emptyAnnot (fixStmtE noSemi st) s
+
+
+fixIfElseBlock :: JSAnnot -> JSSemi -> JSStatement -> JSStatement
+fixIfElseBlock _ _ (JSStatementBlock _ [] _ _) = JSEmptyStatement emptyAnnot
+fixIfElseBlock a s st = fixStmt a s st
+
+fixStmtE :: JSSemi -> JSStatement -> JSStatement
+fixStmtE = fixStmt emptyAnnot
+
+-- Turn a single JSStatement into a JSStatementBlock.
+mkStatementBlock :: JSSemi -> JSStatement -> JSStatement
+mkStatementBlock s (JSStatementBlock _ blk _ _) = JSStatementBlock emptyAnnot (fixStatementList noSemi blk) emptyAnnot s
+mkStatementBlock s x = JSStatementBlock emptyAnnot [fixStmtE noSemi x] emptyAnnot s
+
+-- Filter a list of JSStatment, dropping JSEmptyStatement and empty
+-- JSStatementBlocks. If the resulting list contains only a single element,
+-- remove the enclosing JSStatementBlock and return the inner JSStatement.
+fixStatementBlock :: JSAnnot -> JSSemi -> [JSStatement] -> JSStatement
+fixStatementBlock a s ss =
+ case filter (not . isEmpty) ss of
+ [] -> JSStatementBlock emptyAnnot [] emptyAnnot s
+ [sx] -> fixStmt a s sx
+ sss -> JSStatementBlock emptyAnnot (fixStatementList noSemi sss) emptyAnnot s
+ where
+ isEmpty (JSEmptyStatement _) = True
+ isEmpty (JSStatementBlock _ [] _ _) = True
+ isEmpty _ = False
+
+-- Force semi-colons between statements, and make sure the last statement in a
+-- block has no semi-colon.
+fixStatementList :: JSSemi -> [JSStatement] -> [JSStatement]
+fixStatementList trailingSemi =
+ fixList emptyAnnot trailingSemi . filter (not . isRedundant)
+ where
+ isRedundant (JSStatementBlock _ [] _ _) = True
+ isRedundant (JSEmptyStatement _) = True
+ isRedundant _ = False
+
+ fixList _ _ [] = []
+ fixList a s [JSStatementBlock _ blk _ _] = fixList a s blk
+ fixList a s [x] = [fixStmt a s x]
+ fixList _ s (JSStatementBlock _ blk _ _:xs) = fixList emptyAnnot semi (filter (not . isRedundant) blk) ++ fixList emptyAnnot s xs
+ fixList a s (JSConstant _ vs1 _:JSConstant _ vs2 _: xs) = fixList a s (JSConstant spaceAnnot (concatCommaList vs1 vs2) s : xs)
+ fixList a s (JSVariable _ vs1 _:JSVariable _ vs2 _: xs) = fixList a s (JSVariable spaceAnnot (concatCommaList vs1 vs2) s : xs)
+ fixList a s (x1@JSFunction{}:x2@JSFunction{}:xs) = fixStmt a noSemi x1 : fixList newlineAnnot s (x2:xs)
+ fixList a s (x:xs) = fixStmt a semi x : fixList emptyAnnot s xs
+
+concatCommaList :: JSCommaList a -> JSCommaList a -> JSCommaList a
+concatCommaList xs JSLNil = xs
+concatCommaList JSLNil ys = ys
+concatCommaList xs (JSLOne y) = JSLCons xs emptyAnnot y
+concatCommaList xs ys =
+ let recurse (z, zs) = concatCommaList (JSLCons xs emptyAnnot z) zs
+ in maybe xs recurse $ headCommaList ys
+
+headCommaList :: JSCommaList a -> Maybe (a, JSCommaList a)
+headCommaList JSLNil = Nothing
+headCommaList (JSLOne x) = Just (x, JSLNil)
+headCommaList (JSLCons (JSLOne x) _ y) = Just (x, JSLOne y)
+headCommaList (JSLCons xs _ y) =
+ let rebuild (x, ys) = (x, JSLCons ys emptyAnnot y)
+ in rebuild <$> headCommaList xs
+
+-- -----------------------------------------------------------------------------
+-- JSExpression and the rest can use the MinifyJS typeclass.
+
+instance MinifyJS JSExpression where
+ -- Terminals
+ fix a (JSIdentifier _ s) = JSIdentifier a s
+ fix a (JSDecimal _ s) = JSDecimal a s
+ fix a (JSLiteral _ s) = JSLiteral a s
+ fix a (JSHexInteger _ s) = JSHexInteger a s
+ fix a (JSOctal _ s) = JSOctal a s
+ fix _ (JSStringLiteral _ s) = JSStringLiteral emptyAnnot s
+ fix _ (JSRegEx _ s) = JSRegEx emptyAnnot s
+
+ -- Non-Terminals
+ fix _ (JSArrayLiteral _ xs _) = JSArrayLiteral emptyAnnot (map fixEmpty xs) emptyAnnot
+ fix a (JSArrowExpression ps _ ss) = JSArrowExpression (fix a ps) emptyAnnot (fixStmt emptyAnnot noSemi ss)
+ fix a (JSAssignExpression lhs op rhs) = JSAssignExpression (fix a lhs) (fixEmpty op) (fixEmpty rhs)
+ fix a (JSAwaitExpression _ ex) = JSAwaitExpression a (fixSpace ex)
+ fix a (JSCallExpression ex _ xs _) = JSCallExpression (fix a ex) emptyAnnot (fixEmpty xs) emptyAnnot
+ fix a (JSCallExpressionDot ex _ xs) = JSCallExpressionDot (fix a ex) emptyAnnot (fixEmpty xs)
+ fix a (JSCallExpressionSquare ex _ xs _) = JSCallExpressionSquare (fix a ex) emptyAnnot (fixEmpty xs) emptyAnnot
+ fix a (JSClassExpression _ n h _ ms _) = JSClassExpression a (fixSpace n) (fixSpace h) emptyAnnot (fixEmpty ms) emptyAnnot
+ fix a (JSCommaExpression le _ re) = JSCommaExpression (fix a le) emptyAnnot (fixEmpty re)
+ fix a (JSExpressionBinary lhs op rhs) = fixBinOpExpression a op lhs rhs
+ fix _ (JSExpressionParen _ e _) = JSExpressionParen emptyAnnot (fixEmpty e) emptyAnnot
+ fix a (JSExpressionPostfix e op) = JSExpressionPostfix (fix a e) (fixEmpty op)
+ fix a (JSExpressionTernary cond _ v1 _ v2) = JSExpressionTernary (fix a cond) emptyAnnot (fixEmpty v1) emptyAnnot (fixEmpty v2)
+ fix a (JSFunctionExpression _ n _ x2s _ x3) = JSFunctionExpression a (fixSpace n) emptyAnnot (fixEmpty x2s) emptyAnnot (fixEmpty x3)
+ fix a (JSGeneratorExpression _ _ n _ x2s _ x3) = JSGeneratorExpression a emptyAnnot (fixEmpty n) emptyAnnot (fixEmpty x2s) emptyAnnot (fixEmpty x3)
+ fix a (JSMemberDot xs _ n) = JSMemberDot (fix a xs) emptyAnnot (fixEmpty n)
+ fix a (JSMemberExpression e _ args _) = JSMemberExpression (fix a e) emptyAnnot (fixEmpty args) emptyAnnot
+ fix a (JSMemberNew _ n _ s _) = JSMemberNew a (fix spaceAnnot n) emptyAnnot (fixEmpty s) emptyAnnot
+ fix a (JSMemberSquare xs _ e _) = JSMemberSquare (fix a xs) emptyAnnot (fixEmpty e) emptyAnnot
+ fix a (JSNewExpression _ e) = JSNewExpression a (fixSpace e)
+ fix _ (JSObjectLiteral _ xs _) = JSObjectLiteral emptyAnnot (fixEmpty xs) emptyAnnot
+ fix a (JSTemplateLiteral t _ s ps) = JSTemplateLiteral (fmap (fix a) t) emptyAnnot s (map fixEmpty ps)
+ fix a (JSUnaryExpression op x) = let (ta, fop) = fixUnaryOp a op in JSUnaryExpression fop (fix ta x)
+ fix a (JSVarInitExpression x1 x2) = JSVarInitExpression (fix a x1) (fixEmpty x2)
+ fix a (JSYieldExpression _ x) = JSYieldExpression a (fixSpace x)
+ fix a (JSYieldFromExpression _ _ x) = JSYieldFromExpression a emptyAnnot (fixEmpty x)
+ fix a (JSSpreadExpression _ e) = JSSpreadExpression a (fixEmpty e)
+
+instance MinifyJS JSArrowParameterList where
+ fix _ (JSUnparenthesizedArrowParameter p) = JSUnparenthesizedArrowParameter (fixEmpty p)
+ fix _ (JSParenthesizedArrowParameterList _ ps _) = JSParenthesizedArrowParameterList emptyAnnot (fixEmpty ps) emptyAnnot
+
+fixVarList :: JSCommaList JSExpression -> JSCommaList JSExpression
+fixVarList (JSLCons h _ v) = JSLCons (fixVarList h) emptyAnnot (fixEmpty v)
+fixVarList (JSLOne a) = JSLOne (fixSpace a)
+fixVarList JSLNil = JSLNil
+
+fixBinOpExpression :: JSAnnot -> JSBinOp -> JSExpression -> JSExpression -> JSExpression
+fixBinOpExpression a (JSBinOpPlus _) lhs rhs = fixBinOpPlus a lhs rhs
+fixBinOpExpression a (JSBinOpIn _) lhs rhs = JSExpressionBinary (fix a lhs) (JSBinOpIn spaceAnnot) (fix spaceAnnot rhs)
+fixBinOpExpression a (JSBinOpInstanceOf _) lhs rhs = JSExpressionBinary (fix a lhs) (JSBinOpInstanceOf spaceAnnot) (fix spaceAnnot rhs)
+fixBinOpExpression a op lhs rhs = JSExpressionBinary (fix a lhs) (fixEmpty op) (fixEmpty rhs)
+
+fixBinOpPlus :: JSAnnot -> JSExpression -> JSExpression -> JSExpression
+fixBinOpPlus a lhs rhs =
+ case (fix a lhs, fixEmpty rhs) of
+ (JSStringLiteral _ s1, JSStringLiteral _ s2) -> stringLitConcat (normalizeToSQ s1) (normalizeToSQ s2)
+ (nlhs, nrhs) -> JSExpressionBinary nlhs (JSBinOpPlus emptyAnnot) nrhs
+
+-- Concatenate two JSStringLiterals. Since the strings will include the string
+-- terminators (either single or double quotes) we use whatever terminator is
+-- used by the first string.
+stringLitConcat :: String -> String -> JSExpression
+stringLitConcat xs [] = JSStringLiteral emptyAnnot xs
+stringLitConcat [] ys = JSStringLiteral emptyAnnot ys
+stringLitConcat xall (_:yss) =
+ JSStringLiteral emptyAnnot (init xall ++ init yss ++ "'")
+
+-- Normalize a String. If its single quoted, just return it and its double quoted
+-- convert it to single quoted.
+normalizeToSQ :: String -> String
+normalizeToSQ str =
+ case str of
+ [] -> []
+ ('\'' : _) -> str
+ ('"' : xs) -> '\'' : convertSQ xs
+ other -> other -- Should not happen.
+ where
+ convertSQ [] = []
+ convertSQ [_] = "'"
+ convertSQ ('\'':xs) = '\\' : '\'' : convertSQ xs
+ convertSQ ('\\':'\"':xs) = '"' : convertSQ xs
+ convertSQ (x:xs) = x : convertSQ xs
+
+
+instance MinifyJS JSBinOp where
+ fix _ (JSBinOpAnd _) = JSBinOpAnd emptyAnnot
+ fix _ (JSBinOpBitAnd _) = JSBinOpBitAnd emptyAnnot
+ fix _ (JSBinOpBitOr _) = JSBinOpBitOr emptyAnnot
+ fix _ (JSBinOpBitXor _) = JSBinOpBitXor emptyAnnot
+ fix _ (JSBinOpDivide _) = JSBinOpDivide emptyAnnot
+ fix _ (JSBinOpEq _) = JSBinOpEq emptyAnnot
+ fix _ (JSBinOpGe _) = JSBinOpGe emptyAnnot
+ fix _ (JSBinOpGt _) = JSBinOpGt emptyAnnot
+ fix a (JSBinOpIn _) = JSBinOpIn a
+ fix a (JSBinOpInstanceOf _) = JSBinOpInstanceOf a
+ fix _ (JSBinOpLe _) = JSBinOpLe emptyAnnot
+ fix _ (JSBinOpLsh _) = JSBinOpLsh emptyAnnot
+ fix _ (JSBinOpLt _) = JSBinOpLt emptyAnnot
+ fix _ (JSBinOpMinus _) = JSBinOpMinus emptyAnnot
+ fix _ (JSBinOpMod _) = JSBinOpMod emptyAnnot
+ fix _ (JSBinOpNeq _) = JSBinOpNeq emptyAnnot
+ fix a (JSBinOpOf _) = JSBinOpOf a
+ fix _ (JSBinOpOr _) = JSBinOpOr emptyAnnot
+ fix _ (JSBinOpPlus _) = JSBinOpPlus emptyAnnot
+ fix _ (JSBinOpRsh _) = JSBinOpRsh emptyAnnot
+ fix _ (JSBinOpStrictEq _) = JSBinOpStrictEq emptyAnnot
+ fix _ (JSBinOpStrictNeq _) = JSBinOpStrictNeq emptyAnnot
+ fix _ (JSBinOpTimes _) = JSBinOpTimes emptyAnnot
+ fix _ (JSBinOpUrsh _) = JSBinOpUrsh emptyAnnot
+
+
+instance MinifyJS JSUnaryOp where
+ fix _ (JSUnaryOpDecr _) = JSUnaryOpDecr emptyAnnot
+ fix _ (JSUnaryOpDelete _) = JSUnaryOpDelete emptyAnnot
+ fix _ (JSUnaryOpIncr _) = JSUnaryOpIncr emptyAnnot
+ fix _ (JSUnaryOpMinus _) = JSUnaryOpMinus emptyAnnot
+ fix _ (JSUnaryOpNot _) = JSUnaryOpNot emptyAnnot
+ fix _ (JSUnaryOpPlus _) = JSUnaryOpPlus emptyAnnot
+ fix _ (JSUnaryOpTilde _) = JSUnaryOpTilde emptyAnnot
+ fix _ (JSUnaryOpTypeof _) = JSUnaryOpTypeof emptyAnnot
+ fix _ (JSUnaryOpVoid _) = JSUnaryOpVoid emptyAnnot
+
+fixUnaryOp :: JSAnnot -> JSUnaryOp -> (JSAnnot, JSUnaryOp)
+fixUnaryOp a (JSUnaryOpDelete _) = (spaceAnnot, JSUnaryOpDelete a)
+fixUnaryOp a (JSUnaryOpTypeof _) = (spaceAnnot, JSUnaryOpTypeof a)
+fixUnaryOp a (JSUnaryOpVoid _) = (spaceAnnot, JSUnaryOpVoid a)
+fixUnaryOp a x = (emptyAnnot, fix a x)
+
+
+instance MinifyJS JSAssignOp where
+ fix a (JSAssign _) = JSAssign a
+ fix a (JSTimesAssign _) = JSTimesAssign a
+ fix a (JSDivideAssign _) = JSDivideAssign a
+ fix a (JSModAssign _) = JSModAssign a
+ fix a (JSPlusAssign _) = JSPlusAssign a
+ fix a (JSMinusAssign _) = JSMinusAssign a
+ fix a (JSLshAssign _) = JSLshAssign a
+ fix a (JSRshAssign _) = JSRshAssign a
+ fix a (JSUrshAssign _) = JSUrshAssign a
+ fix a (JSBwAndAssign _) = JSBwAndAssign a
+ fix a (JSBwXorAssign _) = JSBwXorAssign a
+ fix a (JSBwOrAssign _) = JSBwOrAssign a
+
+instance MinifyJS JSModuleItem where
+ fix _ (JSModuleImportDeclaration _ x1) = JSModuleImportDeclaration emptyAnnot (fixEmpty x1)
+ fix _ (JSModuleExportDeclaration _ x1) = JSModuleExportDeclaration emptyAnnot (fixEmpty x1)
+ fix a (JSModuleStatementListItem s) = JSModuleStatementListItem (fixStmt a noSemi s)
+
+instance MinifyJS JSImportDeclaration where
+ fix _ (JSImportDeclaration imps from _) = JSImportDeclaration (fixEmpty imps) (fix annot from) noSemi
+ where
+ annot = case imps of
+ JSImportClauseDefault {} -> spaceAnnot
+ JSImportClauseNameSpace {} -> spaceAnnot
+ JSImportClauseNamed {} -> emptyAnnot
+ JSImportClauseDefaultNameSpace {} -> spaceAnnot
+ JSImportClauseDefaultNamed {} -> emptyAnnot
+ fix a (JSImportDeclarationBare _ m _) = JSImportDeclarationBare a m noSemi
+
+instance MinifyJS JSImportClause where
+ fix _ (JSImportClauseDefault n) = JSImportClauseDefault (fixSpace n)
+ fix _ (JSImportClauseNameSpace ns) = JSImportClauseNameSpace (fixSpace ns)
+ fix _ (JSImportClauseNamed named) = JSImportClauseNamed (fixEmpty named)
+ fix _ (JSImportClauseDefaultNameSpace def _ ns) = JSImportClauseDefaultNameSpace (fixSpace def) emptyAnnot (fixEmpty ns)
+ fix _ (JSImportClauseDefaultNamed def _ ns) = JSImportClauseDefaultNamed (fixSpace def) emptyAnnot (fixEmpty ns)
+
+instance MinifyJS JSFromClause where
+ fix a (JSFromClause _ _ m) = JSFromClause a emptyAnnot m
+
+instance MinifyJS JSImportNameSpace where
+ fix a (JSImportNameSpace _ _ ident) = JSImportNameSpace (JSBinOpTimes a) spaceAnnot (fixSpace ident)
+
+instance MinifyJS JSImportsNamed where
+ fix _ (JSImportsNamed _ imps _) = JSImportsNamed emptyAnnot (fixEmpty imps) emptyAnnot
+
+instance MinifyJS JSImportSpecifier where
+ fix _ (JSImportSpecifier x1) = JSImportSpecifier (fixEmpty x1)
+ fix _ (JSImportSpecifierAs x1 _ x2) = JSImportSpecifierAs (fixEmpty x1) spaceAnnot (fixSpace x2)
+
+instance MinifyJS JSExportDeclaration where
+ fix a (JSExportFrom x1 from _) = JSExportFrom (fix a x1) (fix a from) noSemi
+ fix _ (JSExportLocals x1 _) = JSExportLocals (fix emptyAnnot x1) noSemi
+ fix _ (JSExport x1 _) = JSExport (fixStmt spaceAnnot noSemi x1) noSemi
+
+instance MinifyJS JSExportClause where
+ fix a (JSExportClause _ x1 _) = JSExportClause emptyAnnot (fixEmpty x1) a
+
+instance MinifyJS JSExportSpecifier where
+ fix _ (JSExportSpecifier x1) = JSExportSpecifier (fixEmpty x1)
+ fix _ (JSExportSpecifierAs x1 _ x2) = JSExportSpecifierAs (fixEmpty x1) spaceAnnot (fixSpace x2)
+
+instance MinifyJS JSTryCatch where
+ fix a (JSCatch _ _ x1 _ x3) = JSCatch a emptyAnnot (fixEmpty x1) emptyAnnot (fixEmpty x3)
+ fix a (JSCatchIf _ _ x1 _ ex _ x3) = JSCatchIf a emptyAnnot (fixEmpty x1) spaceAnnot (fixSpace ex) emptyAnnot (fixEmpty x3)
+
+
+instance MinifyJS JSTryFinally where
+ fix a (JSFinally _ x) = JSFinally a (fixEmpty x)
+ fix _ JSNoFinally = JSNoFinally
+
+
+fixSwitchParts :: [JSSwitchParts] -> [JSSwitchParts]
+fixSwitchParts parts =
+ case parts of
+ [] -> []
+ [x] -> [fixPart noSemi x]
+ (x:xs) -> fixPart semi x : fixSwitchParts xs
+ where
+ fixPart s (JSCase _ e _ ss) = JSCase emptyAnnot (fixCase e) emptyAnnot (fixStatementList s ss)
+ fixPart s (JSDefault _ _ ss) = JSDefault emptyAnnot emptyAnnot (fixStatementList s ss)
+
+fixCase :: JSExpression -> JSExpression
+fixCase (JSStringLiteral _ s) = JSStringLiteral emptyAnnot s
+fixCase e = fix spaceAnnot e
+
+
+instance MinifyJS JSBlock where
+ fix _ (JSBlock _ ss _) = JSBlock emptyAnnot (fixStatementList noSemi ss) emptyAnnot
+
+
+instance MinifyJS JSObjectProperty where
+ fix a (JSPropertyNameandValue n _ vs) = JSPropertyNameandValue (fix a n) emptyAnnot (map fixEmpty vs)
+ fix a (JSPropertyIdentRef _ s) = JSPropertyIdentRef a s
+ fix a (JSObjectMethod m) = JSObjectMethod (fix a m)
+
+instance MinifyJS JSMethodDefinition where
+ fix a (JSMethodDefinition n _ ps _ b) = JSMethodDefinition (fix a n) emptyAnnot (fixEmpty ps) emptyAnnot (fixEmpty b)
+ fix _ (JSGeneratorMethodDefinition _ n _ ps _ b) = JSGeneratorMethodDefinition emptyAnnot (fixEmpty n) emptyAnnot (fixEmpty ps) emptyAnnot (fixEmpty b)
+ fix a (JSPropertyAccessor s n _ ps _ b) = JSPropertyAccessor (fix a s) (fixSpace n) emptyAnnot (fixEmpty ps) emptyAnnot (fixEmpty b)
+
+instance MinifyJS JSPropertyName where
+ fix a (JSPropertyIdent _ s) = JSPropertyIdent a s
+ fix a (JSPropertyString _ s) = JSPropertyString a s
+ fix a (JSPropertyNumber _ s) = JSPropertyNumber a s
+ fix _ (JSPropertyComputed _ x _) = JSPropertyComputed emptyAnnot (fixEmpty x) emptyAnnot
+
+instance MinifyJS JSAccessor where
+ fix a (JSAccessorGet _) = JSAccessorGet a
+ fix a (JSAccessorSet _) = JSAccessorSet a
+
+
+instance MinifyJS JSArrayElement where
+ fix _ (JSArrayElement e) = JSArrayElement (fixEmpty e)
+ fix _ (JSArrayComma _) = JSArrayComma emptyAnnot
+
+
+instance MinifyJS a => MinifyJS (JSCommaList a) where
+ fix _ (JSLCons xs _ x) = JSLCons (fixEmpty xs) emptyAnnot (fixEmpty x)
+ fix _ (JSLOne a) = JSLOne (fixEmpty a)
+ fix _ JSLNil = JSLNil
+
+
+instance MinifyJS a => MinifyJS (JSCommaTrailingList a) where
+ fix _ (JSCTLComma xs _) = JSCTLNone (fixEmpty xs)
+ fix _ (JSCTLNone xs) = JSCTLNone (fixEmpty xs)
+
+
+instance MinifyJS JSIdent where
+ fix a (JSIdentName _ n) = JSIdentName a n
+ fix _ JSIdentNone = JSIdentNone
+
+
+instance MinifyJS (Maybe JSExpression) where
+ fix a me = fix a <$> me
+
+
+instance MinifyJS JSVarInitializer where
+ fix a (JSVarInit _ x) = JSVarInit a (fix emptyAnnot x)
+ fix _ JSVarInitNone = JSVarInitNone
+
+
+instance MinifyJS JSTemplatePart where
+ fix _ (JSTemplatePart e _ s) = JSTemplatePart (fixEmpty e) emptyAnnot s
+
+
+instance MinifyJS JSClassHeritage where
+ fix _ JSExtendsNone = JSExtendsNone
+ fix a (JSExtends _ e) = JSExtends a (fixSpace e)
+
+
+instance MinifyJS [JSClassElement] where
+ fix _ [] = []
+ fix a (JSClassInstanceMethod m:t) = JSClassInstanceMethod (fix a m) : fixEmpty t
+ fix a (JSClassStaticMethod _ m:t) = JSClassStaticMethod a (fixSpace m) : fixEmpty t
+ fix a (JSClassSemi _:t) = fix a t
+
+
+spaceAnnot :: JSAnnot
+spaceAnnot = JSAnnot tokenPosnEmpty [WhiteSpace tokenPosnEmpty " "]
+
+emptyAnnot :: JSAnnot
+emptyAnnot = JSNoAnnot
+
+newlineAnnot :: JSAnnot
+newlineAnnot = JSAnnot tokenPosnEmpty [WhiteSpace tokenPosnEmpty "\n"]
+
+semi :: JSSemi
+semi = JSSemi emptyAnnot
+
+noSemi :: JSSemi
+noSemi = JSSemiAuto
--- /dev/null
+module Test.Language.Javascript.ExpressionParser
+ ( testExpressionParser
+ ) where
+
+import Test.Hspec
+
+import Language.JavaScript.Parser
+import Language.JavaScript.Parser.Grammar7
+import Language.JavaScript.Parser.Parser
+
+
+testExpressionParser :: Spec
+testExpressionParser = describe "Parse expressions:" $ do
+ it "this" $
+ testExpr "this" `shouldBe` "Right (JSAstExpression (JSLiteral 'this'))"
+ it "regex" $ do
+ testExpr "/blah/" `shouldBe` "Right (JSAstExpression (JSRegEx '/blah/'))"
+ testExpr "/$/g" `shouldBe` "Right (JSAstExpression (JSRegEx '/$/g'))"
+ testExpr "/\\n/g" `shouldBe` "Right (JSAstExpression (JSRegEx '/\\n/g'))"
+ testExpr "/(\\/)/" `shouldBe` "Right (JSAstExpression (JSRegEx '/(\\/)/'))"
+ testExpr "/a[/]b/" `shouldBe` "Right (JSAstExpression (JSRegEx '/a[/]b/'))"
+ testExpr "/[/\\]/" `shouldBe` "Right (JSAstExpression (JSRegEx '/[/\\]/'))"
+ testExpr "/(\\/|\\)/" `shouldBe` "Right (JSAstExpression (JSRegEx '/(\\/|\\)/'))"
+ testExpr "/a\\[|\\]$/g" `shouldBe` "Right (JSAstExpression (JSRegEx '/a\\[|\\]$/g'))"
+ testExpr "/[(){}\\[\\]]/g" `shouldBe` "Right (JSAstExpression (JSRegEx '/[(){}\\[\\]]/g'))"
+ testExpr "/^\"(?:\\.|[^\"])*\"|^'(?:[^']|\\.)*'/" `shouldBe` "Right (JSAstExpression (JSRegEx '/^\"(?:\\.|[^\"])*\"|^'(?:[^']|\\.)*'/'))"
+
+ it "identifier" $ do
+ testExpr "_$" `shouldBe` "Right (JSAstExpression (JSIdentifier '_$'))"
+ testExpr "this_" `shouldBe` "Right (JSAstExpression (JSIdentifier 'this_'))"
+ it "array literal" $ do
+ testExpr "[]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral []))"
+ testExpr "[,]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSComma]))"
+ testExpr "[,,]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSComma,JSComma]))"
+ testExpr "[,,x]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSComma,JSComma,JSIdentifier 'x']))"
+ testExpr "[,,x]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSComma,JSComma,JSIdentifier 'x']))"
+ testExpr "[,x,,x]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSComma,JSIdentifier 'x',JSComma,JSComma,JSIdentifier 'x']))"
+ testExpr "[x]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSIdentifier 'x']))"
+ testExpr "[x,]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSIdentifier 'x',JSComma]))"
+ testExpr "[,,,]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSComma,JSComma,JSComma]))"
+ testExpr "[a,,]" `shouldBe` "Right (JSAstExpression (JSArrayLiteral [JSIdentifier 'a',JSComma,JSComma]))"
+ it "operator precedence" $
+ testExpr "2+3*4+5" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('+',JSExpressionBinary ('+',JSDecimal '2',JSExpressionBinary ('*',JSDecimal '3',JSDecimal '4')),JSDecimal '5')))"
+ it "parentheses" $
+ testExpr "(56)" `shouldBe` "Right (JSAstExpression (JSExpressionParen (JSDecimal '56')))"
+ it "string concatenation" $ do
+ testExpr "'ab' + 'bc'" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('+',JSStringLiteral 'ab',JSStringLiteral 'bc')))"
+ testExpr "'bc' + \"cd\"" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('+',JSStringLiteral 'bc',JSStringLiteral \"cd\")))"
+ it "object literal" $ do
+ testExpr "{}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral []))"
+ testExpr "{x:1}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'x') [JSDecimal '1']]))"
+ testExpr "{x:1,y:2}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'x') [JSDecimal '1'],JSPropertyNameandValue (JSIdentifier 'y') [JSDecimal '2']]))"
+ testExpr "{x:1,}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'x') [JSDecimal '1'],JSComma]))"
+ testExpr "{yield:1}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'yield') [JSDecimal '1']]))"
+ testExpr "{x}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyIdentRef 'x']))"
+ testExpr "{x,}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyIdentRef 'x',JSComma]))"
+ testExpr "{set x([a,b]=y) {this.a=a;this.b=b}}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyAccessor JSAccessorSet (JSIdentifier 'x') (JSOpAssign ('=',JSArrayLiteral [JSIdentifier 'a',JSComma,JSIdentifier 'b'],JSIdentifier 'y')) (JSBlock [JSOpAssign ('=',JSMemberDot (JSLiteral 'this',JSIdentifier 'a'),JSIdentifier 'a'),JSSemicolon,JSOpAssign ('=',JSMemberDot (JSLiteral 'this',JSIdentifier 'b'),JSIdentifier 'b')])]))"
+ testExpr "a={if:1,interface:2}" `shouldBe` "Right (JSAstExpression (JSOpAssign ('=',JSIdentifier 'a',JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'if') [JSDecimal '1'],JSPropertyNameandValue (JSIdentifier 'interface') [JSDecimal '2']])))"
+ testExpr "a={\n values: 7,\n}\n" `shouldBe` "Right (JSAstExpression (JSOpAssign ('=',JSIdentifier 'a',JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'values') [JSDecimal '7'],JSComma])))"
+ testExpr "x={get foo() {return 1},set foo(a) {x=a}}" `shouldBe` "Right (JSAstExpression (JSOpAssign ('=',JSIdentifier 'x',JSObjectLiteral [JSPropertyAccessor JSAccessorGet (JSIdentifier 'foo') () (JSBlock [JSReturn JSDecimal '1' ]),JSPropertyAccessor JSAccessorSet (JSIdentifier 'foo') (JSIdentifier 'a') (JSBlock [JSOpAssign ('=',JSIdentifier 'x',JSIdentifier 'a')])])))"
+ testExpr "{evaluate:evaluate,load:function load(s){if(x)return s;1}}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'evaluate') [JSIdentifier 'evaluate'],JSPropertyNameandValue (JSIdentifier 'load') [JSFunctionExpression 'load' (JSIdentifier 's') (JSBlock [JSIf (JSIdentifier 'x') (JSReturn JSIdentifier 's' JSSemicolon),JSDecimal '1'])]]))"
+ testExpr "obj = { name : 'A', 'str' : 'B', 123 : 'C', }" `shouldBe` "Right (JSAstExpression (JSOpAssign ('=',JSIdentifier 'obj',JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'name') [JSStringLiteral 'A'],JSPropertyNameandValue (JSIdentifier ''str'') [JSStringLiteral 'B'],JSPropertyNameandValue (JSIdentifier '123') [JSStringLiteral 'C'],JSComma])))"
+ testExpr "{[x]:1}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSPropertyNameandValue (JSPropertyComputed (JSIdentifier 'x')) [JSDecimal '1']]))"
+ testExpr "{ a(x,y) {}, 'blah blah'() {} }" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSMethodDefinition (JSIdentifier 'a') (JSIdentifier 'x',JSIdentifier 'y') (JSBlock []),JSMethodDefinition (JSIdentifier ''blah blah'') () (JSBlock [])]))"
+ testExpr "{[x]() {}}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSMethodDefinition (JSPropertyComputed (JSIdentifier 'x')) () (JSBlock [])]))"
+ testExpr "{*a(x,y) {yield y;}}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSGeneratorMethodDefinition (JSIdentifier 'a') (JSIdentifier 'x',JSIdentifier 'y') (JSBlock [JSYieldExpression (JSIdentifier 'y'),JSSemicolon])]))"
+ testExpr "{*[x]({y},...z) {}}" `shouldBe` "Right (JSAstExpression (JSObjectLiteral [JSGeneratorMethodDefinition (JSPropertyComputed (JSIdentifier 'x')) (JSObjectLiteral [JSPropertyIdentRef 'y'],JSSpreadExpression (JSIdentifier 'z')) (JSBlock [])]))"
+
+ it "unary expression" $ do
+ testExpr "delete y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('delete',JSIdentifier 'y')))"
+ testExpr "void y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('void',JSIdentifier 'y')))"
+ testExpr "typeof y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('typeof',JSIdentifier 'y')))"
+ testExpr "++y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('++',JSIdentifier 'y')))"
+ testExpr "--y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('--',JSIdentifier 'y')))"
+ testExpr "+y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('+',JSIdentifier 'y')))"
+ testExpr "-y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('-',JSIdentifier 'y')))"
+ testExpr "~y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('~',JSIdentifier 'y')))"
+ testExpr "!y" `shouldBe` "Right (JSAstExpression (JSUnaryExpression ('!',JSIdentifier 'y')))"
+ testExpr "y++" `shouldBe` "Right (JSAstExpression (JSExpressionPostfix ('++',JSIdentifier 'y')))"
+ testExpr "y--" `shouldBe` "Right (JSAstExpression (JSExpressionPostfix ('--',JSIdentifier 'y')))"
+ testExpr "...y" `shouldBe` "Right (JSAstExpression (JSSpreadExpression (JSIdentifier 'y')))"
+
+
+ it "new expression" $ do
+ testExpr "new x()" `shouldBe` "Right (JSAstExpression (JSMemberNew (JSIdentifier 'x',JSArguments ())))"
+ testExpr "new x.y" `shouldBe` "Right (JSAstExpression (JSNewExpression JSMemberDot (JSIdentifier 'x',JSIdentifier 'y')))"
+
+ it "binary expression" $ do
+ testExpr "x||y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('||',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x&&y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('&&',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x|y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('|',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x^y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('^',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x&y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('&',JSIdentifier 'x',JSIdentifier 'y')))"
+
+ testExpr "x==y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('==',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x!=y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('!=',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x===y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('===',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x!==y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('!==',JSIdentifier 'x',JSIdentifier 'y')))"
+
+ testExpr "x<y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('<',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x>y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('>',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x<=y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('<=',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x>=y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('>=',JSIdentifier 'x',JSIdentifier 'y')))"
+
+ testExpr "x<<y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('<<',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x>>y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('>>',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x>>>y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('>>>',JSIdentifier 'x',JSIdentifier 'y')))"
+
+ testExpr "x+y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('+',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x-y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('-',JSIdentifier 'x',JSIdentifier 'y')))"
+
+ testExpr "x*y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('*',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x/y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('/',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x%y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('%',JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x instanceof y" `shouldBe` "Right (JSAstExpression (JSExpressionBinary ('instanceof',JSIdentifier 'x',JSIdentifier 'y')))"
+
+ it "assign expression" $ do
+ testExpr "x=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x*=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('*=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x/=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('/=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x%=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('%=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x+=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('+=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x-=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('-=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x<<=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('<<=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x>>=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('>>=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x>>>=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('>>>=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x&=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('&=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x^=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('^=',JSIdentifier 'x',JSDecimal '1')))"
+ testExpr "x|=1" `shouldBe` "Right (JSAstExpression (JSOpAssign ('|=',JSIdentifier 'x',JSDecimal '1')))"
+
+ it "function expression" $ do
+ testExpr "function(){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' () (JSBlock [])))"
+ testExpr "function(a){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSIdentifier 'a') (JSBlock [])))"
+ testExpr "function(a,b){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSIdentifier 'a',JSIdentifier 'b') (JSBlock [])))"
+ testExpr "function(...a){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSSpreadExpression (JSIdentifier 'a')) (JSBlock [])))"
+ testExpr "function(a=1){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSOpAssign ('=',JSIdentifier 'a',JSDecimal '1')) (JSBlock [])))"
+ testExpr "function([a,b]){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSArrayLiteral [JSIdentifier 'a',JSComma,JSIdentifier 'b']) (JSBlock [])))"
+ testExpr "function([a,...b]){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSArrayLiteral [JSIdentifier 'a',JSComma,JSSpreadExpression (JSIdentifier 'b')]) (JSBlock [])))"
+ testExpr "function({a,b}){}" `shouldBe` "Right (JSAstExpression (JSFunctionExpression '' (JSObjectLiteral [JSPropertyIdentRef 'a',JSPropertyIdentRef 'b']) (JSBlock [])))"
+ testExpr "a => {}" `shouldBe` "Right (JSAstExpression (JSArrowExpression (JSIdentifier 'a') => JSStatementBlock []))"
+ testExpr "(a) => { a + 2 }" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a')) => JSStatementBlock [JSExpressionBinary ('+',JSIdentifier 'a',JSDecimal '2')]))"
+ testExpr "(a, b) => {}" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a',JSIdentifier 'b')) => JSStatementBlock []))"
+ testExpr "(a, b) => a + b" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a',JSIdentifier 'b')) => JSExpressionBinary ('+',JSIdentifier 'a',JSIdentifier 'b')))"
+ testExpr "() => { 42 }" `shouldBe` "Right (JSAstExpression (JSArrowExpression (()) => JSStatementBlock [JSDecimal '42']))"
+ testExpr "(a, ...b) => b" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a',JSSpreadExpression (JSIdentifier 'b'))) => JSIdentifier 'b'))"
+ testExpr "(a,b=1) => a + b" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSIdentifier 'a',JSOpAssign ('=',JSIdentifier 'b',JSDecimal '1'))) => JSExpressionBinary ('+',JSIdentifier 'a',JSIdentifier 'b')))"
+ testExpr "([a,b]) => a + b" `shouldBe` "Right (JSAstExpression (JSArrowExpression ((JSArrayLiteral [JSIdentifier 'a',JSComma,JSIdentifier 'b'])) => JSExpressionBinary ('+',JSIdentifier 'a',JSIdentifier 'b')))"
+
+ it "generator expression" $ do
+ testExpr "function*(){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression '' () (JSBlock [])))"
+ testExpr "function*(a){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression '' (JSIdentifier 'a') (JSBlock [])))"
+ testExpr "function*(a,b){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression '' (JSIdentifier 'a',JSIdentifier 'b') (JSBlock [])))"
+ testExpr "function*(a,...b){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression '' (JSIdentifier 'a',JSSpreadExpression (JSIdentifier 'b')) (JSBlock [])))"
+ testExpr "function*f(){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression 'f' () (JSBlock [])))"
+ testExpr "function*f(a){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression 'f' (JSIdentifier 'a') (JSBlock [])))"
+ testExpr "function*f(a,b){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression 'f' (JSIdentifier 'a',JSIdentifier 'b') (JSBlock [])))"
+ testExpr "function*f(a,...b){}" `shouldBe` "Right (JSAstExpression (JSGeneratorExpression 'f' (JSIdentifier 'a',JSSpreadExpression (JSIdentifier 'b')) (JSBlock [])))"
+
+ it "member expression" $ do
+ testExpr "x[y]" `shouldBe` "Right (JSAstExpression (JSMemberSquare (JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x[y][z]" `shouldBe` "Right (JSAstExpression (JSMemberSquare (JSMemberSquare (JSIdentifier 'x',JSIdentifier 'y'),JSIdentifier 'z')))"
+ testExpr "x.y" `shouldBe` "Right (JSAstExpression (JSMemberDot (JSIdentifier 'x',JSIdentifier 'y')))"
+ testExpr "x.y.z" `shouldBe` "Right (JSAstExpression (JSMemberDot (JSMemberDot (JSIdentifier 'x',JSIdentifier 'y'),JSIdentifier 'z')))"
+
+ it "call expression" $ do
+ testExpr "x()" `shouldBe` "Right (JSAstExpression (JSMemberExpression (JSIdentifier 'x',JSArguments ())))"
+ testExpr "x()()" `shouldBe` "Right (JSAstExpression (JSCallExpression (JSMemberExpression (JSIdentifier 'x',JSArguments ()),JSArguments ())))"
+ testExpr "x()[4]" `shouldBe` "Right (JSAstExpression (JSCallExpressionSquare (JSMemberExpression (JSIdentifier 'x',JSArguments ()),JSDecimal '4')))"
+ testExpr "x().x" `shouldBe` "Right (JSAstExpression (JSCallExpressionDot (JSMemberExpression (JSIdentifier 'x',JSArguments ()),JSIdentifier 'x')))"
+ testExpr "x(a,b=2).x" `shouldBe` "Right (JSAstExpression (JSCallExpressionDot (JSMemberExpression (JSIdentifier 'x',JSArguments (JSIdentifier 'a',JSOpAssign ('=',JSIdentifier 'b',JSDecimal '2'))),JSIdentifier 'x')))"
+ testExpr "foo (56.8379100, 60.5806664)" `shouldBe` "Right (JSAstExpression (JSMemberExpression (JSIdentifier 'foo',JSArguments (JSDecimal '56.8379100',JSDecimal '60.5806664'))))"
+
+ it "spread expression" $
+ testExpr "... x" `shouldBe` "Right (JSAstExpression (JSSpreadExpression (JSIdentifier 'x')))"
+
+ it "template literal" $ do
+ testExpr "``" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'``',[])))"
+ testExpr "`$`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`$`',[])))"
+ testExpr "`$\\n`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`$\\n`',[])))"
+ testExpr "`\\${x}`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`\\${x}`',[])))"
+ testExpr "`$ {x}`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`$ {x}`',[])))"
+ testExpr "`\n\n`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`\n\n`',[])))"
+ testExpr "`${x+y} ${z}`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`${',[(JSExpressionBinary ('+',JSIdentifier 'x',JSIdentifier 'y'),'} ${'),(JSIdentifier 'z','}`')])))"
+ testExpr "`<${x} ${y}>`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((),'`<${',[(JSIdentifier 'x','} ${'),(JSIdentifier 'y','}>`')])))"
+ testExpr "tag `xyz`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((JSIdentifier 'tag'),'`xyz`',[])))"
+ testExpr "tag()`xyz`" `shouldBe` "Right (JSAstExpression (JSTemplateLiteral ((JSMemberExpression (JSIdentifier 'tag',JSArguments ())),'`xyz`',[])))"
+
+ it "yield" $ do
+ testExpr "yield" `shouldBe` "Right (JSAstExpression (JSYieldExpression ()))"
+ testExpr "yield a + b" `shouldBe` "Right (JSAstExpression (JSYieldExpression (JSExpressionBinary ('+',JSIdentifier 'a',JSIdentifier 'b'))))"
+ testExpr "yield* g()" `shouldBe` "Right (JSAstExpression (JSYieldFromExpression (JSMemberExpression (JSIdentifier 'g',JSArguments ()))))"
+
+ it "class expression" $ do
+ testExpr "class Foo extends Bar { a(x,y) {} *b() {} }" `shouldBe` "Right (JSAstExpression (JSClassExpression 'Foo' (JSIdentifier 'Bar') [JSMethodDefinition (JSIdentifier 'a') (JSIdentifier 'x',JSIdentifier 'y') (JSBlock []),JSGeneratorMethodDefinition (JSIdentifier 'b') () (JSBlock [])]))"
+ testExpr "class { static get [a]() {}; }" `shouldBe` "Right (JSAstExpression (JSClassExpression '' () [JSClassStaticMethod (JSPropertyAccessor JSAccessorGet (JSPropertyComputed (JSIdentifier 'a')) () (JSBlock [])),JSClassSemi]))"
+ testExpr "class Foo extends Bar { a(x,y) { super(x); } }" `shouldBe` "Right (JSAstExpression (JSClassExpression 'Foo' (JSIdentifier 'Bar') [JSMethodDefinition (JSIdentifier 'a') (JSIdentifier 'x',JSIdentifier 'y') (JSBlock [JSCallExpression (JSLiteral 'super',JSArguments (JSIdentifier 'x')),JSSemicolon])]))"
+
+
+testExpr :: String -> String
+testExpr str = showStrippedMaybe (parseUsing parseExpression str "src")
--- /dev/null
+module Test.Language.Javascript.Lexer
+ ( testLexer
+ ) where
+
+import Test.Hspec
+
+import Data.List (intercalate)
+
+import Language.JavaScript.Parser.Lexer
+
+
+testLexer :: Spec
+testLexer = describe "Lexer:" $ do
+ it "comments" $ do
+ testLex "// 𝟘𝟙𝟚𝟛𝟜𝟝𝟞𝟟𝟠𝟡 " `shouldBe` "[CommentToken]"
+ testLex "/* 𝟘𝟙𝟚𝟛𝟜𝟝𝟞𝟟𝟠𝟡 */" `shouldBe` "[CommentToken]"
+
+ it "numbers" $ do
+ testLex "123" `shouldBe` "[DecimalToken 123]"
+ testLex "037" `shouldBe` "[OctalToken 037]"
+ testLex "0xab" `shouldBe` "[HexIntegerToken 0xab]"
+ testLex "0xCD" `shouldBe` "[HexIntegerToken 0xCD]"
+
+ it "invalid numbers" $ do
+ testLex "089" `shouldBe` "[DecimalToken 0,DecimalToken 89]"
+ testLex "0xGh" `shouldBe` "[DecimalToken 0,IdentifierToken 'xGx']"
+
+ it "string" $ do
+ testLex "'cat'" `shouldBe` "[StringToken 'cat']"
+ testLex "\"dog\"" `shouldBe` "[StringToken \"dog\"]"
+
+ it "strings with escape chars" $ do
+ testLex "'\t'" `shouldBe` "[StringToken '\t']"
+ testLex "'\\n'" `shouldBe` "[StringToken '\\n']"
+ testLex "'\\\\n'" `shouldBe` "[StringToken '\\\\n']"
+ testLex "'\\\\'" `shouldBe` "[StringToken '\\\\']"
+ testLex "'\\0'" `shouldBe` "[StringToken '\\0']"
+ testLex "'\\12'" `shouldBe` "[StringToken '\\12']"
+ testLex "'\\s'" `shouldBe` "[StringToken '\\s']"
+ testLex "'\\-'" `shouldBe` "[StringToken '\\-']"
+
+ it "strings with non-escaped chars" $
+ testLex "'\\/'" `shouldBe` "[StringToken '\\/']"
+
+ it "strings with escaped quotes" $ do
+ testLex "'\"'" `shouldBe` "[StringToken '\"']"
+ testLex "\"\\\"\"" `shouldBe` "[StringToken \"\\\\\"\"]"
+ testLex "'\\\''" `shouldBe` "[StringToken '\\\\'']"
+ testLex "'\"'" `shouldBe` "[StringToken '\"']"
+ testLex "\"\\'\"" `shouldBe` "[StringToken \"\\'\"]"
+
+ it "spread token" $ do
+ testLex "...a" `shouldBe` "[SpreadToken,IdentifierToken 'a']"
+
+ it "assignment" $ do
+ testLex "x=1" `shouldBe` "[IdentifierToken 'x',SimpleAssignToken,DecimalToken 1]"
+ testLex "x=1\ny=2" `shouldBe` "[IdentifierToken 'x',SimpleAssignToken,DecimalToken 1,WsToken,IdentifierToken 'y',SimpleAssignToken,DecimalToken 2]"
+
+ it "break/continue/return" $ do
+ testLex "break\nx=1" `shouldBe` "[BreakToken,WsToken,IdentifierToken 'x',SimpleAssignToken,DecimalToken 1]"
+ testLex "continue\nx=1" `shouldBe` "[ContinueToken,WsToken,IdentifierToken 'x',SimpleAssignToken,DecimalToken 1]"
+ testLex "return\nx=1" `shouldBe` "[ReturnToken,WsToken,IdentifierToken 'x',SimpleAssignToken,DecimalToken 1]"
+
+ it "var/let" $ do
+ testLex "var\n" `shouldBe` "[VarToken,WsToken]"
+ testLex "let\n" `shouldBe` "[LetToken,WsToken]"
+
+ it "in/of" $ do
+ testLex "in\n" `shouldBe` "[InToken,WsToken]"
+ testLex "of\n" `shouldBe` "[OfToken,WsToken]"
+
+ it "function" $ do
+ testLex "async function\n" `shouldBe` "[AsyncToken,WsToken,FunctionToken,WsToken]"
+
+
+testLex :: String -> String
+testLex str =
+ either id stringify $ alexTestTokeniser str
+ where
+ stringify xs = "[" ++ intercalate "," (map showToken xs) ++ "]"
+
+ showToken :: Token -> String
+ showToken (StringToken _ lit _) = "StringToken " ++ stringEscape lit
+ showToken (IdentifierToken _ lit _) = "IdentifierToken '" ++ stringEscape lit ++ "'"
+ showToken (DecimalToken _ lit _) = "DecimalToken " ++ lit
+ showToken (OctalToken _ lit _) = "OctalToken " ++ lit
+ showToken (HexIntegerToken _ lit _) = "HexIntegerToken " ++ lit
+ showToken token = takeWhile (/= ' ') $ show token
+
+ stringEscape [] = []
+ stringEscape (term:rest) =
+ let escapeTerm [] = []
+ escapeTerm [_] = [term]
+ escapeTerm (x:xs)
+ | term == x = "\\" ++ x : escapeTerm xs
+ | otherwise = x : escapeTerm xs
+ in term : escapeTerm rest
--- /dev/null
+module Test.Language.Javascript.LiteralParser
+ ( testLiteralParser
+ ) where
+
+import Test.Hspec
+
+import Control.Monad (forM_)
+import Data.Char (chr, isPrint)
+
+import Language.JavaScript.Parser
+import Language.JavaScript.Parser.Grammar7
+import Language.JavaScript.Parser.Parser
+
+
+testLiteralParser :: Spec
+testLiteralParser = describe "Parse literals:" $ do
+ it "null/true/false" $ do
+ testLiteral "null" `shouldBe` "Right (JSAstLiteral (JSLiteral 'null'))"
+ testLiteral "false" `shouldBe` "Right (JSAstLiteral (JSLiteral 'false'))"
+ testLiteral "true" `shouldBe` "Right (JSAstLiteral (JSLiteral 'true'))"
+ it "hex numbers" $ do
+ testLiteral "0x1234fF" `shouldBe` "Right (JSAstLiteral (JSHexInteger '0x1234fF'))"
+ testLiteral "0X1234fF" `shouldBe` "Right (JSAstLiteral (JSHexInteger '0X1234fF'))"
+ it "decimal numbers" $ do
+ testLiteral "1.0e4" `shouldBe` "Right (JSAstLiteral (JSDecimal '1.0e4'))"
+ testLiteral "2.3E6" `shouldBe` "Right (JSAstLiteral (JSDecimal '2.3E6'))"
+ testLiteral "4.5" `shouldBe` "Right (JSAstLiteral (JSDecimal '4.5'))"
+ testLiteral "0.7e8" `shouldBe` "Right (JSAstLiteral (JSDecimal '0.7e8'))"
+ testLiteral "0.7E8" `shouldBe` "Right (JSAstLiteral (JSDecimal '0.7E8'))"
+ testLiteral "10" `shouldBe` "Right (JSAstLiteral (JSDecimal '10'))"
+ testLiteral "0" `shouldBe` "Right (JSAstLiteral (JSDecimal '0'))"
+ testLiteral "0.03" `shouldBe` "Right (JSAstLiteral (JSDecimal '0.03'))"
+ testLiteral "0.7e+8" `shouldBe` "Right (JSAstLiteral (JSDecimal '0.7e+8'))"
+ testLiteral "0.7e-18" `shouldBe` "Right (JSAstLiteral (JSDecimal '0.7e-18'))"
+ testLiteral "1.0e+4" `shouldBe` "Right (JSAstLiteral (JSDecimal '1.0e+4'))"
+ testLiteral "1.0e-4" `shouldBe` "Right (JSAstLiteral (JSDecimal '1.0e-4'))"
+ testLiteral "1e18" `shouldBe` "Right (JSAstLiteral (JSDecimal '1e18'))"
+ testLiteral "1e+18" `shouldBe` "Right (JSAstLiteral (JSDecimal '1e+18'))"
+ testLiteral "1e-18" `shouldBe` "Right (JSAstLiteral (JSDecimal '1e-18'))"
+ testLiteral "1E-01" `shouldBe` "Right (JSAstLiteral (JSDecimal '1E-01'))"
+ it "octal numbers" $ do
+ testLiteral "070" `shouldBe` "Right (JSAstLiteral (JSOctal '070'))"
+ testLiteral "010234567" `shouldBe` "Right (JSAstLiteral (JSOctal '010234567'))"
+ it "strings" $ do
+ testLiteral "'cat'" `shouldBe` "Right (JSAstLiteral (JSStringLiteral 'cat'))"
+ testLiteral "\"cat\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"cat\"))"
+ testLiteral "'\\u1234'" `shouldBe` "Right (JSAstLiteral (JSStringLiteral '\\u1234'))"
+ testLiteral "'\\uabcd'" `shouldBe` "Right (JSAstLiteral (JSStringLiteral '\\uabcd'))"
+ testLiteral "\"\\r\\n\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\r\\n\"))"
+ testLiteral "\"\\b\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\b\"))"
+ testLiteral "\"\\f\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\f\"))"
+ testLiteral "\"\\t\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\t\"))"
+ testLiteral "\"\\v\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\v\"))"
+ testLiteral "\"\\0\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\0\"))"
+ testLiteral "\"hello\\nworld\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"hello\\nworld\"))"
+ testLiteral "'hello\\nworld'" `shouldBe` "Right (JSAstLiteral (JSStringLiteral 'hello\\nworld'))"
+
+ testLiteral "'char \n'" `shouldBe` "Left (\"lexical error @ line 1 and column 7\")"
+
+ forM_ (mkTestStrings SingleQuote) $ \ str ->
+ testLiteral str `shouldBe` ("Right (JSAstLiteral (JSStringLiteral " ++ str ++ "))")
+
+ forM_ (mkTestStrings DoubleQuote) $ \ str ->
+ testLiteral str `shouldBe` ("Right (JSAstLiteral (JSStringLiteral " ++ str ++ "))")
+
+ it "strings with escaped quotes" $ do
+ testLiteral "'\"'" `shouldBe` "Right (JSAstLiteral (JSStringLiteral '\"'))"
+ testLiteral "\"\\\"\"" `shouldBe` "Right (JSAstLiteral (JSStringLiteral \"\\\"\"))"
+
+
+data Quote
+ = SingleQuote
+ | DoubleQuote
+ deriving Eq
+
+
+mkTestStrings :: Quote -> [String]
+mkTestStrings quote =
+ map mkString [0 .. 255]
+ where
+ mkString :: Int -> String
+ mkString i =
+ quoteString $ "char #" ++ show i ++ " " ++ showCh i
+
+ showCh :: Int -> String
+ showCh ch
+ | ch == 34 = if quote == DoubleQuote then "\\\"" else "\""
+ | ch == 39 = if quote == SingleQuote then "\\\'" else "'"
+ | ch == 92 = "\\\\"
+ | ch < 127 && isPrint (chr ch) = [chr ch]
+ | otherwise =
+ let str = "000" ++ show ch
+ slen = length str
+ in "\\" ++ drop (slen - 3) str
+
+ quoteString s =
+ if quote == SingleQuote
+ then '\'' : (s ++ "'")
+ else '"' : (s ++ ['"'])
+
+
+testLiteral :: String -> String
+testLiteral str = showStrippedMaybe $ parseUsing parseLiteral str "src"
--- /dev/null
+module Test.Language.Javascript.Minify
+ ( testMinifyExpr
+ , testMinifyStmt
+ , testMinifyProg
+ , testMinifyModule
+ ) where
+
+import Control.Monad (forM_)
+import Test.Hspec
+
+import Language.JavaScript.Parser hiding (parseModule)
+import Language.JavaScript.Parser.Grammar7
+import Language.JavaScript.Parser.Lexer (Alex)
+import Language.JavaScript.Parser.Parser hiding (parseModule)
+import Language.JavaScript.Process.Minify
+import qualified Language.JavaScript.Parser.AST as AST
+
+
+testMinifyExpr :: Spec
+testMinifyExpr = describe "Minify expressions:" $ do
+ it "terminals" $ do
+ minifyExpr " identifier " `shouldBe` "identifier"
+ minifyExpr " 1 " `shouldBe` "1"
+ minifyExpr " this " `shouldBe` "this"
+ minifyExpr " 0x12ab " `shouldBe` "0x12ab"
+ minifyExpr " 0567 " `shouldBe` "0567"
+ minifyExpr " 'helo' " `shouldBe` "'helo'"
+ minifyExpr " \"good bye\" " `shouldBe` "\"good bye\""
+ minifyExpr " /\\n/g " `shouldBe` "/\\n/g"
+
+ it "array literals" $ do
+ minifyExpr " [ ] " `shouldBe` "[]"
+ minifyExpr " [ , ] " `shouldBe` "[,]"
+ minifyExpr " [ , , ] " `shouldBe` "[,,]"
+ minifyExpr " [ x ] " `shouldBe` "[x]"
+ minifyExpr " [ x , y ] " `shouldBe` "[x,y]"
+
+ it "object literals" $ do
+ minifyExpr " { } " `shouldBe` "{}"
+ minifyExpr " { a : 1 } " `shouldBe` "{a:1}"
+ minifyExpr " { b : 2 , } " `shouldBe` "{b:2}"
+ minifyExpr " { c : 3 , d : 4 , } " `shouldBe` "{c:3,d:4}"
+ minifyExpr " { 'str' : true , 42 : false , } " `shouldBe` "{'str':true,42:false}"
+ minifyExpr " { x , } " `shouldBe` "{x}"
+ minifyExpr " { [ x + y ] : 1 } " `shouldBe` "{[x+y]:1}"
+ minifyExpr " { a ( x, y ) { } } " `shouldBe` "{a(x,y){}}"
+ minifyExpr " { [ x + y ] ( ) { } } " `shouldBe` "{[x+y](){}}"
+ minifyExpr " { * a ( x, y ) { } } " `shouldBe` "{*a(x,y){}}"
+
+ it "parentheses" $ do
+ minifyExpr " ( 'hello' ) " `shouldBe` "('hello')"
+ minifyExpr " ( 12 ) " `shouldBe` "(12)"
+ minifyExpr " ( 1 + 2 ) " `shouldBe` "(1+2)"
+
+ it "unary" $ do
+ minifyExpr " a -- " `shouldBe` "a--"
+ minifyExpr " delete b " `shouldBe` "delete b"
+ minifyExpr " c ++ " `shouldBe` "c++"
+ minifyExpr " - d " `shouldBe` "-d"
+ minifyExpr " ! e " `shouldBe` "!e"
+ minifyExpr " + f " `shouldBe` "+f"
+ minifyExpr " ~ g " `shouldBe` "~g"
+ minifyExpr " typeof h " `shouldBe` "typeof h"
+ minifyExpr " void i " `shouldBe` "void i"
+
+ it "binary" $ do
+ minifyExpr " a && z " `shouldBe` "a&&z"
+ minifyExpr " b & z " `shouldBe` "b&z"
+ minifyExpr " c | z " `shouldBe` "c|z"
+ minifyExpr " d ^ z " `shouldBe` "d^z"
+ minifyExpr " e / z " `shouldBe` "e/z"
+ minifyExpr " f == z " `shouldBe` "f==z"
+ minifyExpr " g >= z " `shouldBe` "g>=z"
+ minifyExpr " h > z " `shouldBe` "h>z"
+ minifyExpr " i in z " `shouldBe` "i in z"
+ minifyExpr " j instanceof z " `shouldBe` "j instanceof z"
+ minifyExpr " k <= z " `shouldBe` "k<=z"
+ minifyExpr " l << z " `shouldBe` "l<<z"
+ minifyExpr " m < z " `shouldBe` "m<z"
+ minifyExpr " n - z " `shouldBe` "n-z"
+ minifyExpr " o % z " `shouldBe` "o%z"
+ minifyExpr " p != z " `shouldBe` "p!=z"
+ minifyExpr " q || z " `shouldBe` "q||z"
+ minifyExpr " r + z " `shouldBe` "r+z"
+ minifyExpr " s >> z " `shouldBe` "s>>z"
+ minifyExpr " t === z " `shouldBe` "t===z"
+ minifyExpr " u !== z " `shouldBe` "u!==z"
+ minifyExpr " v * z " `shouldBe` "v*z"
+ minifyExpr " w >>> z " `shouldBe` "w>>>z"
+
+ it "ternary" $ do
+ minifyExpr " true ? 1 : 2 " `shouldBe` "true?1:2"
+ minifyExpr " x ? y + 1 : j - 1 " `shouldBe` "x?y+1:j-1"
+
+ it "member access" $ do
+ minifyExpr " a . b " `shouldBe` "a.b"
+ minifyExpr " c . d . e " `shouldBe` "c.d.e"
+
+ it "new" $ do
+ minifyExpr " new f ( ) " `shouldBe` "new f()"
+ minifyExpr " new g ( 1 ) " `shouldBe` "new g(1)"
+ minifyExpr " new h ( 1 , 2 ) " `shouldBe` "new h(1,2)"
+ minifyExpr " new k . x " `shouldBe` "new k.x"
+
+ it "array access" $ do
+ minifyExpr " i [ a ] " `shouldBe` "i[a]"
+ minifyExpr " j [ a ] [ b ]" `shouldBe` "j[a][b]"
+
+ it "function" $ do
+ minifyExpr " function ( ) { } " `shouldBe` "function(){}"
+ minifyExpr " function ( a ) { } " `shouldBe` "function(a){}"
+ minifyExpr " function ( a , b ) { return a + b ; } " `shouldBe` "function(a,b){return a+b}"
+ minifyExpr " function ( a , ...b ) { return b ; } " `shouldBe` "function(a,...b){return b}"
+ minifyExpr " function ( a = 1 , b = 2 ) { return a + b ; } " `shouldBe` "function(a=1,b=2){return a+b}"
+ minifyExpr " function ( [ a , b ] ) { return b ; } " `shouldBe` "function([a,b]){return b}"
+ minifyExpr " function ( { a , b , } ) { return a + b ; } " `shouldBe` "function({a,b}){return a+b}"
+
+ minifyExpr "a => {}" `shouldBe` "a=>{}"
+ minifyExpr "(a) => {}" `shouldBe` "(a)=>{}"
+ minifyExpr "( a ) => { a + 2 }" `shouldBe` "(a)=>a+2"
+ minifyExpr "(a, b) => a + b" `shouldBe` "(a,b)=>a+b"
+ minifyExpr "() => { 42 }" `shouldBe` "()=>42"
+ minifyExpr "(a, ...b) => b" `shouldBe` "(a,...b)=>b"
+ minifyExpr "(a = 1, b = 2) => a + b" `shouldBe` "(a=1,b=2)=>a+b"
+ minifyExpr "( [ a , b ] ) => a + b" `shouldBe` "([a,b])=>a+b"
+ minifyExpr "( { a , b , } ) => a + b" `shouldBe` "({a,b})=>a+b"
+
+ it "generator" $ do
+ minifyExpr " function * ( ) { } " `shouldBe` "function*(){}"
+ minifyExpr " function * ( a ) { yield * a ; } " `shouldBe` "function*(a){yield*a}"
+ minifyExpr " function * ( a , b ) { yield a + b ; } " `shouldBe` "function*(a,b){yield a+b}"
+
+ it "calls" $ do
+ minifyExpr " a ( ) " `shouldBe` "a()"
+ minifyExpr " b ( ) ( ) " `shouldBe` "b()()"
+ minifyExpr " c ( ) [ x ] " `shouldBe` "c()[x]"
+ minifyExpr " d ( ) . y " `shouldBe` "d().y"
+
+ it "property accessor" $ do
+ minifyExpr " { get foo ( ) { return x } } " `shouldBe` "{get foo(){return x}}"
+ minifyExpr " { set foo ( a ) { x = a } } " `shouldBe` "{set foo(a){x=a}}"
+ minifyExpr " { set foo ( [ a , b ] ) { x = a } } " `shouldBe` "{set foo([a,b]){x=a}}"
+
+ it "string concatenation" $ do
+ minifyExpr " 'ab' + \"cd\" " `shouldBe` "'abcd'"
+ minifyExpr " \"bc\" + 'de' " `shouldBe` "'bcde'"
+ minifyExpr " \"cd\" + 'ef' + 'gh' " `shouldBe` "'cdefgh'"
+
+ minifyExpr " 'de' + '\"fg\"' + 'hi' " `shouldBe` "'de\"fg\"hi'"
+ minifyExpr " 'ef' + \"'gh'\" + 'ij' " `shouldBe` "'ef\\'gh\\'ij'"
+
+ -- minifyExpr " 'de' + '\"fg\"' + 'hi' " `shouldBe` "'de\"fg\"hi'"
+ -- minifyExpr " 'ef' + \"'gh'\" + 'ij' " `shouldBe` "'ef'gh'ij'"
+
+ it "spread exporession" $
+ minifyExpr " ... x " `shouldBe` "...x"
+
+ it "template literal" $ do
+ minifyExpr " ` a + b + ${ c + d } + ... ` " `shouldBe` "` a + b + ${c+d} + ... `"
+ minifyExpr " tagger () ` a + b ` " `shouldBe` "tagger()` a + b `"
+
+ it "class" $ do
+ minifyExpr " class Foo {\n a() {\n return 0;\n };\n static [ b ] ( x ) {}\n } " `shouldBe` "class Foo{a(){return 0}static[b](x){}}"
+ minifyExpr " class { static get a() { return 0; } static set a(v) {} } " `shouldBe` "class{static get a(){return 0}static set a(v){}}"
+ minifyExpr " class { ; ; ; } " `shouldBe` "class{}"
+ minifyExpr " class Foo extends Bar {} " `shouldBe` "class Foo extends Bar{}"
+ minifyExpr " class extends (getBase()) {} " `shouldBe` "class extends(getBase()){}"
+ minifyExpr " class extends [ Bar1, Bar2 ][getBaseIndex()] {} " `shouldBe` "class extends[Bar1,Bar2][getBaseIndex()]{}"
+
+
+testMinifyStmt :: Spec
+testMinifyStmt = describe "Minify statements:" $ do
+ forM_ [ "break", "continue", "return" ] $ \kw ->
+ it kw $ do
+ minifyStmt (" " ++ kw ++ " ; ") `shouldBe` kw
+ minifyStmt (" {" ++ kw ++ " ;} ") `shouldBe` kw
+ minifyStmt (" " ++ kw ++ " x ; ") `shouldBe` (kw ++ " x")
+ minifyStmt ("\n\n" ++ kw ++ " x ;\n") `shouldBe` (kw ++ " x")
+
+ it "block" $ do
+ minifyStmt "\n{ a = 1\nb = 2\n } " `shouldBe` "{a=1;b=2}"
+ minifyStmt " { c = 3 ; d = 4 ; } " `shouldBe` "{c=3;d=4}"
+ minifyStmt " { ; e = 1 } " `shouldBe` "e=1"
+ minifyStmt " { { } ; f = 1 ; { } ; } ; " `shouldBe` "f=1"
+
+ it "if" $ do
+ minifyStmt " if ( 1 ) return ; " `shouldBe` "if(1)return"
+ minifyStmt " if ( 1 ) ; " `shouldBe` "if(1);"
+
+ it "if/else" $ do
+ minifyStmt " if ( a ) ; else break ; " `shouldBe` "if(a);else break"
+ minifyStmt " if ( b ) break ; else break ; " `shouldBe` "if(b){break}else break"
+ minifyStmt " if ( c ) continue ; else continue ; " `shouldBe` "if(c){continue}else continue"
+ minifyStmt " if ( d ) return ; else return ; " `shouldBe` "if(d){return}else return"
+ minifyStmt " if ( e ) { b = 1 } else c = 2 ;" `shouldBe` "if(e){b=1}else c=2"
+ minifyStmt " if ( f ) { b = 1 } else { c = 2 ; d = 4 ; } ;" `shouldBe` "if(f){b=1}else{c=2;d=4}"
+ minifyStmt " if ( g ) { ex ; } else { ex ; } ; " `shouldBe` "if(g){ex}else ex"
+ minifyStmt " if ( h ) ; else if ( 2 ){ 3 ; } " `shouldBe` "if(h);else if(2)3"
+
+ it "while" $ do
+ minifyStmt " while ( x < 2 ) x ++ ; " `shouldBe` "while(x<2)x++"
+ minifyStmt " while ( x < 0x12 && y > 1 ) { x *= 3 ; y += 1 ; } ; " `shouldBe` "while(x<0x12&&y>1){x*=3;y+=1}"
+
+ it "do/while" $ do
+ minifyStmt " do x = foo (y) ; while ( x < y ) ; " `shouldBe` "do{x=foo(y)}while(x<y)"
+ minifyStmt " do { x = foo (x, y) ; y -- ; } while ( x > y ) ; " `shouldBe` "do{x=foo(x,y);y--}while(x>y)"
+
+ it "for" $ do
+ minifyStmt " for ( ; ; ) ; " `shouldBe` "for(;;);"
+ minifyStmt " for ( k = 0 ; k <= 10 ; k ++ ) ; " `shouldBe` "for(k=0;k<=10;k++);"
+ minifyStmt " for ( k = 0, j = 1 ; k <= 10 && j < 10 ; k ++ , j -- ) ; " `shouldBe` "for(k=0,j=1;k<=10&&j<10;k++,j--);"
+ minifyStmt " for (var x ; y ; z) { } " `shouldBe` "for(var x;y;z){}"
+ minifyStmt " for ( x in 5 ) foo (x) ;" `shouldBe` "for(x in 5)foo(x)"
+ minifyStmt " for ( var x in 5 ) { foo ( x++ ); y ++ ; } ;" `shouldBe` "for(var x in 5){foo(x++);y++}"
+ minifyStmt " for (let x ; y ; z) { } " `shouldBe` "for(let x;y;z){}"
+ minifyStmt " for ( let x in 5 ) { foo ( x++ ); y ++ ; } ;" `shouldBe` "for(let x in 5){foo(x++);y++}"
+ minifyStmt " for ( let x of 5 ) { foo ( x++ ); y ++ ; } ;" `shouldBe` "for(let x of 5){foo(x++);y++}"
+ minifyStmt " for (const x ; y ; z) { } " `shouldBe` "for(const x;y;z){}"
+ minifyStmt " for ( const x in 5 ) { foo ( x ); y ++ ; } ;" `shouldBe` "for(const x in 5){foo(x);y++}"
+ minifyStmt " for ( const x of 5 ) { foo ( x ); y ++ ; } ;" `shouldBe` "for(const x of 5){foo(x);y++}"
+ minifyStmt " for ( x of 5 ) { foo ( x++ ); y ++ ; } ;" `shouldBe` "for(x of 5){foo(x++);y++}"
+ minifyStmt " for ( var x of 5 ) { foo ( x++ ); y ++ ; } ;" `shouldBe` "for(var x of 5){foo(x++);y++}"
+ it "labelled" $ do
+ minifyStmt " start : while ( true ) { if ( i ++ < 3 ) continue start ; break ; } ; " `shouldBe` "start:while(true){if(i++<3)continue start;break}"
+ minifyStmt " { k ++ ; start : while ( true ) { if ( i ++ < 3 ) continue start ; break ; } ; } ; " `shouldBe` "{k++;start:while(true){if(i++<3)continue start;break}}"
+
+ it "function" $ do
+ minifyStmt " function f ( ) { } ; " `shouldBe` "function f(){}"
+ minifyStmt " function f ( a ) { } ; " `shouldBe` "function f(a){}"
+ minifyStmt " function f ( a , b ) { return a + b ; } ; " `shouldBe` "function f(a,b){return a+b}"
+ minifyStmt " function f ( a , ... b ) { return b ; } ; " `shouldBe` "function f(a,...b){return b}"
+ minifyStmt " function f ( a = 1 , b = 2 ) { return a + b ; } ; " `shouldBe` "function f(a=1,b=2){return a+b}"
+ minifyStmt " function f ( [ a , b ] ) { return a + b ; } ; " `shouldBe` "function f([a,b]){return a+b}"
+ minifyStmt " function f ( { a , b , } ) { return a + b ; } ; " `shouldBe` "function f({a,b}){return a+b}"
+ minifyStmt " async function f ( ) { } " `shouldBe` "async function f(){}"
+
+ it "generator" $ do
+ minifyStmt " function * f ( ) { } ; " `shouldBe` "function*f(){}"
+ minifyStmt " function * f ( a ) { yield * a ; } ; " `shouldBe` "function*f(a){yield*a}"
+ minifyStmt " function * f ( a , b ) { yield a + b ; } ; " `shouldBe` "function*f(a,b){yield a+b}"
+
+ it "with" $ do
+ minifyStmt " with ( x ) { } ; " `shouldBe` "with(x){}"
+ minifyStmt " with ({ first: 'John' }) { foo ('Hello '+first); }" `shouldBe` "with({first:'John'})foo('Hello '+first)"
+
+ it "throw" $ do
+ minifyStmt " throw a " `shouldBe` "throw a"
+ minifyStmt " throw b ; " `shouldBe` "throw b"
+ minifyStmt " { throw c ; } ;" `shouldBe` "throw c"
+
+ it "switch" $ do
+ minifyStmt " switch ( a ) { } ; " `shouldBe` "switch(a){}"
+ minifyStmt " switch ( b ) { case 1 : 1 ; case 2 : 2 ; } ;" `shouldBe` "switch(b){case 1:1;case 2:2}"
+ minifyStmt " switch ( c ) { case 1 : case 'a': case \"b\" : break ; default : break ; } ; " `shouldBe` "switch(c){case 1:case'a':case\"b\":break;default:break}"
+ minifyStmt " switch ( d ) { default : if (a) {x} else y ; if (b) { x } else y ; }" `shouldBe` "switch(d){default:if(a){x}else y;if(b){x}else y}"
+
+ it "try/catch/finally" $ do
+ minifyStmt " try { } catch ( a ) { } " `shouldBe` "try{}catch(a){}"
+ minifyStmt " try { b } finally { } " `shouldBe` "try{b}finally{}"
+ minifyStmt " try { } catch ( c ) { } finally { } " `shouldBe` "try{}catch(c){}finally{}"
+ minifyStmt " try { } catch ( d ) { } catch ( x ){ } finally { } " `shouldBe` "try{}catch(d){}catch(x){}finally{}"
+ minifyStmt " try { } catch ( e ) { } catch ( y ) { } " `shouldBe` "try{}catch(e){}catch(y){}"
+ minifyStmt " try { } catch ( f if f == x ) { } catch ( z ) { } " `shouldBe` "try{}catch(f if f==x){}catch(z){}"
+
+ it "variable declaration" $ do
+ minifyStmt " var a " `shouldBe` "var a"
+ minifyStmt " var b ; " `shouldBe` "var b"
+ minifyStmt " var c = 1 ; " `shouldBe` "var c=1"
+ minifyStmt " var d = 1, x = 2 ; " `shouldBe` "var d=1,x=2"
+ minifyStmt " let c = 1 ; " `shouldBe` "let c=1"
+ minifyStmt " let d = 1, x = 2 ; " `shouldBe` "let d=1,x=2"
+ minifyStmt " const { a : [ b , c ] } = d; " `shouldBe` "const{a:[b,c]}=d"
+
+ it "string concatenation" $
+ minifyStmt " f (\"ab\"+\"cd\") " `shouldBe` "f('abcd')"
+
+ it "class" $ do
+ minifyStmt " class Foo {\n a() {\n return 0;\n }\n static b ( x ) {}\n } " `shouldBe` "class Foo{a(){return 0}static b(x){}}"
+ minifyStmt " class Foo extends Bar {} " `shouldBe` "class Foo extends Bar{}"
+ minifyStmt " class Foo extends (getBase()) {} " `shouldBe` "class Foo extends(getBase()){}"
+ minifyStmt " class Foo extends [ Bar1, Bar2 ][getBaseIndex()] {} " `shouldBe` "class Foo extends[Bar1,Bar2][getBaseIndex()]{}"
+
+ it "miscellaneous" $
+ minifyStmt " let r = await p ; " `shouldBe` "let r=await p"
+
+testMinifyProg :: Spec
+testMinifyProg = describe "Minify programs:" $ do
+ it "simple" $ do
+ minifyProg " a = f ? e : g ; " `shouldBe` "a=f?e:g"
+ minifyProg " for ( i = 0 ; ; ) { ; var t = 1 ; } " `shouldBe` "for(i=0;;)var t=1"
+ it "if" $
+ minifyProg " if ( x ) { } ; t ; " `shouldBe` "if(x);t"
+ it "if/else" $ do
+ minifyProg " if ( a ) { } else { } ; break ; " `shouldBe` "if(a){}else;break"
+ minifyProg " if ( b ) {x = 1} else {x = 2} f () ; " `shouldBe` "if(b){x=1}else x=2;f()"
+ it "empty block" $ do
+ minifyProg " a = 1 ; { } ; " `shouldBe` "a=1"
+ minifyProg " { } ; b = 1 ; " `shouldBe` "b=1"
+ it "empty statement" $ do
+ minifyProg " a = 1 + b ; c ; ; { d ; } ; " `shouldBe` "a=1+b;c;d"
+ minifyProg " b = a + 2 ; c ; { d ; } ; ; " `shouldBe` "b=a+2;c;d"
+ it "nested block" $ do
+ minifyProg "{a;;x;};y;z;;" `shouldBe` "a;x;y;z"
+ minifyProg "{b;;{x;y;};};z;;" `shouldBe` "b;x;y;z"
+ it "functions" $
+ minifyProg " function f() {} ; function g() {} ;" `shouldBe` "function f(){}\nfunction g(){}"
+ it "variable declaration" $ do
+ minifyProg " var a = 1 ; var b = 2 ;" `shouldBe` "var a=1,b=2"
+ minifyProg " var c=1;var d=2;var e=3;" `shouldBe` "var c=1,d=2,e=3"
+ minifyProg " const f = 1 ; const g = 2 ;" `shouldBe` "const f=1,g=2"
+ minifyProg " var h = 1 ; const i = 2 ;" `shouldBe` "var h=1;const i=2"
+ it "try/catch/finally" $
+ minifyProg " try { } catch (a) {} finally {} ; try { } catch ( b ) { } ; " `shouldBe` "try{}catch(a){}finally{}try{}catch(b){}"
+
+testMinifyModule :: Spec
+testMinifyModule = describe "Minify modules:" $ do
+ it "import" $ do
+ minifyModule "import def from 'mod' ; " `shouldBe` "import def from'mod'"
+ minifyModule "import * as foo from \"mod\" ; " `shouldBe` "import * as foo from\"mod\""
+ minifyModule "import def, * as foo from \"mod\" ; " `shouldBe` "import def,* as foo from\"mod\""
+ minifyModule "import { baz, bar as foo } from \"mod\" ; " `shouldBe` "import{baz,bar as foo}from\"mod\""
+ minifyModule "import def, { baz, bar as foo } from \"mod\" ; " `shouldBe` "import def,{baz,bar as foo}from\"mod\""
+ minifyModule "import \"mod\" ; " `shouldBe` "import\"mod\""
+
+ it "export" $ do
+ minifyModule " export { } ; " `shouldBe` "export{}"
+ minifyModule " export { a } ; " `shouldBe` "export{a}"
+ minifyModule " export { a, b } ; " `shouldBe` "export{a,b}"
+ minifyModule " export { a, b as c , d } ; " `shouldBe` "export{a,b as c,d}"
+ minifyModule " export { } from \"mod\" ; " `shouldBe` "export{}from\"mod\""
+ minifyModule " export const a = 1 ; " `shouldBe` "export const a=1"
+ minifyModule " export function f () { } ; " `shouldBe` "export function f(){}"
+ minifyModule " export function * f () { } ; " `shouldBe` "export function*f(){}"
+
+-- -----------------------------------------------------------------------------
+-- Minify test helpers.
+
+minifyExpr :: String -> String
+minifyExpr = minifyWith parseExpression
+
+minifyStmt :: String -> String
+minifyStmt = minifyWith parseStatement
+
+minifyProg :: String -> String
+minifyProg = minifyWith parseProgram
+
+minifyModule :: String -> String
+minifyModule = minifyWith parseModule
+
+minifyWith :: (Alex AST.JSAST) -> String -> String
+minifyWith p str = either id (renderToString . minifyJS) (parseUsing p str "src")
--- /dev/null
+module Test.Language.Javascript.ModuleParser
+ ( testModuleParser
+ ) where
+
+import Test.Hspec
+
+import Language.JavaScript.Parser
+
+
+testModuleParser :: Spec
+testModuleParser = describe "Parse modules:" $ do
+ it "as" $
+ test "as"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleStatementListItem (JSIdentifier 'as')])"
+
+ it "import" $ do
+ -- Not yet supported
+ -- test "import 'a';" `shouldBe` ""
+
+ test "import def from 'mod';"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefault (JSIdentifier 'def'),JSFromClause ''mod''))])"
+ test "import def from \"mod\";"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefault (JSIdentifier 'def'),JSFromClause '\"mod\"'))])"
+ test "import * as thing from 'mod';"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseNameSpace (JSImportNameSpace (JSIdentifier 'thing')),JSFromClause ''mod''))])"
+ test "import { foo, bar, baz as quux } from 'mod';"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseNameSpace (JSImportsNamed ((JSImportSpecifier (JSIdentifier 'foo'),JSImportSpecifier (JSIdentifier 'bar'),JSImportSpecifierAs (JSIdentifier 'baz',JSIdentifier 'quux')))),JSFromClause ''mod''))])"
+ test "import def, * as thing from 'mod';"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefaultNameSpace (JSIdentifier 'def',JSImportNameSpace (JSIdentifier 'thing')),JSFromClause ''mod''))])"
+ test "import def, { foo, bar, baz as quux } from 'mod';"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleImportDeclaration (JSImportDeclaration (JSImportClauseDefaultNamed (JSIdentifier 'def',JSImportsNamed ((JSImportSpecifier (JSIdentifier 'foo'),JSImportSpecifier (JSIdentifier 'bar'),JSImportSpecifierAs (JSIdentifier 'baz',JSIdentifier 'quux')))),JSFromClause ''mod''))])"
+
+ it "export" $ do
+ test "export {}"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExportLocals (JSExportClause (())))])"
+ test "export {};"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExportLocals (JSExportClause (())))])"
+ test "export const a = 1;"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExport (JSConstant (JSVarInitExpression (JSIdentifier 'a') [JSDecimal '1'])))])"
+ test "export function f() {};"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExport (JSFunction 'f' () (JSBlock [])))])"
+ test "export { a };"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExportLocals (JSExportClause ((JSExportSpecifier (JSIdentifier 'a')))))])"
+ test "export { a as b };"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExportLocals (JSExportClause ((JSExportSpecifierAs (JSIdentifier 'a',JSIdentifier 'b')))))])"
+ test "export {} from 'mod'"
+ `shouldBe`
+ "Right (JSAstModule [JSModuleExportDeclaration (JSExportFrom (JSExportClause (()),JSFromClause ''mod''))])"
+
+
+test :: String -> String
+test str = showStrippedMaybe (parseModule str "src")
--- /dev/null
+{-# LANGUAGE CPP #-}
+module Test.Language.Javascript.ProgramParser
+ ( testProgramParser
+ ) where
+
+#if ! MIN_VERSION_base(4,13,0)
+import Control.Applicative ((<$>))
+#endif
+import Test.Hspec
+
+import Language.JavaScript.Parser
+import Language.JavaScript.Parser.Grammar7
+import Language.JavaScript.Parser.Parser
+
+
+testProgramParser :: Spec
+testProgramParser = describe "Program parser:" $ do
+ it "function" $ do
+ testProg "function a(){}" `shouldBe` "Right (JSAstProgram [JSFunction 'a' () (JSBlock [])])"
+ testProg "function a(b,c){}" `shouldBe` "Right (JSAstProgram [JSFunction 'a' (JSIdentifier 'b',JSIdentifier 'c') (JSBlock [])])"
+ it "comments" $ do
+ testProg "//blah\nx=1;//foo\na" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon,JSIdentifier 'a'])"
+ testProg "/*x=1\ny=2\n*/z=2;//foo\na" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'z',JSDecimal '2'),JSSemicolon,JSIdentifier 'a'])"
+ testProg "/* */\nfunction f() {\n/* */\n}\n" `shouldBe` "Right (JSAstProgram [JSFunction 'f' () (JSBlock [])])"
+ testProg "/* **/\nfunction f() {\n/* */\n}\n" `shouldBe` "Right (JSAstProgram [JSFunction 'f' () (JSBlock [])])"
+
+ it "if" $ do
+ testProg "if(x);x=1" `shouldBe` "Right (JSAstProgram [JSIf (JSIdentifier 'x') (JSEmptyStatement),JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1')])"
+ testProg "if(a)x=1;y=2" `shouldBe` "Right (JSAstProgram [JSIf (JSIdentifier 'a') (JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon),JSOpAssign ('=',JSIdentifier 'y',JSDecimal '2')])"
+ testProg "if(a)x=a()y=2" `shouldBe` "Right (JSAstProgram [JSIf (JSIdentifier 'a') (JSOpAssign ('=',JSIdentifier 'x',JSMemberExpression (JSIdentifier 'a',JSArguments ()))),JSOpAssign ('=',JSIdentifier 'y',JSDecimal '2')])"
+ testProg "if(true)break \nfoo();" `shouldBe` "Right (JSAstProgram [JSIf (JSLiteral 'true') (JSBreak),JSMethodCall (JSIdentifier 'foo',JSArguments ()),JSSemicolon])"
+ testProg "if(true)continue \nfoo();" `shouldBe` "Right (JSAstProgram [JSIf (JSLiteral 'true') (JSContinue),JSMethodCall (JSIdentifier 'foo',JSArguments ()),JSSemicolon])"
+ testProg "if(true)break \nfoo();" `shouldBe` "Right (JSAstProgram [JSIf (JSLiteral 'true') (JSBreak),JSMethodCall (JSIdentifier 'foo',JSArguments ()),JSSemicolon])"
+
+ it "assign" $
+ testProg "x = 1\n y=2;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSOpAssign ('=',JSIdentifier 'y',JSDecimal '2'),JSSemicolon])"
+
+ it "regex" $ do
+ testProg "x=/\\n/g" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSRegEx '/\\n/g')])"
+ testProg "x=i(/^$/g,\"\\\\$&\")" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSMemberExpression (JSIdentifier 'i',JSArguments (JSRegEx '/^$/g',JSStringLiteral \"\\\\$&\")))])"
+ testProg "x=i(/[?|^&(){}\\[\\]+\\-*\\/\\.]/g,\"\\\\$&\")" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSMemberExpression (JSIdentifier 'i',JSArguments (JSRegEx '/[?|^&(){}\\[\\]+\\-*\\/\\.]/g',JSStringLiteral \"\\\\$&\")))])"
+ testProg "(match = /^\"(?:\\\\.|[^\"])*\"|^'(?:[^']|\\\\.)*'/(input))" `shouldBe` "Right (JSAstProgram [JSExpressionParen (JSOpAssign ('=',JSIdentifier 'match',JSMemberExpression (JSRegEx '/^\"(?:\\\\.|[^\"])*\"|^'(?:[^']|\\\\.)*'/',JSArguments (JSIdentifier 'input'))))])"
+ testProg "if(/^[a-z]/.test(t)){consts+=t.toUpperCase();keywords[t]=i}else consts+=(/^\\W/.test(t)?opTypeNames[t]:t);"
+ `shouldBe` "Right (JSAstProgram [JSIfElse (JSMemberExpression (JSMemberDot (JSRegEx '/^[a-z]/',JSIdentifier 'test'),JSArguments (JSIdentifier 't'))) (JSStatementBlock [JSOpAssign ('+=',JSIdentifier 'consts',JSMemberExpression (JSMemberDot (JSIdentifier 't',JSIdentifier 'toUpperCase'),JSArguments ())),JSSemicolon,JSOpAssign ('=',JSMemberSquare (JSIdentifier 'keywords',JSIdentifier 't'),JSIdentifier 'i')]) (JSOpAssign ('+=',JSIdentifier 'consts',JSExpressionParen (JSExpressionTernary (JSMemberExpression (JSMemberDot (JSRegEx '/^\\W/',JSIdentifier 'test'),JSArguments (JSIdentifier 't')),JSMemberSquare (JSIdentifier 'opTypeNames',JSIdentifier 't'),JSIdentifier 't'))),JSSemicolon)])"
+
+ it "unicode" $ do
+ testProg "àáâãäå = 1;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier '\224\225\226\227\228\229',JSDecimal '1'),JSSemicolon])"
+ testProg "//comment\x000Ax=1;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon])"
+ testProg "//comment\x000Dx=1;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon])"
+ testProg "//comment\x2028x=1;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon])"
+ testProg "//comment\x2029x=1;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon])"
+ testProg "$aà = 1;_b=2;\0065a=2" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier '$a\224',JSDecimal '1'),JSSemicolon,JSOpAssign ('=',JSIdentifier '_b',JSDecimal '2'),JSSemicolon,JSOpAssign ('=',JSIdentifier 'Aa',JSDecimal '2')])"
+ testProg "x=\"àáâãäå\";y='\3012a\0068'" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral \"\224\225\226\227\228\229\"),JSSemicolon,JSOpAssign ('=',JSIdentifier 'y',JSStringLiteral '\3012aD')])"
+ testProg "a \f\v\t\r\n=\x00a0\x1680\x180e\x2000\x2001\x2002\x2003\x2004\x2005\x2006\x2007\x2008\x2009\x200a\x2028\x2029\x202f\x205f\x3000\&1;" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'a',JSDecimal '1'),JSSemicolon])"
+ testProg "/* * geolocation. пытаемся определить свое местоположение * если не получается то используем defaultLocation * @Param {object} map экземпляр карты * @Param {object LatLng} defaultLocation Координаты центра по умолчанию * @Param {function} callbackAfterLocation Фу-ия которая вызывается после * геолокации. Т.к запрос геолокации асинхронен */x" `shouldBe` "Right (JSAstProgram [JSIdentifier 'x'])"
+ testFileUtf8 "./test/Unicode.js" `shouldReturn` "JSAstProgram [JSOpAssign ('=',JSIdentifier '\224\225\226\227\228\229',JSDecimal '1'),JSSemicolon]"
+
+ it "strings" $ do
+ -- Working in ECMASCRIPT 5.1 changes
+ testProg "x='abc\\ndef';" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral 'abc\\ndef'),JSSemicolon])"
+ testProg "x=\"abc\\ndef\";" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral \"abc\\ndef\"),JSSemicolon])"
+ testProg "x=\"abc\\rdef\";" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral \"abc\\rdef\"),JSSemicolon])"
+ testProg "x=\"abc\\r\\ndef\";" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral \"abc\\r\\ndef\"),JSSemicolon])"
+ testProg "x=\"abc\\x2028 def\";" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral \"abc\\x2028 def\"),JSSemicolon])"
+ testProg "x=\"abc\\x2029 def\";" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSStringLiteral \"abc\\x2029 def\"),JSSemicolon])"
+
+ it "object literal" $ do
+ testProg "x = { y: 1e8 }" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'y') [JSDecimal '1e8']])])"
+ testProg "{ y: 1e8 }" `shouldBe` "Right (JSAstProgram [JSStatementBlock [JSLabelled (JSIdentifier 'y') (JSDecimal '1e8')]])"
+ testProg "{ y: 18 }" `shouldBe` "Right (JSAstProgram [JSStatementBlock [JSLabelled (JSIdentifier 'y') (JSDecimal '18')]])"
+ testProg "x = { y: 18 }" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'x',JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'y') [JSDecimal '18']])])"
+ testProg "var k = {\ny: somename\n}" `shouldBe` "Right (JSAstProgram [JSVariable (JSVarInitExpression (JSIdentifier 'k') [JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'y') [JSIdentifier 'somename']]])])"
+ testProg "var k = {\ny: code\n}" `shouldBe` "Right (JSAstProgram [JSVariable (JSVarInitExpression (JSIdentifier 'k') [JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'y') [JSIdentifier 'code']]])])"
+ testProg "var k = {\ny: mode\n}" `shouldBe` "Right (JSAstProgram [JSVariable (JSVarInitExpression (JSIdentifier 'k') [JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'y') [JSIdentifier 'mode']]])])"
+
+ it "programs" $ do
+ testProg "newlines=spaces.match(/\\n/g)" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'newlines',JSMemberExpression (JSMemberDot (JSIdentifier 'spaces',JSIdentifier 'match'),JSArguments (JSRegEx '/\\n/g')))])"
+ testProg "Animal=function(){return this.name};" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'Animal',JSFunctionExpression '' () (JSBlock [JSReturn JSMemberDot (JSLiteral 'this',JSIdentifier 'name') ])),JSSemicolon])"
+ testProg "$(img).click(function(){alert('clicked!')});" `shouldBe` "Right (JSAstProgram [JSCallExpression (JSCallExpressionDot (JSMemberExpression (JSIdentifier '$',JSArguments (JSIdentifier 'img')),JSIdentifier 'click'),JSArguments (JSFunctionExpression '' () (JSBlock [JSMethodCall (JSIdentifier 'alert',JSArguments (JSStringLiteral 'clicked!'))]))),JSSemicolon])"
+ testProg "function() {\nz = function z(o) {\nreturn r;\n};}" `shouldBe` "Right (JSAstProgram [JSFunctionExpression '' () (JSBlock [JSOpAssign ('=',JSIdentifier 'z',JSFunctionExpression 'z' (JSIdentifier 'o') (JSBlock [JSReturn JSIdentifier 'r' JSSemicolon])),JSSemicolon])])"
+ testProg "function() {\nz = function /*z*/(o) {\nreturn r;\n};}" `shouldBe` "Right (JSAstProgram [JSFunctionExpression '' () (JSBlock [JSOpAssign ('=',JSIdentifier 'z',JSFunctionExpression '' (JSIdentifier 'o') (JSBlock [JSReturn JSIdentifier 'r' JSSemicolon])),JSSemicolon])])"
+ testProg "{zero}\nget;two\n{three\nfour;set;\n{\nsix;{seven;}\n}\n}" `shouldBe` "Right (JSAstProgram [JSStatementBlock [JSIdentifier 'zero'],JSIdentifier 'get',JSSemicolon,JSIdentifier 'two',JSStatementBlock [JSIdentifier 'three',JSIdentifier 'four',JSSemicolon,JSIdentifier 'set',JSSemicolon,JSStatementBlock [JSIdentifier 'six',JSSemicolon,JSStatementBlock [JSIdentifier 'seven',JSSemicolon]]]])"
+ testProg "{zero}\none1;two\n{three\nfour;five;\n{\nsix;{seven;}\n}\n}" `shouldBe` "Right (JSAstProgram [JSStatementBlock [JSIdentifier 'zero'],JSIdentifier 'one1',JSSemicolon,JSIdentifier 'two',JSStatementBlock [JSIdentifier 'three',JSIdentifier 'four',JSSemicolon,JSIdentifier 'five',JSSemicolon,JSStatementBlock [JSIdentifier 'six',JSSemicolon,JSStatementBlock [JSIdentifier 'seven',JSSemicolon]]]])"
+ testProg "v = getValue(execute(n[0], x)) in getValue(execute(n[1], x));" `shouldBe` "Right (JSAstProgram [JSOpAssign ('=',JSIdentifier 'v',JSExpressionBinary ('in',JSMemberExpression (JSIdentifier 'getValue',JSArguments (JSMemberExpression (JSIdentifier 'execute',JSArguments (JSMemberSquare (JSIdentifier 'n',JSDecimal '0'),JSIdentifier 'x')))),JSMemberExpression (JSIdentifier 'getValue',JSArguments (JSMemberExpression (JSIdentifier 'execute',JSArguments (JSMemberSquare (JSIdentifier 'n',JSDecimal '1'),JSIdentifier 'x')))))),JSSemicolon])"
+ testProg "function Animal(name){if(!name)throw new Error('Must specify an animal name');this.name=name};Animal.prototype.toString=function(){return this.name};o=new Animal(\"bob\");o.toString()==\"bob\""
+ `shouldBe` "Right (JSAstProgram [JSFunction 'Animal' (JSIdentifier 'name') (JSBlock [JSIf (JSUnaryExpression ('!',JSIdentifier 'name')) (JSThrow (JSMemberNew (JSIdentifier 'Error',JSArguments (JSStringLiteral 'Must specify an animal name')))),JSOpAssign ('=',JSMemberDot (JSLiteral 'this',JSIdentifier 'name'),JSIdentifier 'name')]),JSOpAssign ('=',JSMemberDot (JSMemberDot (JSIdentifier 'Animal',JSIdentifier 'prototype'),JSIdentifier 'toString'),JSFunctionExpression '' () (JSBlock [JSReturn JSMemberDot (JSLiteral 'this',JSIdentifier 'name') ])),JSSemicolon,JSOpAssign ('=',JSIdentifier 'o',JSMemberNew (JSIdentifier 'Animal',JSArguments (JSStringLiteral \"bob\"))),JSSemicolon,JSExpressionBinary ('==',JSMemberExpression (JSMemberDot (JSIdentifier 'o',JSIdentifier 'toString'),JSArguments ()),JSStringLiteral \"bob\")])"
+
+
+testProg :: String -> String
+testProg str = showStrippedMaybe (parseUsing parseProgram str "src")
+
+testFileUtf8 :: FilePath -> IO String
+testFileUtf8 fileName = showStripped <$> parseFileUtf8 fileName
+
--- /dev/null
+module Test.Language.Javascript.RoundTrip
+ ( testRoundTrip
+ ) where
+
+import Test.Hspec
+
+import Language.JavaScript.Parser
+import qualified Language.JavaScript.Parser.AST as AST
+
+
+testRoundTrip :: Spec
+testRoundTrip = describe "Roundtrip:" $ do
+ it "multi comment" $ do
+ testRT "/*a*/\n//foo\nnull"
+ testRT "/*a*/x"
+ testRT "/*a*/null"
+ testRT "/*b*/false"
+ testRT "true/*c*/"
+ testRT "/*c*/true"
+ testRT "/*d*/0x1234fF"
+ testRT "/*e*/1.0e4"
+ testRT "/*x*/011"
+ testRT "/*f*/\"hello\\nworld\""
+ testRT "/*g*/'hello\\nworld'"
+ testRT "/*h*/this"
+ testRT "/*i*//blah/"
+ testRT "//j\nthis_"
+
+ it "arrays" $ do
+ testRT "/*a*/[/*b*/]"
+ testRT "/*a*/[/*b*/,/*c*/]"
+ testRT "/*a*/[/*b*/,/*c*/,/*d*/]"
+ testRT "/*a*/[/*b/*,/*c*/,/*d*/x/*e*/]"
+ testRT "/*a*/[/*b*/,/*c*/,/*d*/x/*e*/]"
+ testRT "/*a*/[/*b*/,/*c*/x/*d*/,/*e*/,/*f*/x/*g*/]"
+ testRT "/*a*/[/*b*/x/*c*/]"
+ testRT "/*a*/[/*b*/x/*c*/,/*d*/]"
+
+ it "object literals" $ do
+ testRT "/*a*/{/*b*/}"
+ testRT "/*a*/{/*b*/x/*c*/:/*d*/1/*e*/}"
+ testRT "/*a*/{/*b*/x/*c*/}"
+ testRT "/*a*/{/*b*/of/*c*/}"
+ testRT "x=/*a*/{/*b*/x/*c*/:/*d*/1/*e*/,/*f*/y/*g*/:/*h*/2/*i*/}"
+ testRT "x=/*a*/{/*b*/x/*c*/:/*d*/1/*e*/,/*f*/y/*g*/:/*h*/2/*i*/,/*j*/z/*k*/:/*l*/3/*m*/}"
+ testRT "a=/*a*/{/*b*/x/*c*/:/*d*/1/*e*/,/*f*/}"
+ testRT "/*a*/{/*b*/[/*c*/x/*d*/+/*e*/y/*f*/]/*g*/:/*h*/1/*i*/}"
+ testRT "/*a*/{/*b*/a/*c*/(/*d*/x/*e*/,/*f*/y/*g*/)/*h*/{/*i*/}/*j*/}"
+ testRT "/*a*/{/*b*/[/*c*/x/*d*/+/*e*/y/*f*/]/*g*/(/*h*/)/*i*/{/*j*/}/*k*/}"
+ testRT "/*a*/{/*b*/*/*c*/a/*d*/(/*e*/x/*f*/,/*g*/y/*h*/)/*i*/{/*j*/}/*k*/}"
+
+ it "miscellaneous" $ do
+ testRT "/*a*/(/*b*/56/*c*/)"
+ testRT "/*a*/true/*b*/?/*c*/1/*d*/:/*e*/2"
+ testRT "/*a*/x/*b*/||/*c*/y"
+ testRT "/*a*/x/*b*/&&/*c*/y"
+ testRT "/*a*/x/*b*/|/*c*/y"
+ testRT "/*a*/x/*b*/^/*c*/y"
+ testRT "/*a*/x/*b*/&/*c*/y"
+ testRT "/*a*/x/*b*/==/*c*/y"
+ testRT "/*a*/x/*b*/!=/*c*/y"
+ testRT "/*a*/x/*b*/===/*c*/y"
+ testRT "/*a*/x/*b*/!==/*c*/y"
+ testRT "/*a*/x/*b*/</*c*/y"
+ testRT "/*a*/x/*b*/>/*c*/y"
+ testRT "/*a*/x/*b*/<=/*c*/y"
+ testRT "/*a*/x/*b*/>=/*c*/y"
+ testRT "/*a*/x /*b*/instanceof /*c*/y"
+ testRT "/*a*/x/*b*/=/*c*/{/*d*/get/*e*/ foo/*f*/(/*g*/)/*h*/ {/*i*/return/*j*/ 1/*k*/}/*l*/,/*m*/set/*n*/ foo/*o*/(/*p*/a/*q*/) /*r*/{/*s*/x/*t*/=/*u*/a/*v*/}/*w*/}"
+ testRT "x = { set foo(/*a*/[/*b*/a/*c*/,/*d*/b/*e*/]/*f*/=/*g*/y/*h*/) {} }"
+ testRT "... /*a*/ x"
+
+ testRT "a => {}"
+ testRT "(a) => { a + 2 }"
+ testRT "(a, b) => {}"
+ testRT "(a, b) => a + b"
+ testRT "() => { 42 }"
+ testRT "(...a) => a"
+ testRT "(a=1, b=2) => a + b"
+ testRT "([a, b]) => a + b"
+ testRT "({a, b}) => a + b"
+
+ testRT "function (...a) {}"
+ testRT "function (a=1, b=2) {}"
+ testRT "function ([a, ...b]) {}"
+ testRT "function ({a, b: c}) {}"
+
+ testRT "/*a*/function/*b*/*/*c*/f/*d*/(/*e*/)/*f*/{/*g*/yield/*h*/a/*i*/}/*j*/"
+ testRT "function*(a, b) { yield a ; yield b ; }"
+
+ testRT "/*a*/`<${/*b*/x/*c*/}>`/*d*/"
+ testRT "`\\${}`"
+ testRT "`\n\n`"
+ testRT "{}+``"
+ -- ^ https://github.com/erikd/language-javascript/issues/104
+
+
+ it "statement" $ do
+ testRT "if (1) {}"
+ testRT "if (1) {} else {}"
+ testRT "if (1) x=1; else {}"
+ testRT "do {x=1} while (true);"
+ testRT "do x=x+1;while(x<4);"
+ testRT "while(true);"
+ testRT "for(;;);"
+ testRT "for(x=1;x<10;x++);"
+ testRT "for(var x;;);"
+ testRT "for(var x=1;;);"
+ testRT "for(var x;y;z){}"
+ testRT "for(x in 5){}"
+ testRT "for(var x in 5){}"
+ testRT "for(let x;y;z){}"
+ testRT "for(let x in 5){}"
+ testRT "for(let x of 5){}"
+ testRT "for(const x;y;z){}"
+ testRT "for(const x in 5){}"
+ testRT "for(const x of 5){}"
+ testRT "for(x of 5){}"
+ testRT "for(var x of 5){}"
+ testRT "var x=1;"
+ testRT "const x=1,y=2;"
+ testRT "continue;"
+ testRT "continue x;"
+ testRT "break;"
+ testRT "break x;"
+ testRT "return;"
+ testRT "return x;"
+ testRT "with (x) {};"
+ testRT "abc:x=1"
+ testRT "switch (x) {}"
+ testRT "switch (x) {case 1:break;}"
+ testRT "switch (x) {case 0:\ncase 1:break;}"
+ testRT "switch (x) {default:break;}"
+ testRT "switch (x) {default:\ncase 1:break;}"
+ testRT "var x=1;let y=2;"
+ testRT "var [x, y]=z;"
+ testRT "let {x: [y]}=z;"
+ testRT "let yield=1"
+
+ it "module" $ do
+ testRTModule "import def from 'mod'"
+ testRTModule "import def from \"mod\";"
+ testRTModule "import * as foo from \"mod\" ; "
+ testRTModule "import def, * as foo from \"mod\" ; "
+ testRTModule "import { baz, bar as foo } from \"mod\" ; "
+ testRTModule "import def, { baz, bar as foo } from \"mod\" ; "
+
+ testRTModule "export {};"
+ testRTModule " export {} ; "
+ testRTModule "export { a , b , c };"
+ testRTModule "export { a, X as B, c }"
+ testRTModule "export {} from \"mod\";"
+ testRTModule "export const a = 1 ; "
+ testRTModule "export function f () { } ; "
+ testRTModule "export function * f () { } ; "
+ testRTModule "export class Foo\nextends Bar\n{ get a () { return 1 ; } static b ( x,y ) {} ; } ; "
+
+
+testRT :: String -> Expectation
+testRT = testRTWith readJs
+
+testRTModule :: String -> Expectation
+testRTModule = testRTWith readJsModule
+
+testRTWith :: (String -> AST.JSAST) -> String -> Expectation
+testRTWith f str = renderToString (f str) `shouldBe` str
--- /dev/null
+module Test.Language.Javascript.StatementParser
+ ( testStatementParser
+ ) where
+
+
+import Test.Hspec
+
+import Language.JavaScript.Parser
+import Language.JavaScript.Parser.Grammar7
+import Language.JavaScript.Parser.Parser
+
+
+testStatementParser :: Spec
+testStatementParser = describe "Parse statements:" $ do
+ it "simple" $ do
+ testStmt "x" `shouldBe` "Right (JSAstStatement (JSIdentifier 'x'))"
+ testStmt "null" `shouldBe` "Right (JSAstStatement (JSLiteral 'null'))"
+ testStmt "true?1:2" `shouldBe` "Right (JSAstStatement (JSExpressionTernary (JSLiteral 'true',JSDecimal '1',JSDecimal '2')))"
+
+ it "block" $ do
+ testStmt "{}" `shouldBe` "Right (JSAstStatement (JSStatementBlock []))"
+ testStmt "{x=1}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1')]))"
+ testStmt "{x=1;y=2}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon,JSOpAssign ('=',JSIdentifier 'y',JSDecimal '2')]))"
+ testStmt "{{}}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSStatementBlock []]))"
+ testStmt "{{{}}}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSStatementBlock [JSStatementBlock []]]))"
+
+ it "if" $
+ testStmt "if (1) {}" `shouldBe` "Right (JSAstStatement (JSIf (JSDecimal '1') (JSStatementBlock [])))"
+
+ it "if/else" $ do
+ testStmt "if (1) {} else {}" `shouldBe` "Right (JSAstStatement (JSIfElse (JSDecimal '1') (JSStatementBlock []) (JSStatementBlock [])))"
+ testStmt "if (1) x=1; else {}" `shouldBe` "Right (JSAstStatement (JSIfElse (JSDecimal '1') (JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'),JSSemicolon) (JSStatementBlock [])))"
+ testStmt " if (1);else break" `shouldBe` "Right (JSAstStatement (JSIfElse (JSDecimal '1') (JSEmptyStatement) (JSBreak)))"
+
+ it "while" $
+ testStmt "while(true);" `shouldBe` "Right (JSAstStatement (JSWhile (JSLiteral 'true') (JSEmptyStatement)))"
+
+ it "do/while" $ do
+ testStmt "do {x=1} while (true);" `shouldBe` "Right (JSAstStatement (JSDoWhile (JSStatementBlock [JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1')]) (JSLiteral 'true') (JSSemicolon)))"
+ testStmt "do x=x+1;while(x<4);" `shouldBe` "Right (JSAstStatement (JSDoWhile (JSOpAssign ('=',JSIdentifier 'x',JSExpressionBinary ('+',JSIdentifier 'x',JSDecimal '1')),JSSemicolon) (JSExpressionBinary ('<',JSIdentifier 'x',JSDecimal '4')) (JSSemicolon)))"
+
+ it "for" $ do
+ testStmt "for(;;);" `shouldBe` "Right (JSAstStatement (JSFor () () () (JSEmptyStatement)))"
+ testStmt "for(x=1;x<10;x++);" `shouldBe` "Right (JSAstStatement (JSFor (JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1')) (JSExpressionBinary ('<',JSIdentifier 'x',JSDecimal '10')) (JSExpressionPostfix ('++',JSIdentifier 'x')) (JSEmptyStatement)))"
+
+ testStmt "for(var x;;);" `shouldBe` "Right (JSAstStatement (JSForVar (JSVarInitExpression (JSIdentifier 'x') ) () () (JSEmptyStatement)))"
+ testStmt "for(var x=1;;);" `shouldBe` "Right (JSAstStatement (JSForVar (JSVarInitExpression (JSIdentifier 'x') [JSDecimal '1']) () () (JSEmptyStatement)))"
+ testStmt "for(var x;y;z){}" `shouldBe` "Right (JSAstStatement (JSForVar (JSVarInitExpression (JSIdentifier 'x') ) (JSIdentifier 'y') (JSIdentifier 'z') (JSStatementBlock [])))"
+
+ testStmt "for(x in 5){}" `shouldBe` "Right (JSAstStatement (JSForIn JSIdentifier 'x' (JSDecimal '5') (JSStatementBlock [])))"
+
+ testStmt "for(var x in 5){}" `shouldBe` "Right (JSAstStatement (JSForVarIn (JSVarInitExpression (JSIdentifier 'x') ) (JSDecimal '5') (JSStatementBlock [])))"
+
+ testStmt "for(let x;y;z){}" `shouldBe` "Right (JSAstStatement (JSForLet (JSVarInitExpression (JSIdentifier 'x') ) (JSIdentifier 'y') (JSIdentifier 'z') (JSStatementBlock [])))"
+ testStmt "for(let x in 5){}" `shouldBe` "Right (JSAstStatement (JSForLetIn (JSVarInitExpression (JSIdentifier 'x') ) (JSDecimal '5') (JSStatementBlock [])))"
+ testStmt "for(let x of 5){}" `shouldBe` "Right (JSAstStatement (JSForLetOf (JSVarInitExpression (JSIdentifier 'x') ) (JSDecimal '5') (JSStatementBlock [])))"
+ testStmt "for(const x;y;z){}" `shouldBe` "Right (JSAstStatement (JSForConst (JSVarInitExpression (JSIdentifier 'x') ) (JSIdentifier 'y') (JSIdentifier 'z') (JSStatementBlock [])))"
+ testStmt "for(const x in 5){}" `shouldBe` "Right (JSAstStatement (JSForConstIn (JSVarInitExpression (JSIdentifier 'x') ) (JSDecimal '5') (JSStatementBlock [])))"
+ testStmt "for(const x of 5){}" `shouldBe` "Right (JSAstStatement (JSForConstOf (JSVarInitExpression (JSIdentifier 'x') ) (JSDecimal '5') (JSStatementBlock [])))"
+ testStmt "for(x of 5){}" `shouldBe` "Right (JSAstStatement (JSForOf JSIdentifier 'x' (JSDecimal '5') (JSStatementBlock [])))"
+ testStmt "for(var x of 5){}" `shouldBe` "Right (JSAstStatement (JSForVarOf (JSVarInitExpression (JSIdentifier 'x') ) (JSDecimal '5') (JSStatementBlock [])))"
+
+ it "variable/constant/let declaration" $ do
+ testStmt "var x=1;" `shouldBe` "Right (JSAstStatement (JSVariable (JSVarInitExpression (JSIdentifier 'x') [JSDecimal '1'])))"
+ testStmt "const x=1,y=2;" `shouldBe` "Right (JSAstStatement (JSConstant (JSVarInitExpression (JSIdentifier 'x') [JSDecimal '1'],JSVarInitExpression (JSIdentifier 'y') [JSDecimal '2'])))"
+ testStmt "let x=1,y=2;" `shouldBe` "Right (JSAstStatement (JSLet (JSVarInitExpression (JSIdentifier 'x') [JSDecimal '1'],JSVarInitExpression (JSIdentifier 'y') [JSDecimal '2'])))"
+ testStmt "var [a,b]=x" `shouldBe` "Right (JSAstStatement (JSVariable (JSVarInitExpression (JSArrayLiteral [JSIdentifier 'a',JSComma,JSIdentifier 'b']) [JSIdentifier 'x'])))"
+ testStmt "const {a:b}=x" `shouldBe` "Right (JSAstStatement (JSConstant (JSVarInitExpression (JSObjectLiteral [JSPropertyNameandValue (JSIdentifier 'a') [JSIdentifier 'b']]) [JSIdentifier 'x'])))"
+
+ it "break" $ do
+ testStmt "break;" `shouldBe` "Right (JSAstStatement (JSBreak,JSSemicolon))"
+ testStmt "break x;" `shouldBe` "Right (JSAstStatement (JSBreak 'x',JSSemicolon))"
+ testStmt "{break}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSBreak]))"
+
+ it "continue" $ do
+ testStmt "continue;" `shouldBe` "Right (JSAstStatement (JSContinue,JSSemicolon))"
+ testStmt "continue x;" `shouldBe` "Right (JSAstStatement (JSContinue 'x',JSSemicolon))"
+ testStmt "{continue}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSContinue]))"
+
+ it "return" $ do
+ testStmt "return;" `shouldBe` "Right (JSAstStatement (JSReturn JSSemicolon))"
+ testStmt "return x;" `shouldBe` "Right (JSAstStatement (JSReturn JSIdentifier 'x' JSSemicolon))"
+ testStmt "return 123;" `shouldBe` "Right (JSAstStatement (JSReturn JSDecimal '123' JSSemicolon))"
+ testStmt "{return}" `shouldBe` "Right (JSAstStatement (JSStatementBlock [JSReturn ]))"
+
+ it "with" $
+ testStmt "with (x) {};" `shouldBe` "Right (JSAstStatement (JSWith (JSIdentifier 'x') (JSStatementBlock [])))"
+
+ it "assign" $
+ testStmt "var z = x[i] / y;" `shouldBe` "Right (JSAstStatement (JSVariable (JSVarInitExpression (JSIdentifier 'z') [JSExpressionBinary ('/',JSMemberSquare (JSIdentifier 'x',JSIdentifier 'i'),JSIdentifier 'y')])))"
+
+ it "label" $
+ testStmt "abc:x=1" `shouldBe` "Right (JSAstStatement (JSLabelled (JSIdentifier 'abc') (JSOpAssign ('=',JSIdentifier 'x',JSDecimal '1'))))"
+
+ it "throw" $
+ testStmt "throw 1" `shouldBe` "Right (JSAstStatement (JSThrow (JSDecimal '1')))"
+
+ it "switch" $ do
+ testStmt "switch (x) {}" `shouldBe` "Right (JSAstStatement (JSSwitch (JSIdentifier 'x') []))"
+ testStmt "switch (x) {case 1:break;}" `shouldBe` "Right (JSAstStatement (JSSwitch (JSIdentifier 'x') [JSCase (JSDecimal '1') ([JSBreak,JSSemicolon])]))"
+ testStmt "switch (x) {case 0:\ncase 1:break;}" `shouldBe` "Right (JSAstStatement (JSSwitch (JSIdentifier 'x') [JSCase (JSDecimal '0') ([]),JSCase (JSDecimal '1') ([JSBreak,JSSemicolon])]))"
+ testStmt "switch (x) {default:break;}" `shouldBe` "Right (JSAstStatement (JSSwitch (JSIdentifier 'x') [JSDefault ([JSBreak,JSSemicolon])]))"
+ testStmt "switch (x) {default:\ncase 1:break;}" `shouldBe` "Right (JSAstStatement (JSSwitch (JSIdentifier 'x') [JSDefault ([]),JSCase (JSDecimal '1') ([JSBreak,JSSemicolon])]))"
+
+ it "try/cathc/finally" $ do
+ testStmt "try{}catch(a){}" `shouldBe` "Right (JSAstStatement (JSTry (JSBlock [],[JSCatch (JSIdentifier 'a',JSBlock [])],JSFinally ())))"
+ testStmt "try{}finally{}" `shouldBe` "Right (JSAstStatement (JSTry (JSBlock [],[],JSFinally (JSBlock []))))"
+ testStmt "try{}catch(a){}finally{}" `shouldBe` "Right (JSAstStatement (JSTry (JSBlock [],[JSCatch (JSIdentifier 'a',JSBlock [])],JSFinally (JSBlock []))))"
+ testStmt "try{}catch(a){}catch(b){}finally{}" `shouldBe` "Right (JSAstStatement (JSTry (JSBlock [],[JSCatch (JSIdentifier 'a',JSBlock []),JSCatch (JSIdentifier 'b',JSBlock [])],JSFinally (JSBlock []))))"
+ testStmt "try{}catch(a){}catch(b){}" `shouldBe` "Right (JSAstStatement (JSTry (JSBlock [],[JSCatch (JSIdentifier 'a',JSBlock []),JSCatch (JSIdentifier 'b',JSBlock [])],JSFinally ())))"
+ testStmt "try{}catch(a if true){}catch(b){}" `shouldBe` "Right (JSAstStatement (JSTry (JSBlock [],[JSCatch (JSIdentifier 'a') if JSLiteral 'true' (JSBlock []),JSCatch (JSIdentifier 'b',JSBlock [])],JSFinally ())))"
+
+ it "function" $ do
+ testStmt "function x(){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' () (JSBlock [])))"
+ testStmt "function x(a){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' (JSIdentifier 'a') (JSBlock [])))"
+ testStmt "function x(a,b){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' (JSIdentifier 'a',JSIdentifier 'b') (JSBlock [])))"
+ testStmt "function x(...a){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' (JSSpreadExpression (JSIdentifier 'a')) (JSBlock [])))"
+ testStmt "function x(a=1){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' (JSOpAssign ('=',JSIdentifier 'a',JSDecimal '1')) (JSBlock [])))"
+ testStmt "function x([a]){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' (JSArrayLiteral [JSIdentifier 'a']) (JSBlock [])))"
+ testStmt "function x({a}){}" `shouldBe` "Right (JSAstStatement (JSFunction 'x' (JSObjectLiteral [JSPropertyIdentRef 'a']) (JSBlock [])))"
+
+ it "generator" $ do
+ testStmt "function* x(){}" `shouldBe` "Right (JSAstStatement (JSGenerator 'x' () (JSBlock [])))"
+ testStmt "function* x(a){}" `shouldBe` "Right (JSAstStatement (JSGenerator 'x' (JSIdentifier 'a') (JSBlock [])))"
+ testStmt "function* x(a,b){}" `shouldBe` "Right (JSAstStatement (JSGenerator 'x' (JSIdentifier 'a',JSIdentifier 'b') (JSBlock [])))"
+ testStmt "function* x(a,...b){}" `shouldBe` "Right (JSAstStatement (JSGenerator 'x' (JSIdentifier 'a',JSSpreadExpression (JSIdentifier 'b')) (JSBlock [])))"
+
+ it "class" $ do
+ testStmt "class Foo extends Bar { a(x,y) {} *b() {} }" `shouldBe` "Right (JSAstStatement (JSClass 'Foo' (JSIdentifier 'Bar') [JSMethodDefinition (JSIdentifier 'a') (JSIdentifier 'x',JSIdentifier 'y') (JSBlock []),JSGeneratorMethodDefinition (JSIdentifier 'b') () (JSBlock [])]))"
+ testStmt "class Foo { static get [a]() {}; }" `shouldBe` "Right (JSAstStatement (JSClass 'Foo' () [JSClassStaticMethod (JSPropertyAccessor JSAccessorGet (JSPropertyComputed (JSIdentifier 'a')) () (JSBlock [])),JSClassSemi]))"
+ testStmt "class Foo extends Bar { a(x,y) { super[x](y); } }" `shouldBe` "Right (JSAstStatement (JSClass 'Foo' (JSIdentifier 'Bar') [JSMethodDefinition (JSIdentifier 'a') (JSIdentifier 'x',JSIdentifier 'y') (JSBlock [JSMethodCall (JSMemberSquare (JSLiteral 'super',JSIdentifier 'x'),JSArguments (JSIdentifier 'y')),JSSemicolon])]))"
+
+
+testStmt :: String -> String
+testStmt str = showStrippedMaybe (parseUsing parseStatement str "src")
--- /dev/null
+// -*- coding: utf-8 -*-
+
+àáâãäå = 1;
+
+
+
\ No newline at end of file
--- /dev/null
+function f() {}
--- /dev/null
+
+import Control.Monad (when)
+import System.Exit
+import Test.Hspec
+import Test.Hspec.Runner
+
+
+import Test.Language.Javascript.ExpressionParser
+import Test.Language.Javascript.Lexer
+import Test.Language.Javascript.LiteralParser
+import Test.Language.Javascript.Minify
+import Test.Language.Javascript.ModuleParser
+import Test.Language.Javascript.ProgramParser
+import Test.Language.Javascript.RoundTrip
+import Test.Language.Javascript.StatementParser
+
+
+main :: IO ()
+main = do
+ summary <- hspecWithResult defaultConfig testAll
+ when (summaryFailures summary == 0)
+ exitSuccess
+ exitFailure
+
+
+testAll :: Spec
+testAll = do
+ testLexer
+ testLiteralParser
+ testExpressionParser
+ testStatementParser
+ testProgramParser
+ testModuleParser
+ testRoundTrip
+ testMinifyExpr
+ testMinifyStmt
+ testMinifyProg
+ testMinifyModule
--- /dev/null
+-*- coding: utf-8; mode: xub -*-
+¢ € ₠ £ ¥ ¤
+ ° © ® ™ § ¶ † ‡ ※
+ •◦ ‣ ✓ ●■◆ ○□◇ ★☆ ♠♣♥♦ ♤♧♡♢
+ “” ‘’ ¿¡ «» ‹› ¶§ª - ‐ ‑ ‒ – — ― …
+àáâãäåæç èéêë ìíîï ðñòóôõö øùúûüýþÿ ÀÁÂÃÄÅ Ç ÈÉÊË ÌÍÎÏ ÐÑ ÒÓÔÕÖ ØÙÚÛÜÝÞß
+Æ ᴁ ᴂ ᴈ
+ ΑΒΓΔ ΕΖΗΘ ΙΚΛΜ ΝΞΟΠ ΡΣΤΥ ΦΧΨΩ αβγδ εζηθ ικλμ νξοπ ρςτυ φχψω
+ ⌈⌉ ⌊⌋ ∏ ∑ ∫ ×÷ ⊕ ⊖ ⊗ ⊘ ⊙ ∙ ∘ ′ ″ ‴ ∼ ∂ √ ≔ × ⁱ ⁰ ¹ ² ³ ₀ ₁ ₂
+ π ∞ ± ∎
+ ∀¬∧∨∃⊦∵∴∅∈∉⊂⊃⊆⊇⊄⋂⋃
+ ≠≤≥≮≯≫≪≈≡
+ ℕℤℚℝℂ
+ ←→↑↓ ↔ ↖↗↙↘ ⇐⇒⇑⇓ ⇔⇗ ⇦⇨⇧⇩ ↞↠↟↡ ↺↻ ☞☜☝☟
+λ ƒ Ɱ
+ ⌘ ⌥ ‸ ⇧ ⌤ ↑ ↓ → ← ⇞ ⇟ ↖ ↘ ⌫ ⌦ ⎋⏏ ↶↷ ◀▶▲▼ ◁▷△▽ ⇄ ⇤⇥ ↹ ↵↩⏎ ⌧ ⌨ ␣ ⌶ ⎗⎘⎙⎚ ⌚⌛ ✂✄ ✉✍
+
+ ♩♪♫♬♭♮♯
+ ➀➁➂➃➄➅➆➇➈➉
+ 卐卍✝✚✡☥⎈☭☪☮☺☹ ☯☰☱☲☳☴☵☶☷ ☠☢☣☤♲♳⌬♨♿ ☉☼☾☽ ♀♂ ♔♕♖ ♗♘♙ ♚♛ ♜♝♞♟
+ ❦
+ 、。!,:「」『』〈〉《》〖〗【】〔〕
+
+ㄅㄆㄇㄈㄉㄊㄋㄌㄍㄎㄏㄐㄑㄒㄓㄔㄕㄖㄗㄘㄙㄚㄛㄜㄝㄞㄟㄠㄡㄢㄣㄤㄥㄦㄧㄨㄩ
+
+林花謝了春紅 太匆匆, 無奈朝來寒雨 晚來風
+胭脂淚 留人醉 幾時重, 自是人生長恨 水長東
+
+ http://xahlee.org/emacs/unicode-browser.html
+ http://xahlee.org/Periodic_dosage_dir/t1/20040505_unicode.html