{- This module was generated from data in the Kate syntax highlighting file fortran.xml, version 1.11, by Franchin Matteo (fnch@libero.it) -} module Text.Highlighting.Kate.Syntax.Fortran ( 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 = "Fortran" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.f;*.F;*.for;*.FOR;*.f90;*.F90;*.fpp;*.FPP;*.f95;*.F95;" -- | 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 = "Fortran" } context <- currentContext <|> (pushContext "default" >> 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 [("Fortran",["default"])], synStLanguage = "Fortran", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = False, synStKeywordCaseSensitive = False, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do newline <|> (eof >> return '\n') context <- currentContext case context of "default" -> return () "find_preprocessor" -> return () "find_op_and_log" -> return () "find_comments" -> return () "find_symbols" -> return () "inside_func_paren" -> return () "find_io_stmnts" -> return () "find_io_paren" -> return () "format_stmnt" -> return () "find_begin_stmnts" -> return () "find_end_stmnts" -> return () "find_decls" -> return () "find_paren" -> (popContext >> return ()) "find_intrinsics" -> return () "find_numbers" -> return () "find_strings" -> return () "string_1" -> return () "string_2" -> return () "end_of_string" -> 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"),("Data Type","dt"),("Decimal","dv"),("Float","fl"),("String","st"),("Comment","co"),("Preprocessor","ot"),("Operator","kw"),("Logical","ot"),("IO Function","fu"),("Elemental Procedure","kw"),("Inquiry Function","fu"),("Transformational Function","fu"),("Non elemental subroutine","kw")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) list_keywords = Set.fromList $ words $ "allocate break call case common contains continue cycle deallocate default do forall where elsewhere elseif else equivalence exit external for go goto if implicit include interface intrinsic namelist none nullify operator assignment pause procedure pure elemental record recursive result return select selectcase stop then to use only entry while" list_io'5ffunctions = Set.fromList $ words $ "access backspace close inquire open print read rewind write format" list_io'5fkeywords = Set.fromList $ words $ "unit end err fmt iostat status advance size eor" list_open'5fkeywords = Set.fromList $ words $ "unit iostat err file status access form recl blank position action delim pad" list_inquire'5fkeywords = Set.fromList $ words $ "unit iostat err file exist opened number named name access sequential direct form formatted unformatted recl nextrec blank position action read write readwrite delim pad" list_types = Set.fromList $ words $ "double precision parameter save pointer public private target allocatable optional sequence" list_elemental'5fprocs = Set.fromList $ words $ "abs cabs dabs iabs aimag aint dint anint dnint ceiling cmplx dcmplx dimag floor nint idnint int idint ifix real float sngl dble dreal aprime dconjg dfloat ddmim rand modulo conjg dprod dim ddim idim max amax0 amax1 max0 max1 dmax1 min amin0 amin1 min0 min1 dmin1 mod amod dmod sign dsign isign acos dacos asin dasin atan datan atan2 datan2 cos ccos dcos cosh dcosh exp cexp dexp log alog dlog clog log10 alog10 dlog10 sin csin dsin sinh dsinh sqrt csqrt dsqrt tan dtan tanh dtanh achar char iachar ichar lge lgt lle llt adjustl adjustr index len_trim scan verify logical exponent fraction nearest rrspacing scale set_exponent spacing btest iand ibclr ibits ibset ieor ior ishft ishftc not mvbits merge" list_inquiry'5ffn = Set.fromList $ words $ "associated present kind len digits epsilon huge maxexponent minexponent precision radix range tiny bit_size allocated lbound ubound shape size" list_transform'5ffn = Set.fromList $ words $ "repeat trim selected_int_kind selected_real_kind transfer dot_product matmul all any count maxval minval product sum pack unpack reshape spread cshift eoshift transpose maxloc minloc" list_non'5felem'5fsubr = Set.fromList $ words $ "date_and_time system_clock random_number random_seed" regex_'28'23'7ccDEC'5c'24'7cCDEC'5c'24'29'2e'2a'24 = compileRegex "(#|cDEC\\$|CDEC\\$).*$" regex_'5c'2e'28true'7cfalse'29'5c'2e = compileRegex "\\.(true|false)\\." regex_'5c'2e'5bA'2dZa'2dz'5d'2b'5c'2e = compileRegex "\\.[A-Za-z]+\\." regex_'28'3d'3d'7c'2f'3d'7c'3c'7c'3c'3d'7c'3e'7c'3e'3d'29 = compileRegex "(==|/=|<|<=|>|>=)" regex_'5bcC'5c'2a'5d'2e'2a'24 = compileRegex "[cC\\*].*$" regex_'21'2e'2a'24 = compileRegex "!.*$" regex_'5cb'28read'7cwrite'7cbackspace'7crewind'7cend'5cs'2afile'7cclose'29'5cs'2a'5b'28'5d = compileRegex "\\b(read|write|backspace|rewind|end\\s*file|close)\\s*[(]" regex_'5cbopen'5cs'2a'5b'28'5d = compileRegex "\\bopen\\s*[(]" regex_'5cbinquire'5cs'2a'5b'28'5d = compileRegex "\\binquire\\s*[(]" regex_'5cbformat'5cs'2a'5b'28'5d = compileRegex "\\bformat\\s*[(]" regex_'5cbend'5cs'2afile'5cb = compileRegex "\\bend\\s*file\\b" regex_'5b0'2d9'5d'2a'2f = compileRegex "[0-9]*/" regex_'5cbmodule'5cs'2bprocedure'5cb = compileRegex "\\bmodule\\s+procedure\\b" regex_'5cb'28program'7csubroutine'7cfunction'7cmodule'7cblock'5cs'2adata'29'5cb = compileRegex "\\b(program|subroutine|function|module|block\\s*data)\\b" regex_'5cbend'5cs'2a'28program'7csubroutine'7cfunction'7cmodule'7cblock'5cs'2adata'29'5cb = compileRegex "\\bend\\s*(program|subroutine|function|module|block\\s*data)\\b" regex_'5cbend'5cs'2a'28do'7cif'7cselect'7cwhere'7cforall'7cinterface'29'5cb = compileRegex "\\bend\\s*(do|if|select|where|forall|interface)\\b" regex_'5cbend'5cb = compileRegex "\\bend\\b" regex_'5cbinteger'5b'5c'2a'5d'5cd'7b1'2c2'7d = compileRegex "\\binteger[\\*]\\d{1,2}" regex_'5cbreal'5b'5c'2a'5d'5cd'7b1'2c2'7d = compileRegex "\\breal[\\*]\\d{1,2}" regex_'5cbcomplex'5b'5c'2a'5d'5cd'7b1'2c2'7d = compileRegex "\\bcomplex[\\*]\\d{1,2}" regex_'5cbend'5cs'2atype'5cb = compileRegex "\\bend\\s*type\\b" regex_'5cs'2adata'5cb = compileRegex "\\s*data\\b" regex_'5cs'2areal'5cs'2a'5b'28'5d = compileRegex "\\s*real\\s*[(]" regex_'5cs'2areal'28'3f'21'5b'5cw'5c'2a'5d'29 = compileRegex "\\s*real(?![\\w\\*])" regex_'5cbcharacter'5b'2a'5d'5b0'2d9'5d'2b'5cb = compileRegex "\\bcharacter[*][0-9]+\\b" regex_'5cb'28type'7cinteger'7ccomplex'7ccharacter'7clogical'7cintent'7cdimension'29'5cb'5cs'2a'5b'28'5d = compileRegex "\\b(type|integer|complex|character|logical|intent|dimension)\\b\\s*[(]" regex_'5cb'28type'7cinteger'7ccomplex'7ccharacter'7clogical'7cintent'7cdimension'29'5cb = compileRegex "\\b(type|integer|complex|character|logical|intent|dimension)\\b" regex_'5b0'2d9'5d'2a'5c'2e'5b0'2d9'5d'2b'28'5bde'5d'5b'2b'2d'5d'3f'5b0'2d9'5d'2b'29'3f'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dz'5d'5b'5cw'5f'5d'2a'29'29'3f = compileRegex "[0-9]*\\.[0-9]+([de][+-]?[0-9]+)?([_]([0-9]+|[a-z][\\w_]*))?" regex_'5cb'5b0'2d9'5d'2b'5c'2e'5b0'2d9'5d'2a'28'5bde'5d'5b'2b'2d'5d'3f'5b0'2d9'5d'2b'29'3f'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dz'5d'5b'5cw'5f'5d'2a'29'29'3f'28'3f'21'5ba'2dz'5d'29 = compileRegex "\\b[0-9]+\\.[0-9]*([de][+-]?[0-9]+)?([_]([0-9]+|[a-z][\\w_]*))?(?![a-z])" regex_'5cb'5b0'2d9'5d'2b'5bde'5d'5b'2b'2d'5d'3f'5b0'2d9'5d'2b'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dz'5d'5b'5cw'5f'5d'2a'29'29'3f = compileRegex "\\b[0-9]+[de][+-]?[0-9]+([_]([0-9]+|[a-z][\\w_]*))?" regex_'5cb'5b0'2d9'5d'2b'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dzA'2dZ'5d'5b'5cw'5f'5d'2a'29'29'3f = compileRegex "\\b[0-9]+([_]([0-9]+|[a-zA-Z][\\w_]*))?" regex_'5cb'5bbozx'5d'28'5b'27'5d'5b0'2d9a'2df'5d'2b'5b'27'5d'7c'5b'22'5d'5b0'2d9a'2df'5d'2b'5b'22'5d'29 = compileRegex "\\b[bozx](['][0-9a-f]+[']|[\"][0-9a-f]+[\"])" regex_'5b'5e'27'5d'2a'27 = compileRegex "[^']*'" regex_'26'5cs'2a'24 = compileRegex "&\\s*$" regex_'2e'2a'28'3f'3d'26'5cs'2a'24'29 = compileRegex ".*(?=&\\s*$)" regex_'5b'5e'22'5d'2a'22 = compileRegex "[^\"]*\"" regex_'28'21'2e'2a'29'3f'24 = compileRegex "(!.*)?$" defaultAttributes = [("default","Normal Text"),("find_preprocessor","Normal Text"),("find_op_and_log","Normal Text"),("find_comments","Normal Text"),("find_symbols","Normal Text"),("inside_func_paren","Normal Text"),("find_io_stmnts","Normal Text"),("find_io_paren","Normal Text"),("format_stmnt","Normal Text"),("find_begin_stmnts","Normal Text"),("find_end_stmnts","Normal Text"),("find_decls","Normal Text"),("find_paren","Data Type"),("find_intrinsics","Normal Text"),("find_numbers","Normal Text"),("find_strings","String"),("string_1","String"),("string_2","String"),("end_of_string","String")] parseRules "default" = do (attr, result) <- (((parseRules "find_strings")) <|> ((parseRules "find_decls")) <|> ((parseRules "find_intrinsics")) <|> ((parseRules "find_io_stmnts")) <|> ((parseRules "find_op_and_log")) <|> ((parseRules "find_numbers")) <|> ((parseRules "find_preprocessor")) <|> ((parseRules "find_comments")) <|> ((parseRules "find_symbols")) <|> ((parseRules "find_end_stmnts")) <|> ((parseRules "find_begin_stmnts"))) return (attr, result) parseRules "find_preprocessor" = do (attr, result) <- ((pColumn 0 >> pRegExpr regex_'28'23'7ccDEC'5c'24'7cCDEC'5c'24'29'2e'2a'24 >>= withAttribute "Preprocessor")) return (attr, result) parseRules "find_op_and_log" = do (attr, result) <- (((pRegExpr regex_'5c'2e'28true'7cfalse'29'5c'2e >>= withAttribute "Logical")) <|> ((pRegExpr regex_'5c'2e'5bA'2dZa'2dz'5d'2b'5c'2e >>= withAttribute "Operator")) <|> ((pRegExpr regex_'28'3d'3d'7c'2f'3d'7c'3c'7c'3c'3d'7c'3e'7c'3e'3d'29 >>= withAttribute "Operator"))) return (attr, result) parseRules "find_comments" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'5bcC'5c'2a'5d'2e'2a'24 >>= withAttribute "Comment")) <|> ((pRegExpr regex_'21'2e'2a'24 >>= withAttribute "Comment"))) return (attr, result) parseRules "find_symbols" = do (attr, result) <- (((pDetect2Chars False '*' '*' >>= withAttribute "Keyword")) <|> ((pDetect2Chars False '(' '/' >>= withAttribute "Keyword")) <|> ((pDetect2Chars False '/' ')' >>= withAttribute "Keyword")) <|> ((pAnyChar "&+-*/=?[]^{|}~" >>= withAttribute "Keyword")) <|> ((pAnyChar "()," >>= withAttribute "Symbol"))) return (attr, result) parseRules "inside_func_paren" = do (attr, result) <- (((pDetectChar False '(' >>= withAttribute "Normal Text") >>~ pushContext "inside_func_paren") <|> ((pDetectChar False ')' >>= withAttribute "Normal Text") >>~ (popContext >> return ())) <|> ((parseRules "find_strings")) <|> ((parseRules "find_intrinsics")) <|> ((parseRules "find_numbers"))) return (attr, result) parseRules "find_io_stmnts" = do (attr, result) <- (((pRegExpr regex_'5cb'28read'7cwrite'7cbackspace'7crewind'7cend'5cs'2afile'7cclose'29'5cs'2a'5b'28'5d >>= withAttribute "IO Function") >>~ pushContext "find_io_paren") <|> ((pRegExpr regex_'5cbopen'5cs'2a'5b'28'5d >>= withAttribute "IO Function") >>~ pushContext "find_io_paren") <|> ((pRegExpr regex_'5cbinquire'5cs'2a'5b'28'5d >>= withAttribute "IO Function") >>~ pushContext "find_io_paren") <|> ((pRegExpr regex_'5cbformat'5cs'2a'5b'28'5d >>= withAttribute "IO Function") >>~ pushContext "format_stmnt") <|> ((pRegExpr regex_'5cbend'5cs'2afile'5cb >>= withAttribute "IO Function")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_io'5ffunctions >>= withAttribute "IO Function"))) return (attr, result) parseRules "find_io_paren" = do (attr, result) <- (((pDetectChar False '*' >>= withAttribute "IO Function")) <|> ((pDetectChar False '(' >>= withAttribute "Normal Text") >>~ pushContext "inside_func_paren") <|> ((pDetectChar False ')' >>= withAttribute "IO Function") >>~ (popContext >> return ())) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_io'5fkeywords >>= withAttribute "IO Function")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_inquire'5fkeywords >>= withAttribute "IO Function")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_open'5fkeywords >>= withAttribute "IO Function")) <|> ((parseRules "find_strings")) <|> ((parseRules "find_intrinsics")) <|> ((parseRules "find_numbers")) <|> ((parseRules "find_symbols"))) return (attr, result) parseRules "format_stmnt" = do (attr, result) <- (((pDetectChar False '(' >>= withAttribute "IO Function") >>~ pushContext "format_stmnt") <|> ((pDetectChar False ')' >>= withAttribute "IO Function") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'5b0'2d9'5d'2a'2f >>= withAttribute "IO Function")) <|> ((pAnyChar ":" >>= withAttribute "IO Function")) <|> ((parseRules "find_strings")) <|> ((parseRules "find_symbols"))) return (attr, result) parseRules "find_begin_stmnts" = do (attr, result) <- (((pRegExpr regex_'5cbmodule'5cs'2bprocedure'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cb'28program'7csubroutine'7cfunction'7cmodule'7cblock'5cs'2adata'29'5cb >>= withAttribute "Keyword"))) return (attr, result) parseRules "find_end_stmnts" = do (attr, result) <- (((pRegExpr regex_'5cbend'5cs'2a'28program'7csubroutine'7cfunction'7cmodule'7cblock'5cs'2adata'29'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbend'5cs'2a'28do'7cif'7cselect'7cwhere'7cforall'7cinterface'29'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbend'5cb >>= withAttribute "Keyword"))) return (attr, result) parseRules "find_decls" = do (attr, result) <- (((pRegExpr regex_'5cbinteger'5b'5c'2a'5d'5cd'7b1'2c2'7d >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'5cbreal'5b'5c'2a'5d'5cd'7b1'2c2'7d >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'5cbcomplex'5b'5c'2a'5d'5cd'7b1'2c2'7d >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'5cbend'5cs'2atype'5cb >>= withAttribute "Data Type")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute "Data Type")) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2adata'5cb >>= withAttribute "Data Type")) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2areal'5cs'2a'5b'28'5d >>= withAttribute "Data Type") >>~ pushContext "find_paren") <|> ((pColumn 0 >> pRegExpr regex_'5cs'2areal'28'3f'21'5b'5cw'5c'2a'5d'29 >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'5cbcharacter'5b'2a'5d'5b0'2d9'5d'2b'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'5cb'28type'7cinteger'7ccomplex'7ccharacter'7clogical'7cintent'7cdimension'29'5cb'5cs'2a'5b'28'5d >>= withAttribute "Data Type") >>~ pushContext "find_paren") <|> ((pRegExpr regex_'5cb'28type'7cinteger'7ccomplex'7ccharacter'7clogical'7cintent'7cdimension'29'5cb >>= withAttribute "Data Type")) <|> ((pDetect2Chars False ':' ':' >>= withAttribute "Data Type"))) return (attr, result) parseRules "find_paren" = do (attr, result) <- (((pDetectChar False '(' >>= withAttribute "Data Type") >>~ pushContext "find_paren") <|> ((pDetectChar False ')' >>= withAttribute "Data Type") >>~ (popContext >> return ()))) return (attr, result) parseRules "find_intrinsics" = do (attr, result) <- (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute "Keyword")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_elemental'5fprocs >>= withAttribute "Elemental Procedure")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_inquiry'5ffn >>= withAttribute "Inquiry Function")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_transform'5ffn >>= withAttribute "Transformational Function")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_non'5felem'5fsubr >>= withAttribute "Non elemental subroutine"))) return (attr, result) parseRules "find_numbers" = do (attr, result) <- (((pRegExpr regex_'5b0'2d9'5d'2a'5c'2e'5b0'2d9'5d'2b'28'5bde'5d'5b'2b'2d'5d'3f'5b0'2d9'5d'2b'29'3f'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dz'5d'5b'5cw'5f'5d'2a'29'29'3f >>= withAttribute "Float")) <|> ((pRegExpr regex_'5cb'5b0'2d9'5d'2b'5c'2e'5b0'2d9'5d'2a'28'5bde'5d'5b'2b'2d'5d'3f'5b0'2d9'5d'2b'29'3f'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dz'5d'5b'5cw'5f'5d'2a'29'29'3f'28'3f'21'5ba'2dz'5d'29 >>= withAttribute "Float")) <|> ((pRegExpr regex_'5cb'5b0'2d9'5d'2b'5bde'5d'5b'2b'2d'5d'3f'5b0'2d9'5d'2b'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dz'5d'5b'5cw'5f'5d'2a'29'29'3f >>= withAttribute "Float")) <|> ((pRegExpr regex_'5cb'5b0'2d9'5d'2b'28'5b'5f'5d'28'5b0'2d9'5d'2b'7c'5ba'2dzA'2dZ'5d'5b'5cw'5f'5d'2a'29'29'3f >>= withAttribute "Decimal")) <|> ((pRegExpr regex_'5cb'5bbozx'5d'28'5b'27'5d'5b0'2d9a'2df'5d'2b'5b'27'5d'7c'5b'22'5d'5b0'2d9a'2df'5d'2b'5b'22'5d'29 >>= withAttribute "Decimal"))) return (attr, result) parseRules "find_strings" = do (attr, result) <- (((pDetectChar False '\'' >>= withAttribute "String") >>~ pushContext "string_1") <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "string_2")) return (attr, result) parseRules "string_1" = do (attr, result) <- (((pRegExpr regex_'5b'5e'27'5d'2a'27 >>= withAttribute "String") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'26'5cs'2a'24 >>= withAttribute "Keyword") >>~ pushContext "end_of_string") <|> ((pRegExpr regex_'2e'2a'28'3f'3d'26'5cs'2a'24'29 >>= withAttribute "String") >>~ pushContext "end_of_string") <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "string_2" = do (attr, result) <- (((pRegExpr regex_'5b'5e'22'5d'2a'22 >>= withAttribute "String") >>~ (popContext >> return ())) <|> ((pRegExpr regex_'26'5cs'2a'24 >>= withAttribute "Keyword") >>~ pushContext "end_of_string") <|> ((pRegExpr regex_'2e'2a'28'3f'3d'26'5cs'2a'24'29 >>= withAttribute "String") >>~ pushContext "end_of_string") <|> ((popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules "end_of_string" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "String")) <|> ((pRegExpr regex_'26'5cs'2a'24 >>= withAttribute "Keyword")) <|> ((pFirstNonSpace >> pDetectChar False '&' >>= withAttribute "Keyword") >>~ (popContext >> return ())) <|> ((pFirstNonSpace >> pRegExpr regex_'28'21'2e'2a'29'3f'24 >>= withAttribute "Comment")) <|> ((popContext >> popContext >> return ()) >> return ([], ""))) return (attr, result) parseRules x = fail $ "Unknown context" ++ x