{- This module was generated from data in the Kate syntax highlighting file coldfusion.xml, version 1.04, by -} module Text.Highlighting.Kate.Syntax.Coldfusion (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 = "ColdFusion" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.cfm;*.cfc;*.cfml;*.dbm" -- | 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 -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do (lang,cont) <- currentContext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("ColdFusion","Normal Text")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState if length contexts >= 2 then case context of ("ColdFusion","Normal Text") -> return () ("ColdFusion","ctxCFSCRIPT Tag") -> return () ("ColdFusion","ctxSCRIPT Tag") -> return () ("ColdFusion","ctxSTYLE Tag") -> return () ("ColdFusion","ctxTag") -> return () ("ColdFusion","ctxTable Tag") -> return () ("ColdFusion","ctxAnchor Tag") -> return () ("ColdFusion","ctxImage Tag") -> return () ("ColdFusion","ctxCF Tag") -> return () ("ColdFusion","ctxCustom Tag") -> return () ("ColdFusion","ctxCFX Tag") -> return () ("ColdFusion","ctxHTML Comment") -> return () ("ColdFusion","ctxCF Comment") -> return () ("ColdFusion","ctxC Style Comment") -> return () ("ColdFusion","ctxOne Line Comment") -> (popContext) >> pEndLine ("ColdFusion","ctxHTML Entities") -> (popContext) >> pEndLine ("ColdFusion","ctxCFSCRIPT Block") -> return () ("ColdFusion","ctxSCRIPT Block") -> return () ("ColdFusion","ctxSTYLE Block") -> return () ("ColdFusion","ctxStyle Properties") -> return () ("ColdFusion","ctxStyle Values") -> (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_Script_Keywords = Set.fromList $ words $ "if else for in while do continue break with try catch switch case new var function return this delete true false void throw typeof const default" list_Script_Objects = Set.fromList $ words $ "anchor applet area array boolean button checkbox date document event fileupload form frame function hidden history image layer linke location math navigator number object option password radio regexp reset screen select string submit text textarea window" list_Script_Methods = Set.fromList $ words $ "abs acos alert anchor apply asin atan atan2 back blur call captureevents ceil charat charcodeat clearinterval cleartimeout click close compile concat confirm cos disableexternalcapture enableexternalcapture eval exec exp find floor focus forward fromcharcode getdate getday getfullyear gethours getmilliseconds getminutes getmonth getseconds getselection gettime gettimezoneoffset getutcdate getutcday getutcfullyear getutchours getutcmilliseconds getutcminutes getutcmonth getutcseconds go handleevent home indexof javaenabled join lastindexof link load log match max min moveabove movebelow moveby moveto movetoabsolute open parse plugins.refresh pop pow preference print prompt push random releaseevents reload replace reset resizeby resizeto reverse round routeevent scrollby scrollto search select setdate setfullyear sethours setinterval setmilliseconds setminutes setmonth setseconds settime settimeout setutcdate setutcfullyear setutchours setutcmilliseconds setutcminutes setutcmonth setutcseconds shift sin slice sort splice split sqrt stop string formatting submit substr substring taintenabled tan test tolocalestring tolowercase tosource tostring touppercase toutcstring unshift unwatch utc valueof watch write writeln" list_CFSCRIPT_Keywords = Set.fromList $ words $ "break case catch continue default do else for function if in return switch try var while" list_CFSCRIPT_Functions = Set.fromList $ words $ "abs acos arrayappend arrayavg arrayclear arraydeleteat arrayinsertat arrayisempty arraylen arraymax arraymin arraynew arrayprepend arrayresize arrayset arraysort arraysum arrayswap arraytolist asc asin atn bitand bitmaskclear bitmaskread bitmaskset bitnot bitor bitshln bitshrn bitxor ceiling chr cjustify compare comparenocase cos createdate createdatetime createobject createodbcdate createodbcdatetime createodbctime createtime createtimespan createuuid dateadd datecompare dateconvert datediff dateformat datepart day dayofweek dayofweekasstring dayofyear daysinmonth daysinyear de decimalformat decrementvalue decrypt deleteclientvariable directoryexists dollarformat duplicate encrypt evaluate exp expandpath fileexists find findnocase findoneof firstdayofmonth fix formatbasen getauthuser getbasetagdata getbasetaglist getbasetemplatepath getclientvariableslist getcurrenttemplatepath getdirectoryfrompath getexception getfilefrompath getfunctionlist gethttprequestdata gethttptimestring getk2serverdoccount getk2serverdoccountlimit getlocale getmetadata getmetricdata getpagecontext getprofilesections getprofilestring getservicesettings gettempdirectory gettempfile gettemplatepath gettickcount gettimezoneinfo gettoken hash hour htmlcodeformat htmleditformat iif incrementvalue inputbasen insert int isarray isbinary isboolean iscustomfunction isdate isdebugmode isdefined isk2serverabroker isk2serverdoccountexceeded isk2serveronline isleapyear isnumeric isnumericdate isobject isquery issimplevalue isstruct isuserinrole iswddx isxmldoc isxmlelement isxmlroot javacast jsstringformat lcase left len listappend listchangedelims listcontains listcontainsnocase listdeleteat listfind listfindnocase listfirst listgetat listinsertat listlast listlen listprepend listqualify listrest listsetat listsort listtoarray listvaluecount listvaluecountnocase ljustify log log10 lscurrencyformat lsdateformat lseurocurrencyformat lsiscurrency lsisdate lsisnumeric lsnumberformat lsparsecurrency lsparsedatetime lsparseeurocurrency lsparsenumber lstimeformat ltrim max mid min minute month monthasstring now numberformat paragraphformat parameterexists parsedatetime pi preservesinglequotes quarter queryaddcolumn queryaddrow querynew querysetcell quotedvaluelist rand randomize randrange refind refindnocase removechars repeatstring replace replacelist replacenocase rereplace rereplacenocase reverse right rjustify round rtrim second setencoding setlocale setprofilestring setvariable sgn sin spanexcluding spanincluding sqr stripcr structappend structclear structcopy structcount structdelete structfind structfindkey structfindvalue structget structinsert structisempty structkeyarray structkeyexists structkeylist structnew structsort structupdate tan timeformat tobase64 tobinary tostring trim ucase urldecode urlencodedformat urlsessionformat val valuelist week writeoutput xmlchildpos xmlelemnew xmlformat xmlnew xmlparse xmlsearch xmltransform year yesnoformat" regex_'3c'5bcC'5d'5bfF'5d'5bsS'5d'5bcC'5d'5brR'5d'5biI'5d'5bpP'5d'5btT'5d = compileRegex "<[cC][fF][sS][cC][rR][iI][pP][tT]" regex_'3c'5bsS'5d'5bcC'5d'5brR'5d'5biI'5d'5bpP'5d'5btT'5d = compileRegex "<[sS][cC][rR][iI][pP][tT]" regex_'3c'5bsS'5d'5btT'5d'5byY'5d'5blL'5d'5beE'5d = compileRegex "<[sS][tT][yY][lL][eE]" regex_'3c'5c'2f'3f'5bcC'5d'5bfF'5d'5f = compileRegex "<\\/?[cC][fF]_" regex_'3c'5c'2f'3f'5bcC'5d'5bfF'5d'5bxX'5d'5f = compileRegex "<\\/?[cC][fF][xX]_" regex_'3c'5c'2f'3f'5bcC'5d'5bfF'5d = compileRegex "<\\/?[cC][fF]" regex_'3c'5c'2f'3f'28'5btT'5d'5baAhHbBfFrRdD'5d'29'7c'28'5bcC'5d'5baA'5d'5bpP'5d'5btT'5d'29 = compileRegex "<\\/?([tT][aAhHbBfFrRdD])|([cC][aA][pP][tT])" regex_'3c'5c'2f'3f'5baA'5d_ = compileRegex "<\\/?[aA] " regex_'3c'5c'2f'3f'5biI'5d'5bmM'5d'5bgG'5d_ = compileRegex "<\\/?[iI][mM][gG] " regex_'3c'21'3f'5c'2f'3f'5ba'2dzA'2dZ0'2d9'5f'5d'2b = compileRegex "" regex_'3c'2f'5bsS'5d'5bcC'5d'5brR'5d'5biI'5d'5bpP'5d'5btT'5d'3e = compileRegex "" regex_'3c'2f'5bsS'5d'5btT'5d'5byY'5d'5blL'5d'5beE'5d'3e = compileRegex "" regex_'23'28'5b0'2d9a'2dfA'2dF'5d'7b3'7d'29'7c'28'5b0'2d9a'2dfA'2dF'5d'7b6'7d'29 = compileRegex "#([0-9a-fA-F]{3})|([0-9a-fA-F]{6})" parseRules ("ColdFusion","Normal Text") = (((pString False "" >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxHTML Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("ColdFusion","ctxCF Comment") = (((pString False "--->" >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxCF Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("ColdFusion","ctxC Style Comment") = (((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxC Style Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("ColdFusion","ctxOne Line Comment") = (currentContext >>= \x -> guard (x == ("ColdFusion","ctxOne Line Comment")) >> pDefault >>= withAttribute CommentTok) parseRules ("ColdFusion","ctxHTML Entities") = (((pDetectChar False ';' >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxHTML Entities")) >> pDefault >>= withAttribute NormalTok)) parseRules ("ColdFusion","ctxCFSCRIPT Block") = (((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("ColdFusion","ctxC Style Comment")) <|> ((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("ColdFusion","ctxOne Line Comment")) <|> ((pRegExpr regex_'22'5b'5e'22'5d'2a'22 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'27'5b'5e'27'5d'2a'27 >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute NormalTok)) <|> ((pFloat >>= withAttribute NormalTok)) <|> ((pAnyChar "[()[\\]=+-*/]+" >>= withAttribute NormalTok)) <|> ((pAnyChar "{}" >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_CFSCRIPT_Keywords >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_CFSCRIPT_Functions >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'3c'2f'5bcC'5d'5bfF'5d'5bsS'5d'5bcC'5d'5brR'5d'5biI'5d'5bpP'5d'5btT'5d'3e >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxCFSCRIPT Block")) >> pDefault >>= withAttribute NormalTok)) parseRules ("ColdFusion","ctxSCRIPT Block") = (((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("ColdFusion","ctxC Style Comment")) <|> ((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("ColdFusion","ctxOne Line Comment")) <|> ((pRegExpr regex_'22'5b'5e'22'5d'2a'22 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'27'5b'5e'27'5d'2a'27 >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute NormalTok)) <|> ((pFloat >>= withAttribute NormalTok)) <|> ((pAnyChar "[()[\\]=+-*/]+" >>= withAttribute NormalTok)) <|> ((pAnyChar "{}" >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_Script_Keywords >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_Script_Objects >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_Script_Methods >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'3c'2f'5bsS'5d'5bcC'5d'5brR'5d'5biI'5d'5bpP'5d'5btT'5d'3e >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxSCRIPT Block")) >> pDefault >>= withAttribute NormalTok)) parseRules ("ColdFusion","ctxSTYLE Block") = (((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("ColdFusion","ctxC Style Comment")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("ColdFusion","ctxStyle Properties")) <|> ((pRegExpr regex_'3c'2f'5bsS'5d'5btT'5d'5byY'5d'5blL'5d'5beE'5d'3e >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxSTYLE Block")) >> pDefault >>= withAttribute NormalTok)) parseRules ("ColdFusion","ctxStyle Properties") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("ColdFusion","ctxC Style Comment")) <|> ((pDetectChar False ':' >>= withAttribute NormalTok) >>~ pushContext ("ColdFusion","ctxStyle Values")) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxStyle Properties")) >> pDefault >>= withAttribute NormalTok)) parseRules ("ColdFusion","ctxStyle Values") = (((pDetectChar False ';' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False ',' >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute NormalTok)) <|> ((pFloat >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'23'28'5b0'2d9a'2dfA'2dF'5d'7b3'7d'29'7c'28'5b0'2d9a'2dfA'2dF'5d'7b6'7d'29 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'22'5b'5e'22'5d'2a'22 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'27'5b'5e'27'5d'2a'27 >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("ColdFusion","ctxStyle Values")) >> pDefault >>= withAttribute NormalTok)) parseRules x = parseRules ("ColdFusion","Normal Text") <|> fail ("Unknown context" ++ show x)