language-javascript-0.6.0.13: Parser for JavaScript

Safe HaskellNone
LanguageHaskell98

Language.JavaScript.Parser

Contents

Synopsis

Documentation

parse Source #

Arguments

:: String

The input stream (Javascript source code).

-> String

The name of the Javascript source (filename or input device).

-> Either String JSAST

An error or maybe the abstract syntax tree (AST) of zero or more Javascript statements, plus comments.

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.

parseModule Source #

Arguments

:: String

The input stream (JavaScript source code).

-> String

The name of the JavaScript source (filename or input device).

-> Either String JSAST

An error or maybe the abstract syntax tree (AST) of zero or more JavaScript statements, plus comments.

Parse JavaScript module

parseFile :: FilePath -> IO JSAST Source #

Parse the given file. For UTF-8 support, make sure your locale is set such that "System.IO.localeEncoding" returns "utf8"

parseFileUtf8 :: FilePath -> IO JSAST Source #

Parse the given file, explicitly setting the encoding to UTF8 when reading it

AST elements

data JSExpression Source #

Constructors

JSIdentifier !JSAnnot !String

Terminals

JSDecimal !JSAnnot !String 
JSLiteral !JSAnnot !String 
JSHexInteger !JSAnnot !String 
JSOctal !JSAnnot !String 
JSStringLiteral !JSAnnot !String 
JSRegEx !JSAnnot !String 
JSArrayLiteral !JSAnnot ![JSArrayElement] !JSAnnot

lb, contents, rb

JSAssignExpression !JSExpression !JSAssignOp !JSExpression

lhs, assignop, rhs

JSCallExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot

expr, bl, args, rb

JSCallExpressionDot !JSExpression !JSAnnot !JSExpression

expr, dot, expr

JSCallExpressionSquare !JSExpression !JSAnnot !JSExpression !JSAnnot

expr, [, expr, ]

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 JSIdent) !JSAnnot !JSBlock

fn,name,lb, parameter list,rb,block`

JSMemberDot !JSExpression !JSAnnot !JSExpression

firstpart, dot, name

JSMemberExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot 
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 
JSUnaryExpression !JSUnaryOp !JSExpression 
JSVarInitExpression !JSExpression !JSVarInitializer

identifier, initializer

Instances
Eq JSExpression Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSExpression Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSExpression -> c JSExpression #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSExpression #

toConstr :: JSExpression -> Constr #

dataTypeOf :: JSExpression -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSExpression) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSExpression) #

gmapT :: (forall b. Data b => b -> b) -> JSExpression -> JSExpression #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSExpression -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSExpression -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSExpression -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSExpression -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSExpression -> m JSExpression #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSExpression -> m JSExpression #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSExpression -> m JSExpression #

Show JSExpression Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSAnnot Source #

Constructors

JSAnnot !TokenPosn ![CommentAnnotation]

Annotation: position and comment/whitespace information

JSAnnotSpace

A single space character

JSNoAnnot

No annotation

Instances
Eq JSAnnot Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

(==) :: JSAnnot -> JSAnnot -> Bool #

(/=) :: JSAnnot -> JSAnnot -> Bool #

Data JSAnnot Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSAnnot -> c JSAnnot #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSAnnot #

toConstr :: JSAnnot -> Constr #

dataTypeOf :: JSAnnot -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSAnnot) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSAnnot) #

gmapT :: (forall b. Data b => b -> b) -> JSAnnot -> JSAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSAnnot -> m JSAnnot #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSAnnot -> m JSAnnot #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSAnnot -> m JSAnnot #

Show JSAnnot Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSBinOp Source #

Instances
Eq JSBinOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

(==) :: JSBinOp -> JSBinOp -> Bool #

(/=) :: JSBinOp -> JSBinOp -> Bool #

Data JSBinOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSBinOp -> c JSBinOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSBinOp #

toConstr :: JSBinOp -> Constr #

dataTypeOf :: JSBinOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSBinOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSBinOp) #

gmapT :: (forall b. Data b => b -> b) -> JSBinOp -> JSBinOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSBinOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSBinOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSBinOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSBinOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSBinOp -> m JSBinOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSBinOp -> m JSBinOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSBinOp -> m JSBinOp #

Show JSBinOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSBlock Source #

Constructors

JSBlock !JSAnnot ![JSStatement] !JSAnnot

lbrace, stmts, rbrace

Instances
Eq JSBlock Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

(==) :: JSBlock -> JSBlock -> Bool #

(/=) :: JSBlock -> JSBlock -> Bool #

Data JSBlock Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSBlock -> c JSBlock #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSBlock #

toConstr :: JSBlock -> Constr #

dataTypeOf :: JSBlock -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSBlock) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSBlock) #

gmapT :: (forall b. Data b => b -> b) -> JSBlock -> JSBlock #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSBlock -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSBlock -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSBlock -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSBlock -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSBlock -> m JSBlock #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSBlock -> m JSBlock #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSBlock -> m JSBlock #

Show JSBlock Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSUnaryOp Source #

Instances
Eq JSUnaryOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSUnaryOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSUnaryOp -> c JSUnaryOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSUnaryOp #

toConstr :: JSUnaryOp -> Constr #

dataTypeOf :: JSUnaryOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSUnaryOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSUnaryOp) #

gmapT :: (forall b. Data b => b -> b) -> JSUnaryOp -> JSUnaryOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSUnaryOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSUnaryOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSUnaryOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSUnaryOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSUnaryOp -> m JSUnaryOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSUnaryOp -> m JSUnaryOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSUnaryOp -> m JSUnaryOp #

Show JSUnaryOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSSemi Source #

Constructors

JSSemi !JSAnnot 
JSSemiAuto 
Instances
Eq JSSemi Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

(==) :: JSSemi -> JSSemi -> Bool #

(/=) :: JSSemi -> JSSemi -> Bool #

Data JSSemi Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSSemi -> c JSSemi #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSSemi #

toConstr :: JSSemi -> Constr #

dataTypeOf :: JSSemi -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSSemi) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSSemi) #

gmapT :: (forall b. Data b => b -> b) -> JSSemi -> JSSemi #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSSemi -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSSemi -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSSemi -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSSemi -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSSemi -> m JSSemi #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSSemi -> m JSSemi #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSSemi -> m JSSemi #

Show JSSemi Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSAssignOp Source #

Instances
Eq JSAssignOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSAssignOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSAssignOp -> c JSAssignOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSAssignOp #

toConstr :: JSAssignOp -> Constr #

dataTypeOf :: JSAssignOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSAssignOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSAssignOp) #

gmapT :: (forall b. Data b => b -> b) -> JSAssignOp -> JSAssignOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSAssignOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSAssignOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSAssignOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSAssignOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSAssignOp -> m JSAssignOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSAssignOp -> m JSAssignOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSAssignOp -> m JSAssignOp #

Show JSAssignOp Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSTryCatch Source #

Constructors

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

Instances
Eq JSTryCatch Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSTryCatch Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSTryCatch -> c JSTryCatch #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSTryCatch #

toConstr :: JSTryCatch -> Constr #

dataTypeOf :: JSTryCatch -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSTryCatch) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSTryCatch) #

gmapT :: (forall b. Data b => b -> b) -> JSTryCatch -> JSTryCatch #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSTryCatch -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSTryCatch -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSTryCatch -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSTryCatch -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSTryCatch -> m JSTryCatch #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSTryCatch -> m JSTryCatch #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSTryCatch -> m JSTryCatch #

Show JSTryCatch Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSTryFinally Source #

Constructors

JSFinally !JSAnnot !JSBlock

finally,block

JSNoFinally 
Instances
Eq JSTryFinally Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSTryFinally Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSTryFinally -> c JSTryFinally #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSTryFinally #

toConstr :: JSTryFinally -> Constr #

dataTypeOf :: JSTryFinally -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSTryFinally) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSTryFinally) #

gmapT :: (forall b. Data b => b -> b) -> JSTryFinally -> JSTryFinally #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSTryFinally -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSTryFinally -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSTryFinally -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSTryFinally -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSTryFinally -> m JSTryFinally #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSTryFinally -> m JSTryFinally #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSTryFinally -> m JSTryFinally #

Show JSTryFinally Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSStatement Source #

Constructors

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

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

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

JSFunction !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSIdent) !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

Instances
Eq JSStatement Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSStatement Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSStatement -> c JSStatement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSStatement #

toConstr :: JSStatement -> Constr #

dataTypeOf :: JSStatement -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSStatement) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSStatement) #

gmapT :: (forall b. Data b => b -> b) -> JSStatement -> JSStatement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSStatement -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSStatement -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSStatement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSStatement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSStatement -> m JSStatement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSStatement -> m JSStatement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSStatement -> m JSStatement #

Show JSStatement Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSSwitchParts Source #

Constructors

JSCase !JSAnnot !JSExpression !JSAnnot ![JSStatement]

expr,colon,stmtlist

JSDefault !JSAnnot !JSAnnot ![JSStatement]

colon,stmtlist

Instances
Eq JSSwitchParts Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Data JSSwitchParts Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSSwitchParts -> c JSSwitchParts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSSwitchParts #

toConstr :: JSSwitchParts -> Constr #

dataTypeOf :: JSSwitchParts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSSwitchParts) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSSwitchParts) #

gmapT :: (forall b. Data b => b -> b) -> JSSwitchParts -> JSSwitchParts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSSwitchParts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSSwitchParts -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSSwitchParts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSSwitchParts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSSwitchParts -> m JSSwitchParts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSSwitchParts -> m JSSwitchParts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSSwitchParts -> m JSSwitchParts #

Show JSSwitchParts Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

data JSAST Source #

Instances
Eq JSAST Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

(==) :: JSAST -> JSAST -> Bool #

(/=) :: JSAST -> JSAST -> Bool #

Data JSAST Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSAST -> c JSAST #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSAST #

toConstr :: JSAST -> Constr #

dataTypeOf :: JSAST -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSAST) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSAST) #

gmapT :: (forall b. Data b => b -> b) -> JSAST -> JSAST #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSAST -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSAST -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSAST -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSAST -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSAST -> m JSAST #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSAST -> m JSAST #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSAST -> m JSAST #

Show JSAST Source # 
Instance details

Defined in Language.JavaScript.Parser.AST

Methods

showsPrec :: Int -> JSAST -> ShowS #

show :: JSAST -> String #

showList :: [JSAST] -> ShowS #

data CommentAnnotation Source #

Instances
Eq CommentAnnotation Source # 
Instance details

Defined in Language.JavaScript.Parser.Token

Data CommentAnnotation Source # 
Instance details

Defined in Language.JavaScript.Parser.Token

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CommentAnnotation -> c CommentAnnotation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CommentAnnotation #

toConstr :: CommentAnnotation -> Constr #

dataTypeOf :: CommentAnnotation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CommentAnnotation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CommentAnnotation) #

gmapT :: (forall b. Data b => b -> b) -> CommentAnnotation -> CommentAnnotation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r #

gmapQ :: (forall d. Data d => d -> u) -> CommentAnnotation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CommentAnnotation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CommentAnnotation -> m CommentAnnotation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CommentAnnotation -> m CommentAnnotation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CommentAnnotation -> m CommentAnnotation #

Read CommentAnnotation Source # 
Instance details

Defined in Language.JavaScript.Parser.Token

Show CommentAnnotation Source # 
Instance details

Defined in Language.JavaScript.Parser.Token

data TokenPosn Source #

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.

Constructors

TokenPn !Int !Int !Int 
Instances
Eq TokenPosn Source # 
Instance details

Defined in Language.JavaScript.Parser.SrcLocation

Data TokenPosn Source # 
Instance details

Defined in Language.JavaScript.Parser.SrcLocation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenPosn -> c TokenPosn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenPosn #

toConstr :: TokenPosn -> Constr #

dataTypeOf :: TokenPosn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenPosn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenPosn) #

gmapT :: (forall b. Data b => b -> b) -> TokenPosn -> TokenPosn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenPosn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenPosn -> r #

gmapQ :: (forall d. Data d => d -> u) -> TokenPosn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenPosn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenPosn -> m TokenPosn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenPosn -> m TokenPosn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenPosn -> m TokenPosn #

Read TokenPosn Source # 
Instance details

Defined in Language.JavaScript.Parser.SrcLocation

Show TokenPosn Source # 
Instance details

Defined in Language.JavaScript.Parser.SrcLocation

Pretty Printing