{- This module was generated from data in the Kate syntax highlighting file ocaml.xml, version 3, by Glyn Webster (glynwebster@orcon.net.nz) and Vincent Hugot (vincent.hugot@gmail.com) -} module Text.Highlighting.Kate.Syntax.Ocaml (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Latex 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 = "Objective Caml" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.ml;*.mli" -- | 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 = [("Objective Caml","Code")], 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 } ("Objective Caml","Code") -> return () ("Objective Caml","Nested Code 1") -> return () ("Objective Caml","Nested Code 2") -> return () ("Objective Caml","String") -> return () ("Objective Caml","qtest header") -> pushContext ("Objective Caml","qtest") >> return () ("Objective Caml","qtest param") -> pushContext ("Objective Caml","qtest") >> return () ("Objective Caml","qtest") -> return () ("Objective Caml","Comment") -> return () ("Objective Caml","String in Comment") -> return () ("Objective Caml","Camlp4 Quotation") -> return () ("Objective Caml","Ocamldoc") -> return () ("Objective Caml","Ocamldoc Code") -> return () ("Objective Caml","Ocamldoc Preformatted") -> return () ("Objective Caml","Ocamldoc Verbatim") -> return () ("Objective Caml","Ocamldoc LaTeX") -> return () ("Objective Caml","Ocamldoc Identifier") -> return () ("Objective Caml","Nested Ocamldoc") -> return () ("Objective Caml","Ocamldoc Bold") -> return () ("Objective Caml","Ocamldoc Italic") -> return () ("Objective Caml","Ocamldoc Emphasised") -> return () ("Objective Caml","Ocamldoc Heading") -> return () ("Objective Caml","Ocamldoc Link") -> return () ("Objective Caml","Ocamldoc References") -> return () ("Objective Caml","Unmatched Closing Brackets") -> 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_qtest_keywords = Set.fromList $ words $ "in as forall" list_Keywords = Set.fromList $ words $ "and as assert asr begin class closed constraint do done downto else end exception external false for fun function functor if in include inherit land lazy let lor lsl lsr lxor match method mod module mutable new object of open or parser private rec sig struct then to true try type val virtual when while with" list_Revised_Syntax_Keywords = Set.fromList $ words $ "declare value where" list_Pervasive_Functions = Set.fromList $ words $ "abs abs_float acos asin at_exit atan atan2 bool_of_string ceil char_of_int classify_float close_in close_in_noerr close_out close_out_noerr compare cos cosh decr do_at_exit epsilon_float exp float float_of_int float_of_string floor flush flush_all format_of_string frexp fst ignore in_channel_length incr infinity input input_binary_int input_byte input_char input_line input_value int_of_char int_of_float int_of_string ldexp lnot log log10 max max_float max_int min min_float min_int mod_float modf nan neg_infinity not open_in open_in_bin open_in_gen open_out open_out_bin open_out_gen out_channel_length output output_binary_int output_byte output_char output_string output_value pos_in pos_out pred prerr_char prerr_endline prerr_float prerr_int prerr_newline prerr_string print_char print_endline print_float print_int print_newline print_string read_float read_int read_line really_input ref seek_in seek_out set_binary_mode_in set_binary_mode_out sin sinh snd sqrt stderr stdin stdout string_of_bool string_of_float string_of_format string_of_int succ tan tanh truncate unsafe_really_input valid_float_lexem" list_Flow_Control_Functions = Set.fromList $ words $ "exit failwith invalid_arg raise" list_Pervasive_Types = Set.fromList $ words $ "array bool char exn format4 fpclass in_channel int int32 int64 lazy_t list nativeint open_flag option out_channel real ref string unit" list_Pervasive_Variant_Tags = Set.fromList $ words $ "FP_infinite FP_nan FP_normal FP_subnormal FP_zero None Open_append Open_append Open_binary Open_binary Open_creat Open_creat Open_excl Open_excl Open_nonblock Open_nonblock Open_rdonly Open_rdonly Open_text Open_text Open_trunc Open_trunc Open_wronly Open_wronly Some" list_Pervasive_Exceptions = Set.fromList $ words $ "Assert_failure Division_by_zero End_of_file Exit Failure Invalid_argument Match_failure Not_found Out_of_memory Stack_overflow Sys_blocked_io Sys_error Undefined_recursive_module" list_Standard_Library_Modules = Set.fromList $ words $ "Arg Array ArrayLabels Buffer Callback Char Complex Digest Filename Format Gc Genlex Hashtbl Int32 Int64 Lazy Lexing List ListLabels Map Marshal MoreLabels Nativeint Oo Parsing Printexc Printf Queue Random Scanf Set Sort Stack StdLabels Stream String StringLabels Sys Weak" regex_'5c'28'5c'2a'5c'24'28T'7cQ'7cR'7c'3d'29 = compileRegex True "\\(\\*\\$(T|Q|R|=)" regex_'23'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'2e'2a'24 = compileRegex True "#`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*.*$" regex_'27'28'28'5c'5c'5bntbr'27'22'5c'5c'5d'7c'5c'5c'5b0'2d9'5d'7b3'7d'7c'5c'5cx'5b0'2d9A'2dFa'2df'5d'7b2'7d'29'7c'5b'5e'27'5d'29'27 = compileRegex True "'((\\\\[ntbr'\"\\\\]|\\\\[0-9]{3}|\\\\x[0-9A-Fa-f]{2})|[^'])'" regex_'3c'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'3c = compileRegex True "<:`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*<" regex_'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337'5f'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a = compileRegex True "[a-z\\300-\\326\\330-\\337_][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*" regex_'60'3f'5bA'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a = compileRegex True "`?[A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*" regex_'2d'3f0'5bxX'5d'5b0'2d9A'2dFa'2df'5f'5d'2b = compileRegex True "-?0[xX][0-9A-Fa-f_]+" regex_'2d'3f0'5boO'5d'5b0'2d7'5f'5d'2b = compileRegex True "-?0[oO][0-7_]+" regex_'2d'3f0'5bbB'5d'5b01'5f'5d'2b = compileRegex True "-?0[bB][01_]+" regex_'2d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'28'5c'2e'5b0'2d9'5d'5b0'2d9'5f'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'29'3f'7c'5beE'5d'5b'2d'2b'5d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'29 = compileRegex True "-?[0-9][0-9_]*(\\.[0-9][0-9_]*([eE][-+]?[0-9][0-9_]*)?|[eE][-+]?[0-9][0-9_]*)" regex_'2d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a = compileRegex True "-?[0-9][0-9_]*" regex_'28'5c'5c'5bntbr'27'22'5c'5c'5d'7c'5c'5c'5b0'2d9'5d'7b3'7d'7c'5c'5cx'5b0'2d9A'2dFa'2df'5d'7b2'7d'29 = compileRegex True "(\\\\[ntbr'\"\\\\]|\\\\[0-9]{3}|\\\\x[0-9A-Fa-f]{2})" regex_'5c'5c'24 = compileRegex True "\\\\$" regex_'5c'5c'28'5c'5c'7c'3e'3e'7c'3c'3c'29 = compileRegex True "\\\\(\\\\|>>|<<)" regex_'5c'5c'3c'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'3c = compileRegex True "\\\\<:`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*<" regex_'5c'5c'2e = compileRegex True "\\\\." regex_'5b'7b'5dv'28'5cs'7c'24'29 = compileRegex True "[{]v(\\s|$)" regex_'5b'7b'5db'28'5cs'7c'24'29 = compileRegex True "[{]b(\\s|$)" regex_'5b'7b'5di'28'5cs'7c'24'29 = compileRegex True "[{]i(\\s|$)" regex_'5b'7b'5de'28'5cs'7c'24'29 = compileRegex True "[{]e(\\s|$)" regex_'5b'7b'5d'5b0'2d9'5d'2b'28'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'29'3f'5cs = compileRegex True "[{][0-9]+(:`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*)?\\s" regex_'5b'7b'5d'5b'7b'5d'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'5b'7d'5d = compileRegex True "[{][{]:`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*[}]" regex_'5b'7b'5d'21'28'5ba'2dz'5d'2b'3a'29'3f = compileRegex True "[{]!([a-z]+:)?" regex_'5b'7b'5d'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'28'5cs'7c'24'29 = compileRegex True "[{]`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*(\\s|$)" regex_'40see'5cs'2a'28'3c'5b'5e'3e'5d'2a'3e'7c'22'5b'5e'22'5d'2a'22'7c'27'5b'5e'27'5d'2a'27'29 = compileRegex True "@see\\s*(<[^>]*>|\"[^\"]*\"|'[^']*')" regex_'40'28param'7craise'29'5cs'2a = compileRegex True "@(param|raise)\\s*" regex_'40'28author'7cdeprecated'7creturn'7csince'7cversion'29 = compileRegex True "@(author|deprecated|return|since|version)" regex_'40'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a = compileRegex True "@`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*" regex_'5b__'5d'2a'2d'5cs = compileRegex True "[ ]*-\\s" regex_'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'28'5c'2e'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'29'2a = compileRegex True "`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*(\\.`?[a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\377][a-z\\300-\\326\\330-\\337A-Z\\340-\\366\\370-\\3770-9_']*)*" parseRules ("Objective Caml","Code") = (((pDetectChar False '[' >>= withAttribute NormalTok) >>~ pushContext ("Objective Caml","Nested Code 1")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Objective Caml","Nested Code 2")) <|> ((pString False "(**)" >>= withAttribute CommentTok)) <|> ((pString False "(**" >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","Ocamldoc")) <|> ((pRegExpr regex_'5c'28'5c'2a'5c'24'28T'7cQ'7cR'7c'3d'29 >>= withAttribute NormalTok) >>~ pushContext ("Objective Caml","qtest header")) <|> ((pDetect2Chars False '(' '*' >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","Comment")) <|> ((pFirstNonSpace >> pRegExpr regex_'23'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'2e'2a'24 >>= withAttribute OtherTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Objective Caml","String")) <|> ((pRegExpr regex_'27'28'28'5c'5c'5bntbr'27'22'5c'5c'5d'7c'5c'5c'5b0'2d9'5d'7b3'7d'7c'5c'5cx'5b0'2d9A'2dFa'2df'5d'7b2'7d'29'7c'5b'5e'27'5d'29'27 >>= withAttribute CharTok)) <|> ((pDetect2Chars False '<' '<' >>= withAttribute StringTok) >>~ pushContext ("Objective Caml","Camlp4 Quotation")) <|> ((pRegExpr regex_'3c'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'3c >>= withAttribute StringTok) >>~ pushContext ("Objective Caml","Camlp4 Quotation")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Revised_Syntax_Keywords >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Flow_Control_Functions >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Pervasive_Functions >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Pervasive_Types >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Pervasive_Exceptions >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Pervasive_Variant_Tags >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_Standard_Library_Modules >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337'5f'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'60'3f'5bA'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'2d'3f0'5bxX'5d'5b0'2d9A'2dFa'2df'5f'5d'2b >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'2d'3f0'5boO'5d'5b0'2d7'5f'5d'2b >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'2d'3f0'5bbB'5d'5b01'5f'5d'2b >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'2d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'28'5c'2e'5b0'2d9'5d'5b0'2d9'5f'5d'2a'28'5beE'5d'5b'2d'2b'5d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'29'3f'7c'5beE'5d'5b'2d'2b'5d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'29 >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'2d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a >>= withAttribute DecValTok)) <|> ((parseRules ("Objective Caml","Unmatched Closing Brackets"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Code")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","Nested Code 1") = (((pDetectChar False ']' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","Code"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Nested Code 1")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","Nested Code 2") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","Code"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Nested Code 2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","String") = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'28'5c'5c'5bntbr'27'22'5c'5c'5d'7c'5c'5c'5b0'2d9'5d'7b3'7d'7c'5c'5cx'5b0'2d9A'2dFa'2df'5d'7b2'7d'29 >>= withAttribute CharTok)) <|> ((pRegExpr regex_'5c'5c'24 >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("Objective Caml","qtest header") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_qtest_keywords >>= withAttribute KeywordTok)) <|> ((pDetectChar False '&' >>= withAttribute NormalTok) >>~ pushContext ("Objective Caml","qtest param")) <|> ((pRegExpr regex_'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337'5f'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","qtest header")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","qtest param") = (currentContext >>= \x -> guard (x == ("Objective Caml","qtest param")) >> pDefault >>= withAttribute NormalTok) parseRules ("Objective Caml","qtest") = (((pDetect2Chars False '*' ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","Code"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","qtest")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","Comment") = (((pDetect2Chars False '*' ')' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pDetect2Chars False '(' '*' >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","Comment")) <|> ((pDetectChar False '"' >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","String in Comment")) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","String in Comment") = (((pDetectChar False '"' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","String"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","String in Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Camlp4 Quotation") = (((pDetect2Chars False '>' '>' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetect2Chars False '<' '<' >>= withAttribute StringTok) >>~ pushContext ("Objective Caml","Camlp4 Quotation")) <|> ((pRegExpr regex_'3c'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'3c >>= withAttribute StringTok) >>~ pushContext ("Objective Caml","Camlp4 Quotation")) <|> ((pRegExpr regex_'5c'5c'28'5c'5c'7c'3e'3e'7c'3c'3c'29 >>= withAttribute CharTok)) <|> ((pRegExpr regex_'5c'5c'3c'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'3c >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Camlp4 Quotation")) >> pDefault >>= withAttribute StringTok)) parseRules ("Objective Caml","Ocamldoc") = (((pDetect2Chars False '*' ')' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute CharTok)) <|> ((pString False "(**)" >>= withAttribute CommentTok)) <|> ((pString False "(**" >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","Ocamldoc")) <|> ((pDetect2Chars False '(' '*' >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","Comment")) <|> ((pDetectChar False '"' >>= withAttribute CommentTok) >>~ pushContext ("Objective Caml","String in Comment")) <|> ((pDetectChar False '[' >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Code")) <|> ((pDetect2Chars False '{' '[' >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Preformatted")) <|> ((pDetect2Chars False '{' '%' >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc LaTeX")) <|> ((pDetect2Chars False '{' '^' >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Nested Ocamldoc")) <|> ((pRegExpr regex_'5b'7b'5dv'28'5cs'7c'24'29 >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Verbatim")) <|> ((pRegExpr regex_'5b'7b'5db'28'5cs'7c'24'29 >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Bold")) <|> ((pRegExpr regex_'5b'7b'5di'28'5cs'7c'24'29 >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Italic")) <|> ((pRegExpr regex_'5b'7b'5de'28'5cs'7c'24'29 >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Emphasised")) <|> ((pRegExpr regex_'5b'7b'5d'5b0'2d9'5d'2b'28'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'29'3f'5cs >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Heading")) <|> ((pRegExpr regex_'5b'7b'5d'5b'7b'5d'3a'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'5b'7d'5d >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Link")) <|> ((pRegExpr regex_'5b'7b'5d'21'28'5ba'2dz'5d'2b'3a'29'3f >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc References")) <|> ((pRegExpr regex_'5b'7b'5d'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'28'5cs'7c'24'29 >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Nested Ocamldoc")) <|> ((pRegExpr regex_'40see'5cs'2a'28'3c'5b'5e'3e'5d'2a'3e'7c'22'5b'5e'22'5d'2a'22'7c'27'5b'5e'27'5d'2a'27'29 >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'40'28param'7craise'29'5cs'2a >>= withAttribute OtherTok) >>~ pushContext ("Objective Caml","Ocamldoc Identifier")) <|> ((pRegExpr regex_'40'28author'7cdeprecated'7creturn'7csince'7cversion'29 >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'40'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a >>= withAttribute OtherTok)) <|> ((pColumn 0 >> pRegExpr regex_'5b__'5d'2a'2d'5cs >>= withAttribute OtherTok)) <|> ((parseRules ("Objective Caml","Unmatched Closing Brackets"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc Code") = (((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","Code"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Code")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","Ocamldoc Preformatted") = (((pDetect2Chars False ']' '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","Code"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Preformatted")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","Ocamldoc Verbatim") = (((pDetect2Chars False 'v' '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Verbatim")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc LaTeX") = (((pDetect2Chars False '%' '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Latex.parseExpression (Just ("LaTeX","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc LaTeX")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc Identifier") = (((pRegExpr regex_'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'28'5c'2e'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'29'2a >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '*' ')' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetectSpaces >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Identifier")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Objective Caml","Nested Ocamldoc") = (((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pDetect2Chars False '*' ')' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((parseRules ("Objective Caml","Ocamldoc"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Nested Ocamldoc")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Objective Caml","Ocamldoc Bold") = (((parseRules ("Objective Caml","Nested Ocamldoc"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Bold")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc Italic") = (((parseRules ("Objective Caml","Nested Ocamldoc"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Italic")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc Emphasised") = (((parseRules ("Objective Caml","Nested Ocamldoc"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Emphasised")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc Heading") = (((parseRules ("Objective Caml","Nested Ocamldoc"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Heading")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc Link") = (((parseRules ("Objective Caml","Nested Ocamldoc"))) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc Link")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Objective Caml","Ocamldoc References") = (((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pDetect2Chars False '*' ')' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pRegExpr regex_'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'28'5c'2e'60'3f'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c377'5d'5ba'2dz'5c300'2d'5c326'5c330'2d'5c337A'2dZ'5c340'2d'5c366'5c370'2d'5c3770'2d9'5f'27'5d'2a'29'2a >>= withAttribute CommentTok)) <|> ((pDetectSpaces >>= withAttribute OtherTok)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Ocamldoc References")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Objective Caml","Unmatched Closing Brackets") = (((pDetect2Chars False '*' ')' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetect2Chars False 'v' '}' >>= withAttribute ErrorTok)) <|> ((pDetect2Chars False ']' '}' >>= withAttribute ErrorTok)) <|> ((pDetect2Chars False '%' '}' >>= withAttribute ErrorTok)) <|> ((pDetectChar False ']' >>= withAttribute ErrorTok)) <|> ((pDetectChar False '}' >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("Objective Caml","Unmatched Closing Brackets")) >> pDefault >>= withAttribute NormalTok)) parseRules ("LaTeX", _) = Text.Highlighting.Kate.Syntax.Latex.parseExpression Nothing parseRules x = parseRules ("Objective Caml","Code") <|> fail ("Unknown context" ++ show x)