{- This module was generated from data in the Kate syntax highlighting file d.xml, version 2, by Diggory Hardy (diggory.hardy@gmail.com), Aziz Köksal (aziz.koeksal@gmail.com), Jari-Matti Mäkelä (jmjm@iki.fi), Simon J Mackenzie (project.katedxml@smackoz.fastmail.fm) -} module Text.Highlighting.Kate.Syntax.D (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert 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 = "D" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.d;*.D;*.di;*.DI;" -- | 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 = [("D","normal")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState st <- getState if length contexts >= 2 then case context of _ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False } ("D","normal") -> return () ("D","StartingLetter") -> (popContext) >> pEndLine ("D","Properties") -> return () ("D","NumberLiteral") -> return () ("D","LinePragma") -> (popContext) >> pEndLine ("D","UnicodeShort") -> (popContext) >> pEndLine ("D","UnicodeLong") -> (popContext) >> pEndLine ("D","HTMLEntity") -> (popContext) >> pEndLine ("D","ModuleName") -> return () ("D","Linkage") -> return () ("D","Linkage2") -> return () ("D","Version") -> return () ("D","Version2") -> return () ("D","Scope") -> return () ("D","Scope2") -> return () ("D","Pragma") -> return () ("D","Pragma2") -> return () ("D","RawString") -> return () ("D","BQString") -> return () ("D","HexString") -> return () ("D","CharLiteral") -> pushContext ("D","CharLiteralClosing") >> return () ("D","CharLiteralClosing") -> (popContext >> popContext) >> pEndLine ("D","String") -> return () ("D","CommentRules") -> (popContext) >> pEndLine ("D","Region Marker") -> (popContext) >> pEndLine ("D","CommentLine") -> (popContext) >> pEndLine ("D","CommentBlock") -> return () ("D","CommentNested") -> return () ("D","DdocNormal") -> return () ("D","DdocLine") -> (popContext) >> pEndLine ("D","DdocBlock") -> return () ("D","DdocNested") -> return () ("D","DdocNested2") -> return () ("D","DdocMacro") -> return () ("D","DdocMacro2") -> return () ("D","DdocMacro3") -> return () ("D","MacroRules") -> return () ("D","DdocBlockCode") -> return () ("D","DdocNestedCode") -> return () _ -> 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_userkeywords = Set.fromList $ words $ "" list_statements = Set.fromList $ words $ "asm body break case catch continue default do else finally for foreach foreach_reverse goto if mixin return switch throw try while with synchronized" list_attributes = Set.fromList $ words $ "abstract align auto const export final immutable inout invariant lazy nothrow override package private protected public pure ref static out scope" list_expressions = Set.fromList $ words $ "false null super this true typeid assert cast is new delete in delegate function" list_modules = Set.fromList $ words $ "module import" list_declarators = Set.fromList $ words $ "alias enum typedef class interface struct union" list_types = Set.fromList $ words $ "typeof void bool byte ubyte short ushort int uint long ulong cent ucent float double real ireal ifloat idouble creal cfloat cdouble char wchar dchar" list_templates = Set.fromList $ words $ "macro template" list_properties = Set.fromList $ words $ "init sizeof alignof mangleof stringof tupleof offsetof max min infinity nan dig epsilon mant_dig max_10_exp max_exp min_10_exp min_exp re im length ptr dup idup reverse sort keys values rehash" list_libsymbols = Set.fromList $ words $ "size_t ptrdiff_t hash_t Error Exception Object TypeInfo ClassInfo ModuleInfo Interface OffsetTypeInfo TypeInfo_Typedef TypeInfo_Enum TypeInfo_Pointer TypeInfo_Array TypeInfo_StaticArray TypeInfo_AssociativeArray TypeInfo_Function TypeInfo_Delegate TypeInfo_Class TypeInfo_Interface TypeInfo_Struct TypeInfo_Tuple string wstring dstring bit TypeInfo_Const TypeInfo_Invariant" list_linkage = Set.fromList $ words $ "extern" list_ltypes = Set.fromList $ words $ "C D Windows Pascal System" list_ptypes = Set.fromList $ words $ "msg lib" list_scope'5fkeywords = Set.fromList $ words $ "exit success failure" list_vtypes = Set.fromList $ words $ "DigitalMars X86 X86_64 Windows Win32 Win64 linux LittleEndian BigEndian D_Coverage D_InlineAsm_X86 unittest D_Version2 none all" list_specialtokens = Set.fromList $ words $ "__FILE__ __LINE__ __DATE__ __TIME__ __TIMESTAMP__ __VENDOR__ __VERSION__ __EOF__" list_tests = Set.fromList $ words $ "debug unittest" list_pragma = Set.fromList $ words $ "pragma" list_version = Set.fromList $ words $ "version" list_deprecated = Set.fromList $ words $ "deprecated volatile" regex_'5ba'2dzA'2dZ'5f'5d = compileRegex True "[a-zA-Z_]" regex_'5c'2e'5cd'5b'5cd'5f'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5cd'5b'5cd'5f'5d'2a'29'3f'5bfFL'5d'3fi'3f = compileRegex True "\\.\\d[\\d_]*([eE][-+]?\\d[\\d_]*)?[fFL]?i?" regex_'5cd = compileRegex True "\\d" regex_'5b'5ea'2dzA'2dZ'5f'5d = compileRegex True "[^a-zA-Z_]" regex_in'5cs'2a'28'3f'3d'5c'7b'29 = compileRegex True "in\\s*(?=\\{)" regex_out'5cs'2a'28'3f'3d'28'5c'28'28'5ba'2dzA'2dZ'5f'5d'5b'5cw'5f'5d'2a'29'3f'5c'29'5cs'2a'29'3f'5c'7b'29 = compileRegex True "out\\s*(?=(\\(([a-zA-Z_][\\w_]*)?\\)\\s*)?\\{)" regex_scope'5cs'2a'28'3f'3d'5c'28'29 = compileRegex True "scope\\s*(?=\\()" regex_import'5cs'2a'28'3f'3d'5c'28'29 = compileRegex True "import\\s*(?=\\()" regex_function'5cs'2a'28'3f'3d'5c'28'29 = compileRegex True "function\\s*(?=\\()" regex_delegate'5cs'2a'28'3f'3d'5c'28'29 = compileRegex True "delegate\\s*(?=\\()" regex_0'5bxX'5d'5b'5cda'2dfA'2dF'5f'5d'2a'28'5c'2e'5b'5cda'2dfA'2dF'5f'5d'2a'29'3f'5bpP'5d'5b'2d'2b'5d'3f'5cd'5b'5cd'5f'5d'2a'5bfFL'5d'3fi'3f = compileRegex True "0[xX][\\da-fA-F_]*(\\.[\\da-fA-F_]*)?[pP][-+]?\\d[\\d_]*[fFL]?i?" regex_'5cd'5b'5f'5cd'5d'2a'28'5c'2e'28'3f'21'5c'2e'29'5b'5f'5cd'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5cd'5b'5f'5cd'5d'2a'29'3f'5bfFL'5d'3fi'3f'7c'5beE'5d'5b'2d'2b'5d'3f'5cd'5b'5f'5cd'5d'2a'5bfFL'5d'3fi'3f'7c'5bfF'5di'3f'7c'5bfFL'5d'3fi'29 = compileRegex True "\\d[_\\d]*(\\.(?!\\.)[_\\d]*([eE][-+]?\\d[_\\d]*)?[fFL]?i?|[eE][-+]?\\d[_\\d]*[fFL]?i?|[fF]i?|[fFL]?i)" regex_0'5bbB'5d'5f'2a'5b01'5d'5b01'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f = compileRegex True "0[bB]_*[01][01_]*(L[uU]?|[uU]L?)?" regex_0'5b0'2d7'5f'5d'2b'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f = compileRegex True "0[0-7_]+(L[uU]?|[uU]L?)?" regex_0'5bxX'5d'5f'2a'5b'5cda'2dfA'2dF'5d'5b'5cda'2dfA'2dF'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f = compileRegex True "0[xX]_*[\\da-fA-F][\\da-fA-F_]*(L[uU]?|[uU]L?)?" regex_'5cd'2b'5b'5cd'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f = compileRegex True "\\d+[\\d_]*(L[uU]?|[uU]L?)?" regex_'28'280'28'5b0'2d7'5f'5d'2b'7c'5bbB'5d'5f'2a'5b01'5d'5b01'5f'5d'2a'7c'5bxX'5d'5f'2a'5b'5cda'2dfA'2dF'5d'5b'5cda'2dfA'2dF'5f'5d'2a'29'29'7c'5cd'2b'5b'5cd'5f'5d'2a'29'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f = compileRegex True "((0([0-7_]+|[bB]_*[01][01_]*|[xX]_*[\\da-fA-F][\\da-fA-F_]*))|\\d+[\\d_]*)(L[uU]?|[uU]L?)?" regex_'22'5b'5e'22'5d'2a'22 = compileRegex True "\"[^\"]*\"" regex_'2e'2b = compileRegex True ".+" regex_'5b'5cda'2dfA'2dF'5d'7b4'7d = compileRegex True "[\\da-fA-F]{4}" regex_'5b'5cda'2dfA'2dF'5d'7b8'7d = compileRegex True "[\\da-fA-F]{8}" regex_'5ba'2dzA'2dZ'5d'5cw'2b'3b = compileRegex True "[a-zA-Z]\\w+;" regex_'5b'5e'5cs'5cw'2e'3a'2c'3d'5d = compileRegex True "[^\\s\\w.:,=]" regex_'5b'5e'29'5cs'5cn'5d'2b = compileRegex True "[^)\\s\\n]+" regex_'5b'5e'5cs'5cn'5d'2b = compileRegex True "[^\\s\\n]+" regex_'5b'5e'5csa'2dfA'2dF'5cd'22'5d'2b = compileRegex True "[^\\sa-fA-F\\d\"]+" regex_'5c'5c'28u'5b'5cda'2dfA'2dF'5d'7b4'7d'7cU'5b'5cda'2dfA'2dF'5d'7b8'7d'7c'26'5ba'2dzA'2dZ'5d'5cw'2b'3b'29 = compileRegex True "\\\\(u[\\da-fA-F]{4}|U[\\da-fA-F]{8}|&[a-zA-Z]\\w+;)" regex_'5c'5c'2e = compileRegex True "\\\\." regex_'2e = compileRegex True "." regex_'2f'7b3'2c'7d = compileRegex True "/{3,}" regex_'2f'5c'2a'7b2'2c'7d'28'3f'21'2f'29 = compileRegex True "/\\*{2,}(?!/)" regex_'2f'5c'2b'7b2'2c'7d'28'3f'21'2f'29 = compileRegex True "/\\+{2,}(?!/)" regex_'5b'5cw'5f'5d'2b'3a'28'24'7c'5cs'29 = compileRegex True "[\\w_]+:($|\\s)" regex_'5c'2a'2b'2f = compileRegex True "\\*+/" regex_'5b'5e'2d'5d'2d'7b3'2c'7d = compileRegex True "[^-]-{3,}" regex_'2d'7b3'2c'7d'28'24'7c'5cs'29 = compileRegex True "-{3,}($|\\s)" regex_'5c'2b'2b'2f = compileRegex True "\\++/" parseRules ("D","normal") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((lookAhead (pRegExpr regex_'5ba'2dzA'2dZ'5f'5d) >> pushContext ("D","StartingLetter") >> currentContext >>= parseRules)) <|> ((pHlCStringChar >>= withAttribute SpecialCharTok)) <|> ((pDetect2Chars False '\\' 'u' >>= withAttribute SpecialCharTok) >>~ pushContext ("D","UnicodeShort")) <|> ((pDetect2Chars False '\\' 'U' >>= withAttribute SpecialCharTok) >>~ pushContext ("D","UnicodeLong")) <|> ((pDetect2Chars False '\\' '&' >>= withAttribute SpecialCharTok) >>~ pushContext ("D","HTMLEntity")) <|> ((pDetectChar False '\'' >>= withAttribute CharTok) >>~ pushContext ("D","CharLiteral")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("D","String")) <|> ((pDetectChar False '`' >>= withAttribute SpecialStringTok) >>~ pushContext ("D","BQString")) <|> ((pFirstNonSpace >> pString False "//BEGIN" >>= withAttribute RegionMarkerTok) >>~ pushContext ("D","Region Marker")) <|> ((pFirstNonSpace >> pString False "//END" >>= withAttribute RegionMarkerTok) >>~ pushContext ("D","Region Marker")) <|> ((parseRules ("D","CommentRules"))) <|> ((pString False "..." >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '.' '.' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'2e'5cd'5b'5cd'5f'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5cd'5b'5cd'5f'5d'2a'29'3f'5bfFL'5d'3fi'3f >>= withAttribute FloatTok)) <|> ((pDetectChar False '.' >>= withAttribute NormalTok) >>~ pushContext ("D","Properties")) <|> ((lookAhead (pRegExpr regex_'5cd) >> pushContext ("D","NumberLiteral") >> currentContext >>= parseRules)) <|> ((pString False "#line" >>= withAttribute KeywordTok) >>~ pushContext ("D","LinePragma")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok)) <|> ((pAnyChar ":!%&()+,-/.*<=>?[]|~^;" >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("D","normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","StartingLetter") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((lookAhead (pRegExpr regex_'5b'5ea'2dzA'2dZ'5f'5d) >> (popContext) >> currentContext >>= parseRules)) <|> ((pRegExpr regex_in'5cs'2a'28'3f'3d'5c'7b'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_out'5cs'2a'28'3f'3d'28'5c'28'28'5ba'2dzA'2dZ'5f'5d'5b'5cw'5f'5d'2a'29'3f'5c'29'5cs'2a'29'3f'5c'7b'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_scope'5cs'2a'28'3f'3d'5c'28'29 >>= withAttribute KeywordTok) >>~ pushContext ("D","Scope")) <|> ((pRegExpr regex_import'5cs'2a'28'3f'3d'5c'28'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_function'5cs'2a'28'3f'3d'5c'28'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_delegate'5cs'2a'28'3f'3d'5c'28'29 >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_statements >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_attributes >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_expressions >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_declarators >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_templates >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_modules >>= withAttribute KeywordTok) >>~ pushContext ("D","ModuleName")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_libsymbols >>= withAttribute BuiltInTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_linkage >>= withAttribute KeywordTok) >>~ pushContext ("D","Linkage")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_specialtokens >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_tests >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_pragma >>= withAttribute KeywordTok) >>~ pushContext ("D","Pragma")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_version >>= withAttribute KeywordTok) >>~ pushContext ("D","Version")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_deprecated >>= withAttribute KeywordTok)) <|> ((pDetect2Chars False 'r' '"' >>= withAttribute VerbatimStringTok) >>~ pushContext ("D","RawString")) <|> ((pDetect2Chars False 'x' '"' >>= withAttribute SpecialStringTok) >>~ pushContext ("D","HexString")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_userkeywords >>= withAttribute DataTypeTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("D","StartingLetter")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Properties") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_properties >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("D","NumberLiteral") = (((pRegExpr regex_0'5bxX'5d'5b'5cda'2dfA'2dF'5f'5d'2a'28'5c'2e'5b'5cda'2dfA'2dF'5f'5d'2a'29'3f'5bpP'5d'5b'2d'2b'5d'3f'5cd'5b'5cd'5f'5d'2a'5bfFL'5d'3fi'3f >>= withAttribute FloatTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cd'5b'5f'5cd'5d'2a'28'5c'2e'28'3f'21'5c'2e'29'5b'5f'5cd'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5cd'5b'5f'5cd'5d'2a'29'3f'5bfFL'5d'3fi'3f'7c'5beE'5d'5b'2d'2b'5d'3f'5cd'5b'5f'5cd'5d'2a'5bfFL'5d'3fi'3f'7c'5bfF'5di'3f'7c'5bfFL'5d'3fi'29 >>= withAttribute FloatTok) >>~ (popContext)) <|> ((pRegExpr regex_0'5bbB'5d'5f'2a'5b01'5d'5b01'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pRegExpr regex_0'5b0'2d7'5f'5d'2b'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pRegExpr regex_0'5bxX'5d'5f'2a'5b'5cda'2dfA'2dF'5d'5b'5cda'2dfA'2dF'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cd'2b'5b'5cd'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute DecValTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("D","LinePragma") = (((pDetectSpaces >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28'280'28'5b0'2d7'5f'5d'2b'7c'5bbB'5d'5f'2a'5b01'5d'5b01'5f'5d'2a'7c'5bxX'5d'5f'2a'5b'5cda'2dfA'2dF'5d'5b'5cda'2dfA'2dF'5f'5d'2a'29'29'7c'5cd'2b'5b'5cd'5f'5d'2a'29'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'22'5b'5e'22'5d'2a'22 >>= withAttribute StringTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_specialtokens >>= withAttribute NormalTok)) <|> ((parseRules ("D","CommentRules"))) <|> ((pRegExpr regex_'2e'2b >>= withAttribute ErrorTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","LinePragma")) >> pDefault >>= withAttribute KeywordTok)) parseRules ("D","UnicodeShort") = (((pRegExpr regex_'5b'5cda'2dfA'2dF'5d'7b4'7d >>= withAttribute SpecialCharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","UnicodeShort")) >> pDefault >>= withAttribute SpecialCharTok)) parseRules ("D","UnicodeLong") = (((pRegExpr regex_'5b'5cda'2dfA'2dF'5d'7b8'7d >>= withAttribute SpecialCharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","UnicodeLong")) >> pDefault >>= withAttribute SpecialCharTok)) parseRules ("D","HTMLEntity") = (((pRegExpr regex_'5ba'2dzA'2dZ'5d'5cw'2b'3b >>= withAttribute SpecialCharTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("D","ModuleName") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((parseRules ("D","CommentRules"))) <|> ((lookAhead (pRegExpr regex_'5b'5e'5cs'5cw'2e'3a'2c'3d'5d) >> (popContext) >> currentContext >>= parseRules)) <|> (currentContext >>= \x -> guard (x == ("D","ModuleName")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Linkage") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("D","Linkage2")) <|> ((parseRules ("D","CommentRules"))) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("D","Linkage2") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pString False "C++" >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_ltypes >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((parseRules ("D","CommentRules"))) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5b'5e'29'5cs'5cn'5d'2b >>= withAttribute ErrorTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("D","Linkage2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Version") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '=' >>= withAttribute NormalTok) >>~ pushContext ("D","Version2")) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("D","Version2")) <|> ((parseRules ("D","CommentRules"))) <|> ((pRegExpr regex_'5b'5e'5cs'5cn'5d'2b >>= withAttribute ErrorTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","Version")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Version2") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_vtypes >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pDetectIdentifier >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5cd'2b'5b'5cd'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute DecValTok) >>~ (popContext >> popContext)) <|> ((parseRules ("D","CommentRules"))) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5b'5e'29'5cs'5cn'5d'2b >>= withAttribute ErrorTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("D","Version2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Scope") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("D","Scope2")) <|> ((parseRules ("D","CommentRules"))) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("D","Scope2") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_scope'5fkeywords >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules ("D","CommentRules"))) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5b'5e'29'5cs'5cn'5d'2b >>= withAttribute ErrorTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("D","Scope2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Pragma") = (((pDetectSpaces >>= withAttribute KeywordTok)) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("D","Pragma2")) <|> ((parseRules ("D","CommentRules"))) <|> ((pRegExpr regex_'5b'5e'5cs'5cn'5d'2b >>= withAttribute ErrorTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","Pragma")) >> pDefault >>= withAttribute KeywordTok)) parseRules ("D","Pragma2") = (((pDetectSpaces >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_ptypes >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pDetectIdentifier >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((parseRules ("D","CommentRules"))) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5b'5e'29'5cs'5cn'5d'2b >>= withAttribute ErrorTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("D","Pragma2")) >> pDefault >>= withAttribute KeywordTok)) parseRules ("D","RawString") = (((pDetectChar False '"' >>= withAttribute VerbatimStringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","RawString")) >> pDefault >>= withAttribute VerbatimStringTok)) parseRules ("D","BQString") = (((pDetectChar False '`' >>= withAttribute SpecialStringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("D","BQString")) >> pDefault >>= withAttribute SpecialStringTok)) parseRules ("D","HexString") = (((pDetectChar False '"' >>= withAttribute SpecialStringTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5e'5csa'2dfA'2dF'5cd'22'5d'2b >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("D","HexString")) >> pDefault >>= withAttribute SpecialStringTok)) parseRules ("D","CharLiteral") = (((pDetectChar False '\'' >>= withAttribute CharTok) >>~ (popContext)) <|> ((pHlCStringChar >>= withAttribute SpecialCharTok) >>~ pushContext ("D","CharLiteralClosing")) <|> ((pRegExpr regex_'5c'5c'28u'5b'5cda'2dfA'2dF'5d'7b4'7d'7cU'5b'5cda'2dfA'2dF'5d'7b8'7d'7c'26'5ba'2dzA'2dZ'5d'5cw'2b'3b'29 >>= withAttribute SpecialCharTok) >>~ pushContext ("D","CharLiteralClosing")) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute ErrorTok) >>~ pushContext ("D","CharLiteralClosing")) <|> ((pRegExpr regex_'2e >>= withAttribute CharTok) >>~ pushContext ("D","CharLiteralClosing")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("D","CharLiteralClosing") = (((pDetectChar False '\'' >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("D","String") = (((pHlCStringChar >>= withAttribute SpecialCharTok)) <|> ((pDetect2Chars False '"' 'c' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetect2Chars False '"' 'w' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetect2Chars False '"' 'd' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' 'u' >>= withAttribute SpecialCharTok) >>~ pushContext ("D","UnicodeShort")) <|> ((pDetect2Chars False '\\' 'U' >>= withAttribute SpecialCharTok) >>~ pushContext ("D","UnicodeLong")) <|> ((pDetect2Chars False '\\' '&' >>= withAttribute SpecialCharTok) >>~ pushContext ("D","HTMLEntity")) <|> (currentContext >>= \x -> guard (x == ("D","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("D","CommentRules") = (((parseRules ("D","DdocNormal"))) <|> ((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("D","CommentLine")) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("D","CommentBlock")) <|> ((pDetect2Chars False '/' '+' >>= withAttribute CommentTok) >>~ pushContext ("D","CommentNested")) <|> (currentContext >>= \x -> guard (x == ("D","CommentRules")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","Region Marker") = (currentContext >>= \x -> guard (x == ("D","Region Marker")) >> pDefault >>= withAttribute RegionMarkerTok) parseRules ("D","CommentLine") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("D","CommentLine")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","CommentBlock") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("D","CommentBlock")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","CommentNested") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '/' '+' >>= withAttribute CommentTok) >>~ pushContext ("D","CommentNested")) <|> ((pDetect2Chars False '+' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("D","CommentNested")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","DdocNormal") = (((pRegExpr regex_'2f'7b3'2c'7d >>= withAttribute CommentTok) >>~ pushContext ("D","DdocLine")) <|> ((pRegExpr regex_'2f'5c'2a'7b2'2c'7d'28'3f'21'2f'29 >>= withAttribute CommentTok) >>~ pushContext ("D","DdocBlock")) <|> ((pRegExpr regex_'2f'5c'2b'7b2'2c'7d'28'3f'21'2f'29 >>= withAttribute CommentTok) >>~ pushContext ("D","DdocNested")) <|> (currentContext >>= \x -> guard (x == ("D","DdocNormal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","DdocLine") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '$' '(' >>= withAttribute OtherTok) >>~ pushContext ("D","DdocMacro")) <|> ((pRegExpr regex_'5b'5cw'5f'5d'2b'3a'28'24'7c'5cs'29 >>= withAttribute KeywordTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("D","DdocLine")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","DdocBlock") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'5c'2a'2b'2f >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pFirstNonSpace >> pDetectChar False '*' >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '$' '(' >>= withAttribute OtherTok) >>~ pushContext ("D","DdocMacro")) <|> ((pRegExpr regex_'5b'5cw'5f'5d'2b'3a'28'24'7c'5cs'29 >>= withAttribute KeywordTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pRegExpr regex_'5b'5e'2d'5d'2d'7b3'2c'7d >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'2d'7b3'2c'7d'28'24'7c'5cs'29 >>= withAttribute CommentTok) >>~ pushContext ("D","DdocBlockCode")) <|> (currentContext >>= \x -> guard (x == ("D","DdocBlock")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","DdocNested") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '/' '+' >>= withAttribute CommentTok) >>~ pushContext ("D","DdocNested2")) <|> ((pRegExpr regex_'5c'2b'2b'2f >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pFirstNonSpace >> pDetectChar False '+' >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '$' '(' >>= withAttribute OtherTok) >>~ pushContext ("D","DdocMacro")) <|> ((pRegExpr regex_'5b'5cw'5f'5d'2b'3a'28'24'7c'5cs'29 >>= withAttribute KeywordTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pRegExpr regex_'5b'5e'2d'5d'2d'7b3'2c'7d >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'2d'7b3'2c'7d'28'24'7c'5cs'29 >>= withAttribute CommentTok) >>~ pushContext ("D","DdocNestedCode")) <|> (currentContext >>= \x -> guard (x == ("D","DdocNested")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","DdocNested2") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'5c'2b'2b'2f >>= withAttribute CommentTok) >>~ (popContext)) <|> ((parseRules ("D","DdocNested"))) <|> (currentContext >>= \x -> guard (x == ("D","DdocNested2")) >> pDefault >>= withAttribute CommentTok)) parseRules ("D","DdocMacro") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((parseRules ("D","MacroRules"))) <|> ((pDetectIdentifier >>= withAttribute OtherTok) >>~ pushContext ("D","DdocMacro2")) <|> (currentContext >>= \x -> guard (x == ("D","DdocMacro")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("D","DdocMacro2") = (((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((parseRules ("D","MacroRules"))) <|> (currentContext >>= \x -> guard (x == ("D","DdocMacro2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","DdocMacro3") = (((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("D","MacroRules"))) <|> (currentContext >>= \x -> guard (x == ("D","DdocMacro3")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","MacroRules") = (((pDetect2Chars False '$' '(' >>= withAttribute OtherTok) >>~ pushContext ("D","DdocMacro")) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("D","DdocMacro3")) <|> ((pFirstNonSpace >> pDetectChar False '*' >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("D","MacroRules")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","DdocBlockCode") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'2a'2b'2f >>= withAttribute CommentTok) >>~ (popContext >> popContext)) <|> ((pFirstNonSpace >> pDetectChar False '*' >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'5b'5e'2d'5d'2d'7b3'2c'7d >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'2d'7b3'2c'7d'28'24'7c'5cs'29 >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.D.parseExpression (Just ("D","")))) <|> (currentContext >>= \x -> guard (x == ("D","DdocBlockCode")) >> pDefault >>= withAttribute NormalTok)) parseRules ("D","DdocNestedCode") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'2b'2b'2f >>= withAttribute CommentTok) >>~ (popContext >> popContext)) <|> ((pFirstNonSpace >> pDetectChar False '+' >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'5b'5e'2d'5d'2d'7b3'2c'7d >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'2d'7b3'2c'7d'28'24'7c'5cs'29 >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.D.parseExpression (Just ("D","")))) <|> (currentContext >>= \x -> guard (x == ("D","DdocNestedCode")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Alerts", _) = Text.Highlighting.Kate.Syntax.Alert.parseExpression Nothing parseRules ("D", _) = Text.Highlighting.Kate.Syntax.D.parseExpression Nothing parseRules x = parseRules ("D","normal") <|> fail ("Unknown context" ++ show x)