Safe Haskell | None |
---|---|
Language | Haskell98 |
- parse :: String -> String -> Either String JSAST
- readJs :: String -> JSAST
- parseFile :: FilePath -> IO JSAST
- parseFileUtf8 :: FilePath -> IO JSAST
- showStripped :: JSAST -> String
- showStrippedMaybe :: Show a => Either a JSAST -> String
- data JSExpression
- = JSIdentifier !JSAnnot !String
- | JSDecimal !JSAnnot !String
- | JSLiteral !JSAnnot !String
- | JSHexInteger !JSAnnot !String
- | JSOctal !JSAnnot !String
- | JSStringLiteral !JSAnnot !String
- | JSRegEx !JSAnnot !String
- | JSArrayLiteral !JSAnnot ![JSArrayElement] !JSAnnot
- | JSAssignExpression !JSExpression !JSAssignOp !JSExpression
- | JSCallExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot
- | JSCallExpressionDot !JSExpression !JSAnnot !JSExpression
- | JSCallExpressionSquare !JSExpression !JSAnnot !JSExpression !JSAnnot
- | JSCommaExpression !JSExpression !JSAnnot !JSExpression
- | JSExpressionBinary !JSExpression !JSBinOp !JSExpression
- | JSExpressionParen !JSAnnot !JSExpression !JSAnnot
- | JSExpressionPostfix !JSExpression !JSUnaryOp
- | JSExpressionTernary !JSExpression !JSAnnot !JSExpression !JSAnnot !JSExpression
- | JSFunctionExpression !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSIdent) !JSAnnot !JSBlock
- | JSMemberDot !JSExpression !JSAnnot !JSExpression
- | JSMemberExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot
- | JSMemberNew !JSAnnot !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot
- | JSMemberSquare !JSExpression !JSAnnot !JSExpression !JSAnnot
- | JSNewExpression !JSAnnot !JSExpression
- | JSObjectLiteral !JSAnnot !JSObjectPropertyList !JSAnnot
- | JSUnaryExpression !JSUnaryOp !JSExpression
- | JSVarInitExpression !JSExpression !JSVarInitializer
- data JSAnnot
- 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
- | JSBinOpOr !JSAnnot
- | JSBinOpPlus !JSAnnot
- | JSBinOpRsh !JSAnnot
- | JSBinOpStrictEq !JSAnnot
- | JSBinOpStrictNeq !JSAnnot
- | JSBinOpTimes !JSAnnot
- | JSBinOpUrsh !JSAnnot
- data JSBlock = JSBlock !JSAnnot ![JSStatement] !JSAnnot
- data JSUnaryOp
- data JSSemi
- = JSSemi !JSAnnot
- | JSSemiAuto
- data JSAssignOp
- data JSTryCatch
- data JSTryFinally
- data JSStatement
- = JSStatementBlock !JSAnnot ![JSStatement] !JSAnnot !JSSemi
- | JSBreak !JSAnnot !JSIdent !JSSemi
- | JSConstant !JSAnnot !(JSCommaList JSExpression) !JSSemi
- | JSContinue !JSAnnot !JSIdent !JSSemi
- | JSDoWhile !JSAnnot !JSStatement !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSSemi
- | JSFor !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement
- | JSForIn !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement
- | JSForVar !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement
- | JSForVarIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement
- | JSFunction !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSIdent) !JSAnnot !JSBlock !JSSemi
- | JSIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement
- | JSIfElse !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSAnnot !JSStatement
- | JSLabelled !JSIdent !JSAnnot !JSStatement
- | JSEmptyStatement !JSAnnot
- | JSExpressionStatement !JSExpression !JSSemi
- | JSAssignStatement !JSExpression !JSAssignOp !JSExpression !JSSemi
- | JSMethodCall !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSSemi
- | JSReturn !JSAnnot !(Maybe JSExpression) !JSSemi
- | JSSwitch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSAnnot ![JSSwitchParts] !JSAnnot !JSSemi
- | JSThrow !JSAnnot !JSExpression !JSSemi
- | JSTry !JSAnnot !JSBlock ![JSTryCatch] !JSTryFinally
- | JSVariable !JSAnnot !(JSCommaList JSExpression) !JSSemi
- | JSWhile !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement
- | JSWith !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSSemi
- data JSSwitchParts
- = JSCase !JSAnnot !JSExpression !JSAnnot ![JSStatement]
- | JSDefault !JSAnnot !JSAnnot ![JSStatement]
- data JSAST
- data CommentAnnotation
- data TokenPosn = TokenPn !Int !Int !Int
- tokenPosnEmpty :: TokenPosn
- renderJS :: JSAST -> Builder
- renderToString :: JSAST -> String
- renderToText :: JSAST -> Text
Documentation
:: 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 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.
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
showStripped :: JSAST -> String Source #
AST elements
data JSExpression Source #
JSAnnot !TokenPosn ![CommentAnnotation] | Annotation: position and comment/whitespace information |
JSAnnotSpace | A single space character |
JSNoAnnot | No annotation |
JSBlock !JSAnnot ![JSStatement] !JSAnnot | lbrace, stmts, rbrace |
data JSAssignOp Source #
data JSTryCatch Source #
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 |
data JSTryFinally Source #
JSFinally !JSAnnot !JSBlock | finally,block |
JSNoFinally |
data JSStatement Source #
data JSSwitchParts Source #
JSCase !JSAnnot !JSExpression !JSAnnot ![JSStatement] | expr,colon,stmtlist |
JSDefault !JSAnnot !JSAnnot ![JSStatement] | colon,stmtlist |
JSAstProgram ![JSStatement] !JSAnnot | source elements, tailing whitespace |
JSAstStatement !JSStatement !JSAnnot | |
JSAstExpression !JSExpression !JSAnnot | |
JSAstLiteral !JSExpression !JSAnnot |
data CommentAnnotation 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.
Pretty Printing
renderToString :: JSAST -> String Source #
renderToText :: JSAST -> Text Source #