{- This module was generated from data in the Kate syntax highlighting file fortran.xml, version 1.13, by Franchin Matteo (fnch@libero.it) -} module Text.Highlighting.Kate.Syntax.Fortran (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common 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 = "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 -> [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 = [("Fortran","default")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = False, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState if length contexts >= 2 then case context of ("Fortran","default") -> return () ("Fortran","find_preprocessor") -> return () ("Fortran","find_op_and_log") -> return () ("Fortran","find_comments") -> return () ("Fortran","find_symbols") -> return () ("Fortran","inside_func_paren") -> return () ("Fortran","find_io_stmnts") -> return () ("Fortran","find_io_paren") -> return () ("Fortran","format_stmnt") -> return () ("Fortran","find_begin_stmnts") -> return () ("Fortran","find_end_stmnts") -> return () ("Fortran","find_mid_stmnts") -> return () ("Fortran","find_decls") -> return () ("Fortran","find_paren") -> (popContext) >> pEndLine ("Fortran","find_intrinsics") -> return () ("Fortran","find_numbers") -> return () ("Fortran","find_strings") -> return () ("Fortran","string_1") -> return () ("Fortran","string_2") -> return () ("Fortran","end_of_string") -> 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_keywords = Set.fromList $ words $ "allocate break call case common continue cycle deallocate default forall where elsewhere 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 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'28subroutine'7cfunction'7cblock'5cs'2adata'29'5cb = compileRegex "\\b(subroutine|function|block\\s*data)\\b" regex_'5cb'28program'7cmodule'7cblock'5cs'2adata'29'5cb = compileRegex "\\b(program|module|block\\s*data)\\b" regex_'5cb'28then'7cdo'29'5cb = compileRegex "\\b(then|do)\\b" regex_'5cbend'5cs'2a'28subroutine'7cfunction'7cblock'5cs'2adata'29'5cb = compileRegex "\\bend\\s*(subroutine|function|block\\s*data)\\b" regex_'5cbend'5cs'2a'28program'7cmodule'29'5cb = compileRegex "\\bend\\s*(program|module)\\b" regex_'5cbend'5cs'2a'28do'7cif'29'5cb = compileRegex "\\bend\\s*(do|if)\\b" regex_'5cbend'5cs'2a'28select'7cwhere'7cforall'7cinterface'29'5cb = compileRegex "\\bend\\s*(select|where|forall|interface)\\b" regex_'5cbelse'5cs'2aif'5cb = compileRegex "\\belse\\s*if\\b" regex_'5cbend'5cb = compileRegex "\\bend\\b" regex_'5cbelse'5cb = compileRegex "\\belse\\b" regex_'5cbcontains'5cb = compileRegex "\\bcontains\\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 "(!.*)?$" parseRules ("Fortran","default") = (((parseRules ("Fortran","find_strings"))) <|> ((parseRules ("Fortran","find_decls"))) <|> ((parseRules ("Fortran","find_intrinsics"))) <|> ((parseRules ("Fortran","find_io_stmnts"))) <|> ((parseRules ("Fortran","find_op_and_log"))) <|> ((parseRules ("Fortran","find_numbers"))) <|> ((parseRules ("Fortran","find_preprocessor"))) <|> ((parseRules ("Fortran","find_comments"))) <|> ((parseRules ("Fortran","find_symbols"))) <|> ((parseRules ("Fortran","find_begin_stmnts"))) <|> ((parseRules ("Fortran","find_end_stmnts"))) <|> ((parseRules ("Fortran","find_mid_stmnts"))) <|> (currentContext >>= \x -> guard (x == ("Fortran","default")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_preprocessor") = (((pColumn 0 >> pRegExpr regex_'28'23'7ccDEC'5c'24'7cCDEC'5c'24'29'2e'2a'24 >>= withAttribute OtherTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_preprocessor")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_op_and_log") = (((pRegExpr regex_'5c'2e'28true'7cfalse'29'5c'2e >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5c'2e'5bA'2dZa'2dz'5d'2b'5c'2e >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28'3d'3d'7c'2f'3d'7c'3c'7c'3c'3d'7c'3e'7c'3e'3d'29 >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_op_and_log")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_comments") = (((pColumn 0 >> pRegExpr regex_'5bcC'5c'2a'5d'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'21'2e'2a'24 >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_comments")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_symbols") = (((pDetect2Chars False '*' '*' >>= withAttribute KeywordTok)) <|> ((pDetect2Chars False '(' '/' >>= withAttribute KeywordTok)) <|> ((pDetect2Chars False '/' ')' >>= withAttribute KeywordTok)) <|> ((pAnyChar "&+-*/=?[]^{|}~" >>= withAttribute KeywordTok)) <|> ((pAnyChar "()," >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_symbols")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","inside_func_paren") = (((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Fortran","inside_func_paren")) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("Fortran","find_strings"))) <|> ((parseRules ("Fortran","find_intrinsics"))) <|> ((parseRules ("Fortran","find_numbers"))) <|> (currentContext >>= \x -> guard (x == ("Fortran","inside_func_paren")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_io_stmnts") = (((pRegExpr regex_'5cb'28read'7cwrite'7cbackspace'7crewind'7cend'5cs'2afile'7cclose'29'5cs'2a'5b'28'5d >>= withAttribute FunctionTok) >>~ pushContext ("Fortran","find_io_paren")) <|> ((pRegExpr regex_'5cbopen'5cs'2a'5b'28'5d >>= withAttribute FunctionTok) >>~ pushContext ("Fortran","find_io_paren")) <|> ((pRegExpr regex_'5cbinquire'5cs'2a'5b'28'5d >>= withAttribute FunctionTok) >>~ pushContext ("Fortran","find_io_paren")) <|> ((pRegExpr regex_'5cbformat'5cs'2a'5b'28'5d >>= withAttribute FunctionTok) >>~ pushContext ("Fortran","format_stmnt")) <|> ((pRegExpr regex_'5cbend'5cs'2afile'5cb >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_io'5ffunctions >>= withAttribute FunctionTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_io_stmnts")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_io_paren") = (((pDetectChar False '*' >>= withAttribute FunctionTok)) <|> ((pDetectChar False '(' >>= withAttribute NormalTok) >>~ pushContext ("Fortran","inside_func_paren")) <|> ((pDetectChar False ')' >>= withAttribute FunctionTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_io'5fkeywords >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_inquire'5fkeywords >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_open'5fkeywords >>= withAttribute FunctionTok)) <|> ((parseRules ("Fortran","find_strings"))) <|> ((parseRules ("Fortran","find_intrinsics"))) <|> ((parseRules ("Fortran","find_numbers"))) <|> ((parseRules ("Fortran","find_symbols"))) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_io_paren")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","format_stmnt") = (((pDetectChar False '(' >>= withAttribute FunctionTok) >>~ pushContext ("Fortran","format_stmnt")) <|> ((pDetectChar False ')' >>= withAttribute FunctionTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b0'2d9'5d'2a'2f >>= withAttribute FunctionTok)) <|> ((pAnyChar ":" >>= withAttribute FunctionTok)) <|> ((parseRules ("Fortran","find_strings"))) <|> ((parseRules ("Fortran","find_symbols"))) <|> (currentContext >>= \x -> guard (x == ("Fortran","format_stmnt")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_begin_stmnts") = (((pRegExpr regex_'5cbmodule'5cs'2bprocedure'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28subroutine'7cfunction'7cblock'5cs'2adata'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28program'7cmodule'7cblock'5cs'2adata'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28then'7cdo'29'5cb >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_begin_stmnts")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_end_stmnts") = (((pRegExpr regex_'5cbend'5cs'2a'28subroutine'7cfunction'7cblock'5cs'2adata'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbend'5cs'2a'28program'7cmodule'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbend'5cs'2a'28do'7cif'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbend'5cs'2a'28select'7cwhere'7cforall'7cinterface'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbelse'5cs'2aif'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbend'5cb >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_end_stmnts")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_mid_stmnts") = (((pRegExpr regex_'5cbelse'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbcontains'5cb >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_mid_stmnts")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_decls") = (((pRegExpr regex_'5cbinteger'5b'5c'2a'5d'5cd'7b1'2c2'7d >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5cbreal'5b'5c'2a'5d'5cd'7b1'2c2'7d >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5cbcomplex'5b'5c'2a'5d'5cd'7b1'2c2'7d >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5cbend'5cs'2atype'5cb >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute DataTypeTok)) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2adata'5cb >>= withAttribute DataTypeTok)) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2areal'5cs'2a'5b'28'5d >>= withAttribute DataTypeTok) >>~ pushContext ("Fortran","find_paren")) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2areal'28'3f'21'5b'5cw'5c'2a'5d'29 >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5cbcharacter'5b'2a'5d'5b0'2d9'5d'2b'5cb >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5cb'28type'7cinteger'7ccomplex'7ccharacter'7clogical'7cintent'7cdimension'29'5cb'5cs'2a'5b'28'5d >>= withAttribute DataTypeTok) >>~ pushContext ("Fortran","find_paren")) <|> ((pRegExpr regex_'5cb'28type'7cinteger'7ccomplex'7ccharacter'7clogical'7cintent'7cdimension'29'5cb >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False ':' ':' >>= withAttribute DataTypeTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_decls")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_paren") = (((pDetectChar False '(' >>= withAttribute DataTypeTok) >>~ pushContext ("Fortran","find_paren")) <|> ((pDetectChar False ')' >>= withAttribute DataTypeTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_paren")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Fortran","find_intrinsics") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_elemental'5fprocs >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_inquiry'5ffn >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_transform'5ffn >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_non'5felem'5fsubr >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_intrinsics")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_numbers") = (((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 FloatTok)) <|> ((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 FloatTok)) <|> ((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 FloatTok)) <|> ((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 DecValTok)) <|> ((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 DecValTok)) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_numbers")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Fortran","find_strings") = (((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("Fortran","string_1")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Fortran","string_2")) <|> (currentContext >>= \x -> guard (x == ("Fortran","find_strings")) >> pDefault >>= withAttribute StringTok)) parseRules ("Fortran","string_1") = (((pRegExpr regex_'5b'5e'27'5d'2a'27 >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'26'5cs'2a'24 >>= withAttribute KeywordTok) >>~ pushContext ("Fortran","end_of_string")) <|> ((pRegExpr regex_'2e'2a'28'3f'3d'26'5cs'2a'24'29 >>= withAttribute StringTok) >>~ pushContext ("Fortran","end_of_string")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Fortran","string_2") = (((pRegExpr regex_'5b'5e'22'5d'2a'22 >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'26'5cs'2a'24 >>= withAttribute KeywordTok) >>~ pushContext ("Fortran","end_of_string")) <|> ((pRegExpr regex_'2e'2a'28'3f'3d'26'5cs'2a'24'29 >>= withAttribute StringTok) >>~ pushContext ("Fortran","end_of_string")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("Fortran","end_of_string") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExpr regex_'26'5cs'2a'24 >>= withAttribute KeywordTok)) <|> ((pFirstNonSpace >> pDetectChar False '&' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pFirstNonSpace >> pRegExpr regex_'28'21'2e'2a'29'3f'24 >>= withAttribute CommentTok)) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules x = parseRules ("Fortran","default") <|> fail ("Unknown context" ++ show x)