language-javascript-0.5.14.4: Parser for JavaScript

Safe HaskellSafe
LanguageHaskell98

Language.JavaScript.Parser.AST

Synopsis

Documentation

data Node Source #

Constructors

JSIdentifier String

Terminals

JSDecimal String 
JSLiteral String 
JSHexInteger String 
JSOctal String 
JSStringLiteral Char [Char] 
JSRegEx String 
JSArguments JSNode [JSNode] JSNode

lb, args, rb

JSArrayLiteral JSNode [JSNode] JSNode

lb, contents, rb

JSBlock [JSNode] [JSNode] [JSNode]

optional lb,optional block statements,optional rb

JSBreak JSNode [JSNode] JSNode

break, optional identifier, autosemi

JSCallExpression String [JSNode] [JSNode] [JSNode]

type : ., (), []; opening [ or ., contents, closing

JSCase JSNode JSNode JSNode [JSNode]

case,expr,colon,stmtlist

JSCatch JSNode JSNode JSNode [JSNode] JSNode JSNode

catch,lb,ident,[if,expr],rb,block

JSContinue JSNode [JSNode] JSNode

continue,optional identifier,autosemi

JSDefault JSNode JSNode [JSNode]

default,colon,stmtlist

JSDoWhile JSNode JSNode JSNode JSNode JSNode JSNode JSNode

do,stmt,while,lb,expr,rb,autosemi

JSElision JSNode

comma

JSExpression [JSNode]

expression components

JSExpressionBinary String [JSNode] JSNode [JSNode]

what, lhs, op, rhs

JSExpressionParen JSNode JSNode JSNode

lb,expression,rb

JSExpressionPostfix String [JSNode] JSNode

type, expression, operator

JSExpressionTernary [JSNode] JSNode [JSNode] JSNode [JSNode]

cond, ?, trueval, :, falseval

JSFinally JSNode JSNode

finally,block

JSFor JSNode JSNode [JSNode] JSNode [JSNode] JSNode [JSNode] JSNode JSNode

for,lb,expr,semi,expr,semi,expr,rb.stmt

JSForIn JSNode JSNode [JSNode] JSNode JSNode JSNode JSNode

for,lb,expr,in,expr,rb,stmt

JSForVar JSNode JSNode JSNode [JSNode] JSNode [JSNode] JSNode [JSNode] JSNode JSNode

for,lb,var,vardecl,semi,expr,semi,expr,rb,stmt

JSForVarIn JSNode JSNode JSNode JSNode JSNode JSNode JSNode JSNode

for,lb,var,vardecl,in,expr,rb,stmt

JSFunction JSNode JSNode JSNode [JSNode] JSNode JSNode

fn,name, lb,parameter list,rb,block | JSFunctionBody [JSNode] -- ^body

JSFunctionExpression JSNode [JSNode] JSNode [JSNode] JSNode JSNode

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

JSIf JSNode JSNode JSNode JSNode [JSNode] [JSNode]

if,(,expr,),stmt,optional rest

JSLabelled JSNode JSNode JSNode

identifier,colon,stmt

JSMemberDot [JSNode] JSNode JSNode

firstpart, dot, name

JSMemberSquare [JSNode] JSNode JSNode JSNode

firstpart, lb, expr, rb

JSObjectLiteral JSNode [JSNode] JSNode

lbrace contents rbrace

JSOperator JSNode

opnode

JSPropertyAccessor JSNode JSNode JSNode [JSNode] JSNode JSNode

(get|set), name, lb, params, rb, block

JSPropertyNameandValue JSNode JSNode [JSNode]

name, colon, value

JSReturn JSNode [JSNode] JSNode

return,optional expression,autosemi | JSSourceElements [JSNode] -- ^source elements

JSSourceElementsTop [JSNode]

source elements | JSStatementBlock JSNode JSNode JSNode -- ^lb,block,rb | JSStatementList [JSNode] -- ^statements

JSSwitch JSNode JSNode JSNode JSNode JSNode

switch,lb,expr,rb,caseblock

JSThrow JSNode JSNode

throw val

JSTry JSNode JSNode [JSNode]

try,block,rest

JSUnary String JSNode

type, operator

JSVarDecl JSNode [JSNode]

identifier, optional initializer

JSVariables JSNode [JSNode] JSNode

var|const, decl, autosemi

JSWhile JSNode JSNode JSNode JSNode JSNode

while,lb,expr,rb,stmt

JSWith JSNode JSNode JSNode JSNode [JSNode]

with,lb,expr,rb,stmt list

Instances

Eq Node Source # 

Methods

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

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

Data Node Source # 

Methods

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

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

toConstr :: Node -> Constr #

dataTypeOf :: Node -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Node Source # 
Show Node Source # 

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

data JSNode Source #

The JSNode is the building block of the AST. Each has a syntactic part Node. In addition, the leaf elements (terminals) have a position TokenPosn, as well as an array of comments and/or whitespace that was collected while parsing.

Constructors

NN Node

Non Terminal node, does not have any position or comment information

NT Node TokenPosn [CommentAnnotation]

Terminal node, including position and comment/whitespace information

Instances

Eq JSNode Source # 

Methods

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

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

Data JSNode Source # 

Methods

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

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

toConstr :: JSNode -> Constr #

dataTypeOf :: JSNode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JSNode Source # 
Show JSNode Source #