{- This module was generated from data in the Kate syntax highlighting file prolog.xml, version 1.3, by Torsten Eichstädt (torsten.eichstaedt@web.de) -} module Text.Highlighting.Kate.Syntax.Prolog (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert_indent 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 = "Prolog" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.prolog;*.dcg;*.pro" -- | 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 = [("Prolog","shebang")], 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 } ("Prolog","shebang") -> pushContext ("Prolog","clause") >> return () ("Prolog","syntax_error") -> return () ("Prolog","clause") -> return () ("Prolog","term") -> return () ("Prolog","nested") -> return () ("Prolog","list") -> return () ("Prolog","curly") -> return () ("Prolog","arith_expr") -> return () ("Prolog","nested_expr") -> return () ("Prolog","list_functor") -> pushContext ("Prolog","syntax_error") >> return () ("Prolog","sq") -> return () ("Prolog","dq") -> return () ("Prolog","bq") -> return () ("Prolog","single-quoted") -> return () ("Prolog","double-quoted") -> return () ("Prolog","back-quoted") -> return () ("Prolog","syntax_error_sq") -> return () ("Prolog","syntax_error_dq") -> return () ("Prolog","syntax_error_bq") -> return () ("Prolog","char_code") -> (popContext) >> pEndLine ("Prolog","syntax_error_cc") -> return () ("Prolog","esc_seq_q") -> pushContext ("Prolog","syntax_error") >> return () ("Prolog","esc_seq_cc") -> (popContext >> popContext) >> pEndLine ("Prolog","esc_seq_q2") -> pushContext ("Prolog","syntax_error") >> return () ("Prolog","id") -> return () ("Prolog","var") -> return () ("Prolog","graphic") -> (popContext) >> pEndLine ("Prolog","bin") -> (popContext) >> pEndLine ("Prolog","oct") -> (popContext) >> pEndLine ("Prolog","hex") -> (popContext) >> pEndLine ("Prolog","comment-iso") -> return () ("Prolog","1-comment") -> (popContext) >> pEndLine ("Prolog","region_marker") -> (popContext) >> pEndLine ("Prolog","layout_fold") -> return () ("Prolog","quoted_1st") -> return () ("Prolog","quoted_last") -> return () ("Prolog","layout") -> return () ("Prolog","atomic") -> return () ("Prolog","arith_expr_common") -> return () ("Prolog","number") -> (popContext) >> pEndLine ("Prolog","operator") -> (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_error_term_ISO = Set.fromList $ words $ "error" list_guru_meditation_terms_ISO = Set.fromList $ words $ "instantiation_error uninstantiation_error type_error domain_error existence_error permission_error representation_error evaluation_error resource_error syntax_error system_error" list_bogus_ISO = Set.fromList $ words $ "char_conversion current_char_conversion include ensure_loaded atan xor" list_directives_non'2dISO = Set.fromList $ words $ "consult built_in" list_logic'2bcontrol_ISO = Set.fromList $ words $ "initialization fail repeat call catch throw true false once" list_dyn_clause_mgmt_ISO = Set.fromList $ words $ "dynamic asserta assertz retractall retract abolish clause" list_listing_non'2dISO = Set.fromList $ words $ "listing" list_terms_ISO = Set.fromList $ words $ "atom_concat atom_length atom_chars atom_codes arg subsumes_term acyclic_term char_code compare copy_term functor number_chars number_codes term_variables unify_with_occurs_check" list_terms_non'2dISO = Set.fromList $ words $ "number_atom expand_term term_expansion display print format portray_clause portray term_expansion" list_DCG_non'2dISO = Set.fromList $ words $ "phrase" list_lists_ISO = Set.fromList $ words $ "sort keysort" list_lists_non'2dISO = Set.fromList $ words $ "append delete length last map_list min_list maplist msort memberchk member nth permutation reverse select prefix suffix sublist sum_list" list_streams_ISO = Set.fromList $ words $ "open set_stream_position get_char get_code peek_char peek_code get_byte peek_byte put_char put_code put_byte nl read_term read write_canonical writeq write" list_streams_deprecated = Set.fromList $ words $ "append seeing seen see telling tell told get0 get skip put tab" list_arith_eval_ISO = Set.fromList $ words $ "is" list_arith_ops_int_ISO = Set.fromList $ words $ "rem mod div" list_arith_expr_mixed_ISO = Set.fromList $ words $ "abs sign min max" list_arith_expr_int_ISO = Set.fromList $ words $ "ceiling floor round truncate" list_arith_expr_float_ISO = Set.fromList $ words $ "pi sqrt tan cos sin atan2 acos asin exp log float float_fractional_part float_integer_part" list_prolog_state_ISO = Set.fromList $ words $ "multifile discontigous op set_prolog_flag" list_types_ISO = Set.fromList $ words $ "var nonvar atom integer float number atomic compound callable ground" list_list'2bis'5flist_non'2dISO = Set.fromList $ words $ "list is_list" list_built'2dins_ISO = Set.fromList $ words $ "current_op current_prolog_flag current_input current_output set_input set_output close flush_output at_end_of_stream stream_property" regex_'2e = compileRegex True "." regex_'5c'2e'28'3f'21'28'5c'28'7c'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29'29 = compileRegex True "\\.(?!(\\(|[#$&*+\\-./:<=>?@^~\\\\]))" regex_'28'3b'7c'2d'3e'7c'5c'5c'5c'2b'7c'3a'2d'7c'3d'7c'5c'5c'3d'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "(;|->|\\\\\\+|:-|=|\\\\=)(?![#$&*+\\-./:<=>?@^~\\\\])" regex_'28'27'27'7c'5c'5c'5b0'2d7'5d'2b'5c'5c'7c'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c'7c'5c'5c'2e'7c'5b'5e'27'5c'5c'5d'2b'29'24 = compileRegex True "(''|\\\\[0-7]+\\\\|\\\\x[a-fA-F0-9]+\\\\|\\\\.|[^'\\\\]+)$" regex_'28'22'22'7c'5c'5c'5b0'2d7'5d'2b'5c'5c'7c'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c'7c'5c'5c'2e'7c'5b'5e'22'5c'5c'5d'2b'29'24 = compileRegex True "(\"\"|\\\\[0-7]+\\\\|\\\\x[a-fA-F0-9]+\\\\|\\\\.|[^\"\\\\]+)$" regex_'28'60'60'7c'5c'5c'5b0'2d7'5d'2b'5c'5c'7c'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c'7c'5c'5c'2e'7c'5b'5e'60'5c'5c'5d'2b'29'24 = compileRegex True "(``|\\\\[0-7]+\\\\|\\\\x[a-fA-F0-9]+\\\\|\\\\.|[^`\\\\]+)$" regex_'27'24 = compileRegex True "'$" regex_'22'24 = compileRegex True "\"$" regex_'60'24 = compileRegex True "`$" regex_'5c'5c'5b0'2d7'5d'2b'5c'5c = compileRegex True "\\\\[0-7]+\\\\" regex_'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c = compileRegex True "\\\\x[a-fA-F0-9]+\\\\" regex_'28'3d'3a'3d'7c'3d'5c'5c'3d'7c'3d'3c'7c'3c'7c'3e'3d'7c'3e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "(=:=|=\\\\=|=<|<|>=|>)(?![#$&*+\\-./:<=>?@^~\\\\])" regex_'28'5c'2b'7c'2d'7c'5c'2a'7c'5c'5e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "(\\+|-|\\*|\\^)(?![#$&*+\\-./:<=>?@^~\\\\])" regex_'2f'2f'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "//(?![#$&*+\\-./:<=>?@^~\\\\])" regex_'28'2f'7c'5c'2a'5c'2a'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "(/|\\*\\*)(?![#$&*+\\-./:<=>?@^~\\\\])" regex_'28'2f'5c'5c'7c'5c'5c'2f'7c'5c'5c'7c'3c'3c'7c'3e'3e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "(/\\\\|\\\\/|\\\\|<<|>>)(?![#$&*+\\-./:<=>?@^~\\\\])" regex_0'27'5c'5c'3f'24 = compileRegex True "0'\\\\?$" regex_'5b0'2d9'5d'2b'5c'2e'5b0'2d9'5d'2bE'5b'2b'5c'2d'5d'3f'5b0'2d9'5d'2b = compileRegex True "[0-9]+\\.[0-9]+E[+\\-]?[0-9]+" regex_'5b0'2d9'5d'2b'5c'2e'5b0'2d9'5d'2b = compileRegex True "[0-9]+\\.[0-9]+" regex_'5b0'2d9'5d'2bE'5b'2b'5c'2d'5d'3f'5b0'2d9'5d'2b = compileRegex True "[0-9]+E[+\\-]?[0-9]+" regex_'28'5c'3f'2d'7c'3d'3d'7c'5c'5c'3d'3d'7c'40'3d'3c'7c'40'3c'7c'40'3e'3d'7c'40'3e'7c'3d'5c'2e'5c'2e'7c'40'7c'3a'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "(\\?-|==|\\\\==|@=<|@<|@>=|@>|=\\.\\.|@|:)(?![#$&*+\\-./:<=>?@^~\\\\])" regex_'2d'2d'3e'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 = compileRegex True "-->(?![#$&*+\\-./:<=>?@^~\\\\])" parseRules ("Prolog","shebang") = (((pColumn 0 >> pDetect2Chars False '#' '!' >>= withAttribute CommentTok) >>~ pushContext ("Prolog","1-comment")) <|> ((lookAhead (pRegExpr regex_'2e) >> pushContext ("Prolog","clause") >> currentContext >>= parseRules)) <|> (currentContext >>= \x -> guard (x == ("Prolog","shebang")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","syntax_error") = (((pDetectSpaces >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetectIdentifier >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute ErrorTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Prolog","syntax_error")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","clause") = (((parseRules ("Prolog","layout"))) <|> ((pRegExpr regex_'5c'2e'28'3f'21'28'5c'28'7c'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29'29 >>= withAttribute AlertTok)) <|> ((lookAhead (pRegExpr regex_'2e) >> pushContext ("Prolog","term") >> currentContext >>= parseRules)) <|> (currentContext >>= \x -> guard (x == ("Prolog","clause")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","term") = (((parseRules ("Prolog","layout"))) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","nested")) <|> ((pDetectChar False '[' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","list")) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("Prolog","curly")) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '!' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '|' >>= withAttribute NormalTok)) <|> ((lookAhead (pDetect2Chars False '.' '(') >> pushContext ("Prolog","list_functor") >> currentContext >>= parseRules)) <|> ((pRegExpr regex_'5c'2e'28'3f'21'28'5c'28'7c'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29'29 >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((parseRules ("Prolog","atomic"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","term")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","nested") = (((parseRules ("Prolog","layout"))) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","nested")) <|> ((pDetectChar False '[' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","list")) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("Prolog","curly")) <|> ((pDetectChar False '!' >>= withAttribute KeywordTok)) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '|' >>= withAttribute NormalTok)) <|> ((lookAhead (pDetect2Chars False '.' '(') >> pushContext ("Prolog","list_functor") >> currentContext >>= parseRules)) <|> ((pRegExpr regex_'5c'2e'28'3f'21'28'5c'28'7c'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29'29 >>= withAttribute AlertTok)) <|> ((parseRules ("Prolog","atomic"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","nested")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","list") = (((parseRules ("Prolog","layout"))) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","nested")) <|> ((pDetectChar False ']' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '[' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","list")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","curly")) <|> ((pDetectChar False ',' >>= withAttribute NormalTok)) <|> ((pDetectChar False '!' >>= withAttribute NormalTok)) <|> ((pDetectChar False '|' >>= withAttribute FunctionTok)) <|> ((lookAhead (pDetect2Chars False '.' '(') >> pushContext ("Prolog","list_functor") >> currentContext >>= parseRules)) <|> ((parseRules ("Prolog","atomic"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","list")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","curly") = (((parseRules ("Prolog","layout"))) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","nested")) <|> ((pDetectChar False '[' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","list")) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("Prolog","curly")) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '!' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '|' >>= withAttribute NormalTok)) <|> ((lookAhead (pDetect2Chars False '.' '(') >> pushContext ("Prolog","list_functor") >> currentContext >>= parseRules)) <|> ((parseRules ("Prolog","atomic"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","curly")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","arith_expr") = (((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","nested_expr")) <|> ((lookAhead (pDetectChar False ')') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False '}') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False ']') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False '!') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False ',') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False '|') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pRegExpr regex_'5c'2e'28'3f'21'28'5c'28'7c'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29'29) >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pRegExpr regex_'28'3b'7c'2d'3e'7c'5c'5c'5c'2b'7c'3a'2d'7c'3d'7c'5c'5c'3d'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29) >> (popContext) >> currentContext >>= parseRules)) <|> ((parseRules ("Prolog","arith_expr_common"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","arith_expr")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","nested_expr") = (((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","nested_expr")) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '!' >>= withAttribute NormalTok)) <|> ((pDetectChar False ',' >>= withAttribute ErrorTok)) <|> ((pDetectChar False '|' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'3b'7c'2d'3e'7c'5c'5c'5c'2b'7c'3a'2d'7c'3d'7c'5c'5c'3d'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute FunctionTok)) <|> ((parseRules ("Prolog","arith_expr_common"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","nested_expr")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","list_functor") = (((pDetectChar False '.' >>= withAttribute FunctionTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Prolog","list_functor")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","sq") = (((parseRules ("Prolog","quoted_1st"))) <|> ((pRegExpr regex_'28'27'27'7c'5c'5c'5b0'2d7'5d'2b'5c'5c'7c'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c'7c'5c'5c'2e'7c'5b'5e'27'5c'5c'5d'2b'29'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","syntax_error_sq")) <|> ((pDetect2Chars False '\'' '\'' >>= withAttribute CharTok)) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((parseRules ("Prolog","quoted_last"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","sq")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Prolog","dq") = (((parseRules ("Prolog","quoted_1st"))) <|> ((pRegExpr regex_'28'22'22'7c'5c'5c'5b0'2d7'5d'2b'5c'5c'7c'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c'7c'5c'5c'2e'7c'5b'5e'22'5c'5c'5d'2b'29'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","syntax_error_dq")) <|> ((pDetect2Chars False '"' '"' >>= withAttribute CharTok)) <|> ((pDetectChar False '"' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((parseRules ("Prolog","quoted_last"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","dq")) >> pDefault >>= withAttribute OtherTok)) parseRules ("Prolog","bq") = (((parseRules ("Prolog","quoted_1st"))) <|> ((pRegExpr regex_'28'60'60'7c'5c'5c'5b0'2d7'5d'2b'5c'5c'7c'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c'7c'5c'5c'2e'7c'5b'5e'60'5c'5c'5d'2b'29'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","syntax_error_bq")) <|> ((pDetect2Chars False '`' '`' >>= withAttribute CharTok)) <|> ((pDetectChar False '`' >>= withAttribute StringTok) >>~ (popContext >> popContext)) <|> ((parseRules ("Prolog","quoted_last"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","bq")) >> pDefault >>= withAttribute StringTok)) parseRules ("Prolog","single-quoted") = (((pRegExpr regex_'27'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","sq")) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("Prolog","sq")) <|> (currentContext >>= \x -> guard (x == ("Prolog","single-quoted")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Prolog","double-quoted") = (((pRegExpr regex_'22'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","dq")) <|> ((pDetectChar False '"' >>= withAttribute OtherTok) >>~ pushContext ("Prolog","dq")) <|> (currentContext >>= \x -> guard (x == ("Prolog","double-quoted")) >> pDefault >>= withAttribute OtherTok)) parseRules ("Prolog","back-quoted") = (((pRegExpr regex_'60'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","bq")) <|> ((pDetectChar False '`' >>= withAttribute StringTok) >>~ pushContext ("Prolog","bq")) <|> (currentContext >>= \x -> guard (x == ("Prolog","back-quoted")) >> pDefault >>= withAttribute StringTok)) parseRules ("Prolog","syntax_error_sq") = (((pDetect2Chars False '\\' '\'' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetect2Chars False '\'' '\'' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetectChar False '\'' >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules ("Prolog","syntax_error"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","syntax_error_sq")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","syntax_error_dq") = (((pDetect2Chars False '\\' '"' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetect2Chars False '"' '"' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetectChar False '"' >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules ("Prolog","syntax_error"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","syntax_error_dq")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","syntax_error_bq") = (((pDetect2Chars False '\\' '`' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetect2Chars False '`' '`' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetectChar False '`' >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules ("Prolog","syntax_error"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","syntax_error_bq")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","char_code") = (((pDetect2Chars False '\'' '\'' >>= withAttribute CharTok) >>~ (popContext)) <|> ((pDetectChar False '\'' >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pDetectChar False '\\' >>= withAttribute CharTok) >>~ pushContext ("Prolog","esc_seq_cc")) <|> ((pDetectChar False ' ' >>= withAttribute AlertTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute BaseNTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Prolog","char_code")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","syntax_error_cc") = (((pDetectSpaces >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","esc_seq_q") = (((pRegExpr regex_'5c'5c'5b0'2d7'5d'2b'5c'5c >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5cx'5ba'2dfA'2dF0'2d9'5d'2b'5c'5c >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pDetectChar False '\\' >>= withAttribute CharTok) >>~ pushContext ("Prolog","esc_seq_q2")) <|> (currentContext >>= \x -> guard (x == ("Prolog","esc_seq_q")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","esc_seq_cc") = (((pDetectChar False ' ' >>= withAttribute AlertTok) >>~ (popContext >> popContext)) <|> ((pAnyChar "abfnrtv\\'`\"]" >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","esc_seq_q2") = (((pDetectChar False ' ' >>= withAttribute AlertTok) >>~ (popContext >> popContext)) <|> ((pAnyChar "abfnrtv\\'`\"]" >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","id") = (((pDetectIdentifier >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Prolog","id")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","var") = (((pDetectIdentifier >>= withAttribute DataTypeTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Prolog","var")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","graphic") = (((pAnyChar "#$&*+-./:<=>?@^~\\" >>= withAttribute NormalTok)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","bin") = (((pAnyChar "01" >>= withAttribute BaseNTok)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","oct") = (((pAnyChar "01234567" >>= withAttribute BaseNTok)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","hex") = (((pAnyChar "0123456789abcdefABCDEF" >>= withAttribute BaseNTok)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","comment-iso") = (((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pDetectSpaces >>= withAttribute CommentTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert_indent.parseExpression (Just ("Alerts_indent","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Prolog","comment-iso")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Prolog","1-comment") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert_indent.parseExpression (Just ("Alerts_indent","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Prolog","1-comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Prolog","region_marker") = (((parseRules ("Prolog","1-comment"))) <|> (currentContext >>= \x -> guard (x == ("Prolog","region_marker")) >> pDefault >>= withAttribute RegionMarkerTok)) parseRules ("Prolog","layout_fold") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pFirstNonSpace >> pString False "%BEGIN" >>= withAttribute RegionMarkerTok) >>~ pushContext ("Prolog","region_marker")) <|> ((pFirstNonSpace >> pString False "%END" >>= withAttribute RegionMarkerTok) >>~ pushContext ("Prolog","region_marker")) <|> ((pFirstNonSpace >> pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("Prolog","1-comment")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Prolog","quoted_1st") = (((pLineContinue >>= withAttribute CharTok)) <|> ((pColumn 0 >> pDetectSpaces >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("Prolog","quoted_1st")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","quoted_last") = (((lookAhead (pDetectChar False '\\') >> pushContext ("Prolog","esc_seq_q") >> currentContext >>= parseRules)) <|> ((pDetectChar False ' ' >>= withAttribute AlertTok)) <|> ((pDetectIdentifier >>= withAttribute ErrorTok)) <|> ((pDetectSpaces >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("Prolog","quoted_last")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","layout") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("Prolog","comment-iso")) <|> ((pFirstNonSpace >> pString False "%BEGIN" >>= withAttribute RegionMarkerTok) >>~ pushContext ("Prolog","region_marker")) <|> ((pFirstNonSpace >> pString False "%END" >>= withAttribute RegionMarkerTok) >>~ pushContext ("Prolog","region_marker")) <|> ((pFirstNonSpace >> lookAhead (pDetectChar False '%') >> pushContext ("Prolog","layout_fold") >> currentContext >>= parseRules)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("Prolog","1-comment")) <|> (currentContext >>= \x -> guard (x == ("Prolog","layout")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","atomic") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_logic'2bcontrol_ISO >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_types_ISO >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_dyn_clause_mgmt_ISO >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_streams_ISO >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_terms_ISO >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_prolog_state_ISO >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_DCG_non'2dISO >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_eval_ISO >>= withAttribute DataTypeTok) >>~ pushContext ("Prolog","arith_expr")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_built'2dins_ISO >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_error_term_ISO >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_guru_meditation_terms_ISO >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_bogus_ISO >>= withAttribute AlertTok)) <|> ((parseRules ("Prolog","number"))) <|> ((lookAhead (pDetectChar False '\'') >> pushContext ("Prolog","single-quoted") >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False '`') >> pushContext ("Prolog","back-quoted") >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False '"') >> pushContext ("Prolog","double-quoted") >> currentContext >>= parseRules)) <|> ((parseRules ("Prolog","operator"))) <|> ((lookAhead (pAnyChar "abcdefghijklmnopqrstuvwxyz") >> pushContext ("Prolog","id") >> currentContext >>= parseRules)) <|> ((lookAhead (pAnyChar "ABCDEFGHIJKLMNOPQRSTUVWXYZ_") >> pushContext ("Prolog","var") >> currentContext >>= parseRules)) <|> ((pAnyChar "#$&*+-./:<=>?@^~\\" >>= withAttribute NormalTok) >>~ pushContext ("Prolog","graphic")) <|> (currentContext >>= \x -> guard (x == ("Prolog","atomic")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","arith_expr_common") = (((parseRules ("Prolog","layout"))) <|> ((parseRules ("Prolog","number"))) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_eval_ISO >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_bogus_ISO >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_expr_mixed_ISO >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_expr_int_ISO >>= withAttribute DecValTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_expr_float_ISO >>= withAttribute FloatTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_ops_int_ISO >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'28'3d'3a'3d'7c'3d'5c'5c'3d'7c'3d'3c'7c'3c'7c'3e'3d'7c'3e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute ErrorTok) >>~ (popContext)) <|> ((pRegExpr regex_'28'5c'2b'7c'2d'7c'5c'2a'7c'5c'5e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'2f'2f'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'28'2f'7c'5c'2a'5c'2a'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'28'2f'5c'5c'7c'5c'5c'2f'7c'5c'5c'7c'3c'3c'7c'3e'3e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute NormalTok)) <|> ((parseRules ("Prolog","operator"))) <|> ((lookAhead (pAnyChar "abcdefghijklmnopqrstuvwxyz") >> pushContext ("Prolog","id") >> currentContext >>= parseRules)) <|> ((lookAhead (pAnyChar "ABCDEFGHIJKLMNOPQRSTUVWXYZ_") >> pushContext ("Prolog","var") >> currentContext >>= parseRules)) <|> ((pAnyChar "#$&*+-./:<=>?@^~\\" >>= withAttribute NormalTok) >>~ pushContext ("Prolog","graphic")) <|> (currentContext >>= \x -> guard (x == ("Prolog","arith_expr_common")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","number") = (((pRegExpr regex_0'27'5c'5c'3f'24 >>= withAttribute ErrorTok) >>~ pushContext ("Prolog","syntax_error_cc")) <|> ((pDetect2Chars False '0' '\'' >>= withAttribute BaseNTok) >>~ pushContext ("Prolog","char_code")) <|> ((pDetect2Chars False '0' 'b' >>= withAttribute BaseNTok) >>~ pushContext ("Prolog","bin")) <|> ((pDetect2Chars False '0' 'o' >>= withAttribute BaseNTok) >>~ pushContext ("Prolog","oct")) <|> ((pDetect2Chars False '0' 'x' >>= withAttribute BaseNTok) >>~ pushContext ("Prolog","hex")) <|> ((pRegExpr regex_'5b0'2d9'5d'2b'5c'2e'5b0'2d9'5d'2bE'5b'2b'5c'2d'5d'3f'5b0'2d9'5d'2b >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5b0'2d9'5d'2b'5c'2e'5b0'2d9'5d'2b >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5b0'2d9'5d'2bE'5b'2b'5c'2d'5d'3f'5b0'2d9'5d'2b >>= withAttribute FloatTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> (currentContext >>= \x -> guard (x == ("Prolog","number")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Prolog","operator") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_eval_ISO >>= withAttribute DataTypeTok) >>~ pushContext ("Prolog","arith_expr")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\$#'\"`" list_arith_ops_int_ISO >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'28'3b'7c'2d'3e'7c'5c'5c'5c'2b'7c'3a'2d'7c'3d'7c'5c'5c'3d'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28'5c'3f'2d'7c'3d'3d'7c'5c'5c'3d'3d'7c'40'3d'3c'7c'40'3c'7c'40'3e'3d'7c'40'3e'7c'3d'5c'2e'5c'2e'7c'40'7c'3a'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'2d'2d'3e'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28'3d'3a'3d'7c'3d'5c'5c'3d'7c'3d'3c'7c'3c'7c'3e'3d'7c'3e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute DataTypeTok) >>~ pushContext ("Prolog","arith_expr")) <|> ((pRegExpr regex_'28'5c'2b'7c'2d'7c'5c'2a'7c'5c'5e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'2f'2f'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'28'2f'7c'5c'2a'5c'2a'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'28'2f'5c'5c'7c'5c'5c'2f'7c'5c'5c'7c'3c'3c'7c'3e'3e'29'28'3f'21'5b'23'24'26'2a'2b'5c'2d'2e'2f'3a'3c'3d'3e'3f'40'5e'7e'5c'5c'5d'29 >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Prolog","operator")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Alerts_indent", _) = Text.Highlighting.Kate.Syntax.Alert_indent.parseExpression Nothing parseRules x = parseRules ("Prolog","shebang") <|> fail ("Unknown context" ++ show x)