{- This module was generated from data in the Kate syntax highlighting file d.xml, version 1.43, by 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.Definitions import Text.Highlighting.Kate.Common 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 = "D" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.d;*.D;*.di;*.DI;" -- | 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 = "D" } 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 [("D",["normal"])], synStLanguage = "D", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do newline <|> (eof >> return '\n') context <- currentContext case context of "normal" -> return () "UnicodeShort" -> (popContext >> return ()) "UnicodeLong" -> (popContext >> return ()) "HTMLEntity" -> (popContext >> return ()) "ModuleName" -> return () "Deprecated" -> return () "Linkage" -> (popContext >> return ()) "Linkage2" -> (popContext >> return ()) "Version" -> (popContext >> return ()) "Version2" -> (popContext >> return ()) "Pragmas" -> (popContext >> return ()) "RawString" -> return () "BQString" -> return () "HexString" -> return () "CharLiteral" -> (popContext >> return ()) "String" -> return () "CommentLine" -> (popContext >> return ()) "CommentBlock" -> return () "CommentNested" -> return () _ -> return () lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents, synStCharsParsedInLine = 0, synStPrevChar = '\n' } 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"),("Type","dt"),("Integer","dv"),("Binary","bn"),("Octal","bn"),("Hex","bn"),("Float","fl"),("LibrarySymbols","dt"),("Deprecated","co"),("Module","kw"),("Linkage","kw"),("Debug","kw"),("Assert","kw"),("Version","kw"),("Unit Test","kw"),("Pragma","kw"),("EscapeString","st"),("EscapeSequence","st"),("String","st"),("Char","ch"),("RawString","st"),("BQString","st"),("HexString","st"),("Comment","co"),("Error","er")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) list_keywords = Set.fromList $ words $ "abstract alias align asm auto body break case cast catch class const continue default delegate delete do else enum export false final finally for foreach foreach_reverse function goto if in inout interface invariant is lazy macro mixin new null out override package private protected public ref return scope static struct super switch synchronized template this throw true try typedef typeid typeof union volatile while with" list_deprecated = Set.fromList $ words $ "deprecated" list_modules = Set.fromList $ words $ "module import" list_types = Set.fromList $ words $ "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_libsymbols = Set.fromList $ words $ "string wstring dstring size_t ptrdiff_t hash_t Error Exception Object TypeInfo ClassInfo" list_linkage = Set.fromList $ words $ "extern" list_ltypes = Set.fromList $ words $ "C D Windows Pascal System" list_debug = Set.fromList $ words $ "debug" list_assert = Set.fromList $ words $ "assert" list_pragma = Set.fromList $ words $ "pragma" list_ptypes = Set.fromList $ words $ "msg lib" list_version = Set.fromList $ words $ "version" list_vtypes = Set.fromList $ words $ "DigitalMars X86 AMD64 Windows Win32 Win64 linux LittleEndian BigEndian D_InlineAsm none" list_specialtokens = Set.fromList $ words $ "__FILE__ __LINE__ __DATE__ __TIME__ __TIMESTAMP__ __VENDOR__ __VERSION__ __EOF__" list_unittest = Set.fromList $ words $ "unittest" regex_0'5bxX'5d'5b'5fa'2dfA'2dF'5cd'5d'2a'28'5c'2e'5b'5fa'2dfA'2dF'5cd'5d'2a'29'3f'5bpP'5d'5b'2d'2b'5d'3f'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'5bfFL'5d'3fi'3f = compileRegex "0[xX][_a-fA-F\\d]*(\\.[_a-fA-F\\d]*)?[pP][-+]?[\\d]+[_\\d]*[fFL]?i?" regex_'5b'5cd'5d'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'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'29'3f'5bfFL'5d'3fi'3f'7c'5beE'5d'5b'2d'2b'5d'3f'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'5bfFL'5d'3fi'3f'7c'5bfF'5di'3f'7c'5bfFL'5d'3fi'29 = compileRegex "[\\d][_\\d]*(\\.(?!\\.)[_\\d]*([eE][-+]?[\\d]+[_\\d]*)?[fFL]?i?|[eE][-+]?[\\d]+[_\\d]*[fFL]?i?|[fF]i?|[fFL]?i)" regex_'5c'2e'5b'5cd'5d'5b'5f'5cd'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'29'3f'5bfFL'5d'3fi'3f = compileRegex "\\.[\\d][_\\d]*([eE][-+]?[\\d]+[_\\d]*)?[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 "0[bB]_*[01][01_]*(L[uU]?|[uU]L?)?" regex_0'5f'2a'5b0'2d7'5d'5b0'2d7'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f = compileRegex "0_*[0-7][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 "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 "\\d+[\\d_]*(L[uU]?|[uU]L?)?" regex_'5b'5cda'2dfA'2dF'5d'7b4'7d = compileRegex "[\\da-fA-F]{4}" regex_'5b'5cda'2dfA'2dF'5d'7b8'7d = compileRegex "[\\da-fA-F]{8}" regex_'5ba'2dzA'2dZ'5d'5cw'2b'3b = compileRegex "[a-zA-Z]\\w+;" regex_'5b'5e'5cs'5cw'2e'3a'2c'5d = compileRegex "[^\\s\\w.:,]" regex_'5b'3b'28'7b'3d'5d = compileRegex "[;({=]" regex_'5b'5e'29'5d'2b = compileRegex "[^)]+" regex_'5b'5e'5cn'5d'2b = compileRegex "[^\\n]+" regex_'5b'5e'29'3b'5d'2b = compileRegex "[^);]+" regex_'5b'5e'5csa'2dfA'2dF'5cd'22'5d'2b = compileRegex "[^\\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 "\\\\(u[\\da-fA-F]{4}|U[\\da-fA-F]{8}|&[a-zA-Z]\\w+;)" regex_'2e'27 = compileRegex ".'" defaultAttributes = [("normal","Normal Text"),("UnicodeShort","EscapeString"),("UnicodeLong","EscapeString"),("HTMLEntity","EscapeString"),("ModuleName","Module Name"),("Deprecated","Deprecated"),("Linkage","Linkage"),("Linkage2","Linkage"),("Version","Version"),("Version2","Version"),("Pragmas","Pragma"),("RawString","RawString"),("BQString","BQString"),("HexString","HexString"),("CharLiteral","Char"),("String","String"),("CommentLine","Comment"),("CommentBlock","Comment"),("CommentNested","Comment")] parseRules "normal" = do (attr, result) <- (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute "Keyword")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_modules >>= withAttribute "Module") >>~ pushContext "ModuleName") <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute "Type")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_libsymbols >>= withAttribute "LibrarySymbols")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_linkage >>= withAttribute "Linkage") >>~ pushContext "Linkage") <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_debug >>= withAttribute "Debug")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_assert >>= withAttribute "Assert")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_pragma >>= withAttribute "Pragma") >>~ pushContext "Pragmas") <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_version >>= withAttribute "Version") >>~ pushContext "Version") <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_unittest >>= withAttribute "Unit Test")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_specialtokens >>= withAttribute "SpecialTokens")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_deprecated >>= withAttribute "Deprecated") >>~ pushContext "Deprecated") <|> ((pDetect2Chars False 'r' '"' >>= withAttribute "RawString") >>~ pushContext "RawString") <|> ((pDetect2Chars False 'x' '"' >>= withAttribute "HexString") >>~ pushContext "HexString") <|> ((pDetectIdentifier >>= withAttribute "Normal Text")) <|> ((pHlCStringChar >>= withAttribute "EscapeString") >>~ (popContext >> return ())) <|> ((pDetect2Chars False '\\' 'u' >>= withAttribute "EscapeString") >>~ pushContext "UnicodeShort") <|> ((pDetect2Chars False '\\' 'U' >>= withAttribute "EscapeString") >>~ pushContext "UnicodeLong") <|> ((pDetect2Chars False '\\' '&' >>= withAttribute "EscapeString") >>~ pushContext "HTMLEntity") <|> ((pDetectChar False '\'' >>= withAttribute "Char") >>~ pushContext "CharLiteral") <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "String") <|> ((pDetectChar False '`' >>= withAttribute "BQString") >>~ pushContext "BQString") <|> ((pDetect2Chars False '/' '/' >>= withAttribute "Comment") >>~ pushContext "CommentLine") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "CommentBlock") <|> ((pDetect2Chars False '/' '+' >>= withAttribute "Comment") >>~ pushContext "CommentNested") <|> ((pDetectChar False '{' >>= withAttribute "Normal Text")) <|> ((pDetectChar False '}' >>= withAttribute "Normal Text")) <|> ((pString False "..." >>= withAttribute "Normal Text") >>~ (popContext >> return ())) <|> ((pDetect2Chars False '.' '.' >>= withAttribute "Normal Text")) <|> ((pRegExpr regex_0'5bxX'5d'5b'5fa'2dfA'2dF'5cd'5d'2a'28'5c'2e'5b'5fa'2dfA'2dF'5cd'5d'2a'29'3f'5bpP'5d'5b'2d'2b'5d'3f'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'5bfFL'5d'3fi'3f >>= withAttribute "Float") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5b'5cd'5d'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'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'29'3f'5bfFL'5d'3fi'3f'7c'5beE'5d'5b'2d'2b'5d'3f'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'5bfFL'5d'3fi'3f'7c'5bfF'5di'3f'7c'5bfFL'5d'3fi'29 >>= withAttribute "Float") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5c'2e'5b'5cd'5d'5b'5f'5cd'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5b'5cd'5d'2b'5b'5f'5cd'5d'2a'29'3f'5bfFL'5d'3fi'3f >>= withAttribute "Float") >>~ (popContext >> return ())) <|> ((pRegExpr regex_0'5bbB'5d'5f'2a'5b01'5d'5b01'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute "Binary") >>~ (popContext >> return ())) <|> ((pRegExpr regex_0'5f'2a'5b0'2d7'5d'5b0'2d7'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute "Octal") >>~ (popContext >> return ())) <|> ((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 "Hex") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5cd'2b'5b'5cd'5f'5d'2a'28L'5buU'5d'3f'7c'5buU'5dL'3f'29'3f >>= withAttribute "Integer") >>~ (popContext >> return ())) <|> ((pString False "#line" >>= withAttribute "Pragma") >>~ (popContext >> return ()))) return (attr, result) parseRules "UnicodeShort" = do (attr, result) <- ((pRegExpr regex_'5b'5cda'2dfA'2dF'5d'7b4'7d >>= withAttribute "EscapeString") >>~ (popContext >> return ())) return (attr, result) parseRules "UnicodeLong" = do (attr, result) <- ((pRegExpr regex_'5b'5cda'2dfA'2dF'5d'7b8'7d >>= withAttribute "EscapeString") >>~ (popContext >> return ())) return (attr, result) parseRules "HTMLEntity" = do (attr, result) <- (((pRegExpr regex_'5ba'2dzA'2dZ'5d'5cw'2b'3b >>= withAttribute "EscapeString") >>~ (popContext >> return ())) <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "ModuleName" = do (attr, result) <- (((pDetect2Chars False '/' '/' >>= withAttribute "Comment") >>~ pushContext "CommentLine") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "CommentBlock") <|> ((pDetect2Chars False '/' '+' >>= withAttribute "Comment") >>~ pushContext "CommentNested") <|> ((pRegExpr regex_'5b'5e'5cs'5cw'2e'3a'2c'5d >>= withAttribute "Module Name") >>~ (popContext >> return ()))) return (attr, result) parseRules "Deprecated" = do (attr, result) <- (((pDetect2Chars False '/' '/' >>= withAttribute "Comment") >>~ pushContext "CommentLine") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "CommentBlock") <|> ((pDetect2Chars False '/' '+' >>= withAttribute "Comment") >>~ pushContext "CommentNested") <|> ((pRegExpr regex_'5b'3b'28'7b'3d'5d >>= withAttribute "Normal Text") >>~ (popContext >> return ()))) return (attr, result) parseRules "Linkage" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Linkage")) <|> ((pDetectChar False '(' >>= withAttribute "Normal Text") >>~ pushContext "Linkage2") <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "Linkage2" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Linkage")) <|> ((pString False "C++" >>= withAttribute "Linkage Type") >>~ (popContext >> return ())) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_ltypes >>= withAttribute "Linkage Type") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5b'5e'29'5d'2b >>= withAttribute "Error") >>~ (popContext >> return ())) <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "Version" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Version")) <|> ((pDetectChar False '=' >>= withAttribute "Normal Text") >>~ pushContext "Version2") <|> ((pDetectChar False '(' >>= withAttribute "Normal Text") >>~ pushContext "Version2") <|> ((pDetectChar False ';' >>= withAttribute "Normal Text") >>~ (popContext >> return ())) <|> ((pDetectChar False ')' >>= withAttribute "Normal Text") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5b'5e'5cn'5d'2b >>= withAttribute "Error") >>~ (popContext >> return ())) <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "Version2" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Version")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_vtypes >>= withAttribute "Version Type") >>~ (popContext >> return ())) <|> ((pDetectIdentifier >>= withAttribute "Normal Text") >>~ (popContext >> return ())) <|> ((pInt >>= withAttribute "Integer") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5b'5e'29'3b'5d'2b >>= withAttribute "Error") >>~ (popContext >> return ())) <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "Pragmas" = do (attr, result) <- (((pDetectChar False '(' >>= withAttribute "Normal Text")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_ptypes >>= withAttribute "Version Type") >>~ (popContext >> return ())) <|> ((pDetectIdentifier >>= withAttribute "Normal Text") >>~ (popContext >> return ()))) return (attr, result) parseRules "RawString" = do (attr, result) <- ((pDetectChar False '"' >>= withAttribute "RawString") >>~ (popContext >> return ())) return (attr, result) parseRules "BQString" = do (attr, result) <- ((pDetectChar False '`' >>= withAttribute "BQString") >>~ (popContext >> return ())) return (attr, result) parseRules "HexString" = do (attr, result) <- (((pDetectChar False '"' >>= withAttribute "HexString") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5b'5e'5csa'2dfA'2dF'5cd'22'5d'2b >>= withAttribute "Error"))) return (attr, result) parseRules "CharLiteral" = do (attr, result) <- (((pHlCStringChar >>= withAttribute "EscapeSequence")) <|> ((pDetectChar False '\'' >>= withAttribute "Char") >>~ (popContext >> return ())) <|> ((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 "EscapeSequence")) <|> ((pDetectChar False '\'' >>= withAttribute "Char") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'2e'27 >>= withAttribute "Char")) <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "String" = do (attr, result) <- (((pDetect2Chars False '\\' '"' >>= withAttribute "String")) <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ (popContext >> return ())) <|> ((pHlCStringChar >>= withAttribute "EscapeSequence")) <|> ((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 "EscapeSequence"))) return (attr, result) parseRules "CommentLine" = pzero parseRules "CommentBlock" = do (attr, result) <- ((pDetect2Chars False '*' '/' >>= withAttribute "Comment") >>~ (popContext >> return ())) return (attr, result) parseRules "CommentNested" = do (attr, result) <- (((pDetect2Chars False '/' '+' >>= withAttribute "Comment") >>~ pushContext "CommentNested") <|> ((pDetect2Chars False '+' '/' >>= withAttribute "Comment") >>~ (popContext >> return ()))) return (attr, result) parseRules x = fail $ "Unknown context" ++ x