| Safe Haskell | Safe-Infered | 
|---|
Language.JavaScript.Parser
- parse :: String -> String -> Either ParseError JSNode
 - readJs :: String -> JSNode
 - parseFile :: FilePath -> IO JSNode
 - showStripped :: JSNode -> String
 - showStrippedMaybe :: Show a => Either a JSNode -> [Char]
 - data JSNode = NS Node SrcSpan
 - data  SrcSpan 
- = SpanCoLinear { 
- span_filename :: !String
 - span_row :: !Int
 - span_start_column :: !Int
 - span_end_column :: !Int
 
 - | SpanMultiLine { 
- span_filename :: !String
 - span_start_row :: !Int
 - span_start_column :: !Int
 - span_end_row :: !Int
 - span_end_column :: !Int
 
 - | SpanPoint { 
- span_filename :: !String
 - span_row :: !Int
 - span_column :: !Int
 
 - | SpanEmpty
 
 - = SpanCoLinear { 
 - type AlexSpan = (AlexPosn, Char, String)
 - data  Node 
- = JSArguments [[JSNode]]
 - | JSArrayLiteral [JSNode]
 - | JSBlock JSNode
 - | JSBreak [JSNode] [JSNode]
 - | JSCallExpression String [JSNode]
 - | JSCase JSNode JSNode
 - | JSCatch JSNode [JSNode] JSNode
 - | JSContinue [JSNode]
 - | JSDecimal String
 - | JSDefault JSNode
 - | JSDoWhile JSNode JSNode JSNode
 - | JSElision [JSNode]
 - | JSEmpty JSNode
 - | JSExpression [JSNode]
 - | JSExpressionBinary String [JSNode] [JSNode]
 - | JSExpressionParen JSNode
 - | JSExpressionPostfix String [JSNode]
 - | JSExpressionTernary [JSNode] [JSNode] [JSNode]
 - | JSFinally JSNode
 - | JSFor [JSNode] [JSNode] [JSNode] JSNode
 - | JSForIn [JSNode] JSNode JSNode
 - | JSForVar [JSNode] [JSNode] [JSNode] JSNode
 - | JSForVarIn JSNode JSNode JSNode
 - | JSFunction JSNode [JSNode] JSNode
 - | JSFunctionBody [JSNode]
 - | JSFunctionExpression [JSNode] [JSNode] JSNode
 - | JSHexInteger String
 - | JSIdentifier String
 - | JSIf JSNode JSNode
 - | JSIfElse JSNode JSNode JSNode
 - | JSLabelled JSNode JSNode
 - | JSLiteral String
 - | JSMemberDot [JSNode] JSNode
 - | JSMemberSquare [JSNode] JSNode
 - | JSObjectLiteral [JSNode]
 - | JSOperator String
 - | JSPropertyNameandValue JSNode [JSNode]
 - | JSPropertyAccessor String JSNode [JSNode] JSNode
 - | JSRegEx String
 - | JSReturn [JSNode]
 - | JSSourceElements [JSNode]
 - | JSSourceElementsTop [JSNode]
 - | JSStatementBlock JSNode
 - | JSStatementList [JSNode]
 - | JSStringLiteral Char [Char]
 - | JSSwitch JSNode [JSNode]
 - | JSThrow JSNode
 - | JSTry JSNode [JSNode]
 - | JSUnary String
 - | JSVarDecl JSNode [JSNode]
 - | JSVariables String [JSNode]
 - | JSWhile JSNode JSNode
 - | JSWith JSNode [JSNode]
 
 - data ParseError
 - data AlexPosn = AlexPn !Int !Int !Int
 - type P a = StateT ParseState (Either ParseError) a
 - data ParseState = ParseState {}
 
Documentation
Arguments
| :: String | The input stream (Javascript source code).  | 
| -> String | The name of the Javascript source (filename or input device).  | 
| -> Either ParseError JSNode | An error or maybe the abstract syntax tree (AST) of zero or more Javascript statements, plus comments.  | 
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.
showStripped :: JSNode -> StringSource
Source location spanning a contiguous section of a file.
Constructors
| SpanCoLinear | A span which starts and ends on the same line.  | 
Fields 
  | |
| SpanMultiLine | A span which starts and ends on different lines.  | 
Fields 
  | |
| SpanPoint | A span which is actually just one point in the file.  | 
Fields 
  | |
| SpanEmpty | No span information.  | 
Constructors
data ParseError Source
Constructors
| UnexpectedToken Token | An error from the parser. Token found where it should not be. Note: tokens contain their own source span.  | 
| UnexpectedChar Char AlexPosn | An error from the lexer. Character found where it should not be.  | 
| StrError String | A generic error containing a string message. No source location.  | 
Instances
Posn 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. start_pos gives the position of the
 start of the file and eof_pos a standard encoding for the end of file.
 move_pos calculates the new position after traversing a given character,
 assuming the usual eight character tab stops.
type P a = StateT ParseState (Either ParseError) aSource
data ParseState Source
Constructors
| ParseState | |