{- This module was generated from data in the Kate syntax highlighting file javascript.xml, version 1.22, 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.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Doxygen import qualified Text.Highlighting.Kate.Syntax.Alert import qualified Text.Highlighting.Kate.Syntax.Modelines import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "JavaScript" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.js;*.kwinscript" -- | Highlight source code using this syntax definition. highlight :: String -> [SourceLine] highlight input = evalState (mapM parseSourceLine $ lines input) startingState parseSourceLine :: String -> State SyntaxState SourceLine parseSourceLine = mkParseSourceLine (parseExpression Nothing) -- | Parse an expression using appropriate local context. parseExpression :: Maybe (String,String) -> KateParser Token parseExpression mbcontext = do (lang,cont) <- maybe currentContext return mbcontext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("JavaScript","Shebang")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState if length contexts >= 2 then case context of ("JavaScript","Shebang") -> pushContext ("JavaScript","Normal") >> return () ("JavaScript","Normal") -> return () ("JavaScript","Object Member") -> (popContext) >> pEndLine ("JavaScript","NoRegExp") -> return () ("JavaScript","Conditional Expression") -> return () ("JavaScript","Object") -> return () ("JavaScript","String") -> (popContext) >> pEndLine ("JavaScript","String SQ") -> (popContext) >> pEndLine ("JavaScript","Comment") -> (popContext) >> pEndLine ("JavaScript","Multi/inline Comment") -> return () ("JavaScript","Regular Expression") -> return () ("JavaScript","Regular Expression Character Class") -> return () ("JavaScript","(regex caret first check)") -> (popContext) >> pEndLine ("JavaScript","(charclass caret first check)") -> (popContext) >> pEndLine ("JavaScript","region_marker") -> (popContext) >> pEndLine _ -> return () else return () withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" updateState $ \st -> st { synStPrevChar = last txt , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) } return (attr, txt) list_keywords = Set.fromList $ words $ "break case catch const continue debugger default delete do else finally for function if in instanceof new return switch this throw try typeof var void while with" list_reserved = Set.fromList $ words $ "class enum export extends import super implements interface let package private protected public static yield" list_primitives = Set.fromList $ words $ "Infinity NaN false null true undefined" regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'28'3f'3d'5cs'2a'5c'2e'29 = compileRegex True "[a-zA-Z_$][\\w$]*(?=\\s*\\.)" regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'28'3f'3d'5cs'2a'5c'28'29 = compileRegex True "[a-zA-Z_$][\\w$]*(?=\\s*\\()" regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a = compileRegex True "[a-zA-Z_$][\\w$]*" regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'5cs'2a'28'3f'3d'3a'29 = compileRegex True "[a-zA-Z_$][\\w$]*\\s*(?=:)" regex_'2f'5cw'2a = compileRegex True "/\\w*" regex_'5c'7b'5b'5cd'2c_'5d'2b'5c'7d = compileRegex True "\\{[\\d, ]+\\}" regex_'5c'5c'5bbB'5d = compileRegex True "\\\\[bB]" regex_'5c'5c'5bnrtvfDdSsWw'5d = compileRegex True "\\\\[nrtvfDdSsWw]" regex_'5c'5c'2e = compileRegex True "\\\\." regex_'5c'24'28'3f'3d'2f'29 = compileRegex True "\\$(?=/)" regex_'5c'5c'5b'5c'5b'5c'5d'5d = compileRegex True "\\\\[\\[\\]]" parseRules ("JavaScript","Shebang") = (((pColumn 0 >> pDetect2Chars False '#' '!' >>= withAttribute CommentTok) >>~ pushContext ("JavaScript","Comment")) <|> (pushContext ("JavaScript","Normal") >> currentContext >>= parseRules)) parseRules ("JavaScript","Normal") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pString False "//BEGIN" >>= withAttribute RegionMarkerTok) >>~ pushContext ("JavaScript","region_marker")) <|> ((pString False "//END" >>= withAttribute RegionMarkerTok) >>~ pushContext ("JavaScript","region_marker")) <|> ((pFloat >>= withAttribute FloatTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pHlCOct >>= withAttribute BaseNTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pHlCHex >>= withAttribute BaseNTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pAnyChar "])" >>= withAttribute NormalTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_reserved >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_primitives >>= withAttribute KeywordTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'28'3f'3d'5cs'2a'5c'2e'29 >>= withAttribute OtherTok) >>~ pushContext ("JavaScript","Object Member")) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'28'3f'3d'5cs'2a'5c'28'29 >>= withAttribute FunctionTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pDetectChar False '.' >>= withAttribute NormalTok) >>~ pushContext ("JavaScript","Object Member")) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a >>= withAttribute NormalTok) >>~ pushContext ("JavaScript","NoRegExp")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("JavaScript","String")) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("JavaScript","String SQ")) <|> ((Text.Highlighting.Kate.Syntax.Doxygen.parseExpression (Just ("Doxygen","")))) <|> ((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("JavaScript","Comment")) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("JavaScript","Multi/inline Comment")) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ pushContext ("JavaScript","(regex caret first check)")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("JavaScript","Object")) <|> ((pDetectChar False '?' >>= withAttribute NormalTok) >>~ pushContext ("JavaScript","Conditional Expression")) <|> ((pAnyChar ":!%&+,-/.*<=>?|~^;" >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("JavaScript","Object Member") = (((pDetectChar False '.' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'28'3f'3d'5cs'2a'5c'2e'29 >>= withAttribute OtherTok) >>~ pushContext ("JavaScript","Object Member")) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a >>= withAttribute FunctionTok)) <|> ((parseRules ("JavaScript","NoRegExp"))) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("JavaScript","NoRegExp") = (((lookAhead (pDetect2Chars False '/' '/') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetect2Chars False '/' '*') >> (popContext) >> currentContext >>= parseRules)) <|> ((pDetectChar False '/' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("JavaScript","Conditional Expression") = (((pDetectChar False ':' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("JavaScript","Normal"))) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Conditional Expression")) >> pDefault >>= withAttribute NormalTok)) parseRules ("JavaScript","Object") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'24'5d'5b'5cw'24'5d'2a'5cs'2a'28'3f'3d'3a'29 >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("JavaScript","Normal"))) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Object")) >> pDefault >>= withAttribute NormalTok)) parseRules ("JavaScript","String") = (((pHlCStringChar >>= withAttribute CharTok)) <|> ((pLineContinue >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("JavaScript","String SQ") = (((pHlCStringChar >>= withAttribute CharTok)) <|> ((pLineContinue >>= withAttribute StringTok)) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","String SQ")) >> pDefault >>= withAttribute StringTok)) parseRules ("JavaScript","Comment") = (((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> ((Text.Highlighting.Kate.Syntax.Modelines.parseExpression (Just ("Modelines","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("JavaScript","Multi/inline Comment") = (((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> ((Text.Highlighting.Kate.Syntax.Modelines.parseExpression (Just ("Modelines","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Multi/inline Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("JavaScript","Regular Expression") = (((pRegExpr regex_'2f'5cw'2a >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5c'7b'5b'5cd'2c_'5d'2b'5c'7d >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5c'5c'5bbB'5d >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5c'5c'5bnrtvfDdSsWw'5d >>= withAttribute BaseNTok)) <|> ((pDetectChar False '[' >>= withAttribute BaseNTok) >>~ pushContext ("JavaScript","(charclass caret first check)")) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5c'24'28'3f'3d'2f'29 >>= withAttribute FloatTok)) <|> ((pAnyChar "?+*()|" >>= withAttribute FloatTok)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Regular Expression")) >> pDefault >>= withAttribute OtherTok)) parseRules ("JavaScript","Regular Expression Character Class") = (((pRegExpr regex_'5c'5c'5b'5c'5b'5c'5d'5d >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute FloatTok)) <|> ((pDetectChar False ']' >>= withAttribute BaseNTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","Regular Expression Character Class")) >> pDefault >>= withAttribute BaseNTok)) parseRules ("JavaScript","(regex caret first check)") = (((pDetectChar False '^' >>= withAttribute FloatTok) >>~ pushContext ("JavaScript","Regular Expression")) <|> (pushContext ("JavaScript","Regular Expression") >> currentContext >>= parseRules)) parseRules ("JavaScript","(charclass caret first check)") = (((pDetectChar False '^' >>= withAttribute FloatTok) >>~ pushContext ("JavaScript","Regular Expression Character Class")) <|> (pushContext ("JavaScript","Regular Expression Character Class") >> currentContext >>= parseRules)) parseRules ("JavaScript","region_marker") = (((pDetectIdentifier >>= withAttribute RegionMarkerTok)) <|> ((pDetectSpaces >>= withAttribute RegionMarkerTok)) <|> (currentContext >>= \x -> guard (x == ("JavaScript","region_marker")) >> pDefault >>= withAttribute RegionMarkerTok)) parseRules ("Doxygen", _) = Text.Highlighting.Kate.Syntax.Doxygen.parseExpression Nothing parseRules ("Alerts", _) = Text.Highlighting.Kate.Syntax.Alert.parseExpression Nothing parseRules ("Modelines", _) = Text.Highlighting.Kate.Syntax.Modelines.parseExpression Nothing parseRules x = parseRules ("JavaScript","Shebang") <|> fail ("Unknown context" ++ show x)