{- This module was generated from data in the Kate syntax highlighting file javascript.xml, version 1.18, by Anders Lund (anders@alweb.dk), Joseph Wenninger (jowenn@kde.org), Whitehawk Stormchaser (zerokode@gmx.net) -} module Text.Highlighting.Kate.Syntax.Javascript ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "JavaScript" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.js" -- | Highlight source code using this syntax definition. highlight :: String -> Either String [SourceLine] highlight input = case runParser parseSource startingState "source" input of Left err -> Left $ show err Right result -> Right result -- | Parse an expression using appropriate local context. parseExpression :: GenParser Char SyntaxState LabeledSource parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "JavaScript" } context <- currentContext <|> (pushContext "Normal" >> currentContext) result <- parseRules context updateState $ \st -> st { synStLanguage = oldLang } return result parseSource = do lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents } result <- manyTill parseSourceLine eof return $ map normalizeHighlighting result startingState = SyntaxState {synStContexts = fromList [("JavaScript",["Normal"])], synStLanguage = "JavaScript", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "Normal" -> return () >> pHandleEndLine "String" -> (popContext) >> pEndLine "String 1" -> (popContext) >> pEndLine "Comment" -> (popContext) >> pEndLine "Multi/inline Comment" -> return () >> pHandleEndLine "Regular Expression" -> return () >> pHandleEndLine "(Internal regex catch)" -> return () >> pHandleEndLine "Regular Expression Character Class" -> return () >> pHandleEndLine "(regex caret first check)" -> (popContext) >> pEndLine "(charclass caret first check)" -> (popContext) >> pEndLine "region_marker" -> (popContext) >> pEndLine "ObjectMember" -> return () >> pHandleEndLine _ -> pHandleEndLine withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" let labs = attr : maybeToList (lookup attr styles) st <- getState let oldCharsParsed = synStCharsParsedInLine st let prevchar = if null txt then '\n' else last txt updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } return (labs, txt) styles = [("Keyword","kw"),("Function","fu"),("Objects","kw"),("Object Member","fu"),("Math","kw"),("Events","kw"),("Decimal","dv"),("Float","fl"),("Char","ch"),("String","st"),("String Char","ch"),("Comment","co"),("Regular Expression","ot"),("Pattern Internal Operator","fl"),("Pattern Character Class","bn"),("Region Marker","re"),("JSON","dt")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) list_keywords = Set.fromList $ words $ "if else for in while do continue break with try catch finally switch case new var function return delete true false void throw typeof const default" list_functions = Set.fromList $ words $ "escape isFinite isNaN Number parseFloat parseInt reload taint unescape untaint write" list_objects = Set.fromList $ words $ "Anchor Applet Area Array Boolean Button Checkbox Date document window Image FileUpload Form Frame Function Hidden Link MimeType Math Max Min Layer navigator Object Password Plugin Radio RegExp Reset Screen Select String Text Textarea this Window" list_math = Set.fromList $ words $ "abs acos asin atan atan2 ceil cos ctg E exp floor LN2 LN10 log LOG2E LOG10E PI pow round sin sqrt SQRT1_2 SQRT2 tan" list_events = Set.fromList $ words $ "onAbort onBlur onChange onClick onError onFocus onLoad onMouseOut onMouseOver onReset onSelect onSubmit onUnload" regex_'5cb'5b'5cw'5c'2e'5d'2b'5cb'5cs'2a'28'3f'3d'3a'29 = compileRegex "\\b[\\w\\.]+\\b\\s*(?=:)" regex_'5cb'5b'5cw'5c'2e'5d'2b'28'3f'3d'5c'2e'29 = compileRegex "\\b[\\w\\.]+(?=\\.)" regex_'5b'3d'3f'3a'5d = compileRegex "[=?:]" regex_'5c'28 = compileRegex "\\(" regex_'2f'5big'5d'7b0'2c2'7d = compileRegex "/[ig]{0,2}" regex_'5c'7b'5b'5cd'2c_'5d'2b'5c'7d = compileRegex "\\{[\\d, ]+\\}" regex_'5c'5c'5bbB'5d = compileRegex "\\\\[bB]" regex_'5c'5c'5bnrtvfDdSsWw'5d = compileRegex "\\\\[nrtvfDdSsWw]" regex_'5c'5c'2e = compileRegex "\\\\." regex_'5c'24'28'3f'3d'2f'29 = compileRegex "\\$(?=/)" regex_'2f'2f'28'3f'3d'3b'29 = compileRegex "//(?=;)" regex_'5c'5c'5b'5c'5b'5c'5d'5d = compileRegex "\\\\[\\[\\]]" defaultAttributes = [("Normal","Normal Text"),("String","String"),("String 1","String Char"),("Comment","Comment"),("Multi/inline Comment","Comment"),("Regular Expression","Regular Expression"),("(Internal regex catch)","Normal Text"),("Regular Expression Character Class","Pattern Character Class"),("(regex caret first check)","Pattern Internal Operator"),("(charclass caret first check)","Pattern Internal Operator"),("region_marker","Region Marker"),("ObjectMember","Normal Text")] parseRules "Normal" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Normal Text")) <|> ((pString False "//BEGIN" >>= withAttribute "Region Marker") >>~ pushContext "region_marker") <|> ((pString False "//END" >>= withAttribute "Region Marker") >>~ pushContext "region_marker") <|> ((pFloat >>= withAttribute "Float")) <|> ((pInt >>= withAttribute "Decimal")) <|> ((pRegExpr regex_'5cb'5b'5cw'5c'2e'5d'2b'5cb'5cs'2a'28'3f'3d'3a'29 >>= withAttribute "JSON")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute "Keyword")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute "Function")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_objects >>= withAttribute "Objects")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_math >>= withAttribute "Math")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_events >>= withAttribute "Events")) <|> ((pDetectChar False '.' >>= withAttribute "Normal Text") >>~ pushContext "ObjectMember") <|> ((pRegExpr regex_'5cb'5b'5cw'5c'2e'5d'2b'28'3f'3d'5c'2e'29 >>= withAttribute "Objects") >>~ pushContext "ObjectMember") <|> ((pDetectIdentifier >>= withAttribute "Normal Text")) <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "String") <|> ((pDetectChar False '\'' >>= withAttribute "String Char") >>~ pushContext "String 1") <|> ((pDetect2Chars False '/' '/' >>= withAttribute "Comment") >>~ pushContext "Comment") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "Multi/inline Comment") <|> ((pRegExpr regex_'5b'3d'3f'3a'5d >>= withAttribute "Normal Text") >>~ pushContext "(Internal regex catch)") <|> ((pRegExpr regex_'5c'28 >>= withAttribute "Normal Text") >>~ pushContext "(Internal regex catch)") <|> ((pDetectChar False '{' >>= withAttribute "Symbol")) <|> ((pDetectChar False '}' >>= withAttribute "Symbol")) <|> ((pAnyChar ":!%&+,-/.*<=>?[]|~^;" >>= withAttribute "Symbol"))) return (attr, result) parseRules "String" = do (attr, result) <- (((pDetectIdentifier >>= withAttribute "String")) <|> ((pHlCStringChar >>= withAttribute "String Char")) <|> ((pLineContinue >>= withAttribute "String")) <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "String 1" = do (attr, result) <- (((pDetectIdentifier >>= withAttribute "String Char")) <|> ((pHlCStringChar >>= withAttribute "String Char")) <|> ((pLineContinue >>= withAttribute "String")) <|> ((pDetectChar False '\'' >>= withAttribute "String Char") >>~ (popContext))) return (attr, result) parseRules "Comment" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Comment")) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression)) <|> ((pDetectIdentifier >>= withAttribute "Comment"))) return (attr, result) parseRules "Multi/inline Comment" = do (attr, result) <- (((Text.Highlighting.Kate.Syntax.Alert.parseExpression)) <|> ((pDetect2Chars False '*' '/' >>= withAttribute "Comment") >>~ (popContext))) return (attr, result) parseRules "Regular Expression" = do (attr, result) <- (((pRegExpr regex_'2f'5big'5d'7b0'2c2'7d >>= withAttribute "Regular Expression") >>~ (popContext >> popContext >> popContext)) <|> ((pRegExpr regex_'5c'7b'5b'5cd'2c_'5d'2b'5c'7d >>= withAttribute "Pattern Internal Operator")) <|> ((pRegExpr regex_'5c'5c'5bbB'5d >>= withAttribute "Pattern Internal Operator")) <|> ((pRegExpr regex_'5c'5c'5bnrtvfDdSsWw'5d >>= withAttribute "Pattern Character Class")) <|> ((pDetectChar False '[' >>= withAttribute "Pattern Character Class") >>~ pushContext "(charclass caret first check)") <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute "Pattern Internal Operator")) <|> ((pRegExpr regex_'5c'24'28'3f'3d'2f'29 >>= withAttribute "Pattern Internal Operator")) <|> ((pAnyChar "?+*()|" >>= withAttribute "Pattern Internal Operator"))) return (attr, result) parseRules "(Internal regex catch)" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Normal Text")) <|> ((pRegExpr regex_'2f'2f'28'3f'3d'3b'29 >>= withAttribute "Regular Expression") >>~ (popContext)) <|> ((pDetect2Chars False '/' '/' >>= withAttribute "Comment") >>~ pushContext "Comment") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "Multi/inline Comment") <|> ((pDetectChar False '/' >>= withAttribute "Regular Expression") >>~ pushContext "(regex caret first check)") <|> ((popContext) >> return ([], ""))) return (attr, result) parseRules "Regular Expression Character Class" = do (attr, result) <- (((pRegExpr regex_'5c'5c'5b'5c'5b'5c'5d'5d >>= withAttribute "Pattern Character Class")) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute "Pattern Internal Operator")) <|> ((pDetectChar False ']' >>= withAttribute "Pattern Character Class") >>~ (popContext >> popContext))) return (attr, result) parseRules "(regex caret first check)" = do (attr, result) <- (((pDetectChar False '^' >>= withAttribute "Pattern Internal Operator") >>~ pushContext "Regular Expression") <|> (pushContext "Regular Expression" >> return ([], ""))) return (attr, result) parseRules "(charclass caret first check)" = do (attr, result) <- (((pDetectChar False '^' >>= withAttribute "Pattern Internal Operator") >>~ pushContext "Regular Expression Character Class") <|> (pushContext "Regular Expression Character Class" >> return ([], ""))) return (attr, result) parseRules "region_marker" = do (attr, result) <- (((pDetectIdentifier >>= withAttribute "Region Marker")) <|> ((pDetectSpaces >>= withAttribute "Region Marker"))) return (attr, result) parseRules "ObjectMember" = do (attr, result) <- (((pDetectChar False '.' >>= withAttribute "Normal Text")) <|> ((pDetectIdentifier >>= withAttribute "Object Member")) <|> ((pDetectSpaces >>= withAttribute "Normal Text") >>~ (popContext)) <|> ((lookAhead (pAnyChar "(){}:!%&+,-/.*<=>?[]|~^;") >> return ([],"") ) >>~ (popContext))) return (attr, result) parseRules "" = parseRules "Normal" parseRules x = fail $ "Unknown context" ++ x