{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Coldfusion (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "ColdFusion" , sFilename = "coldfusion.xml" , sShortname = "Coldfusion" , sContexts = fromList [ ( "Normal Text" , Context { cName = "Normal Text" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = StringDetect "" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxCF Tag" , Context { cName = "ctxCF Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxCFSCRIPT Block" , Context { cName = "ctxCFSCRIPT Block" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxC Style Comment" ) ] } , Rule { rMatcher = Detect2Chars '/' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxOne Line Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "[()[\\]=+-*/]+" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "{}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./:;<=>?[\\]^{|}~" } (makeWordSet False [ "break" , "case" , "catch" , "continue" , "default" , "do" , "else" , "for" , "function" , "if" , "in" , "return" , "switch" , "try" , "var" , "while" ]) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./:;<=>?[\\]^{|}~" } (makeWordSet False [ "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" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxCFSCRIPT Tag" , Context { cName = "ctxCFSCRIPT Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxCFSCRIPT Block" ) ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxCFX Tag" , Context { cName = "ctxCFX Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxCustom Tag" , Context { cName = "ctxCustom Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxHTML Comment" , Context { cName = "ctxHTML Comment" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = StringDetect "" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxHTML Entities" , Context { cName = "ctxHTML Entities" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar ';' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxImage Tag" , Context { cName = "ctxImage Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxOne Line Comment" , Context { cName = "ctxOne Line Comment" , cSyntax = "ColdFusion" , cRules = [] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxSCRIPT Block" , Context { cName = "ctxSCRIPT Block" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxC Style Comment" ) ] } , Rule { rMatcher = Detect2Chars '/' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxOne Line Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "[()[\\]=+-*/]+" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "{}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./:;<=>?[\\]^{|}~" } (makeWordSet False [ "break" , "case" , "catch" , "const" , "continue" , "default" , "delete" , "do" , "else" , "false" , "for" , "function" , "if" , "in" , "new" , "return" , "switch" , "this" , "throw" , "true" , "try" , "typeof" , "var" , "void" , "while" , "with" ]) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./:;<=>?[\\]^{|}~" } (makeWordSet False [ "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" ]) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./:;<=>?[\\]^{|}~" } (makeWordSet False [ "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" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxSCRIPT Tag" , Context { cName = "ctxSCRIPT Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxSCRIPT Block" ) ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxSTYLE Block" , Context { cName = "ctxSTYLE Block" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxC Style Comment" ) ] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxStyle Properties" ) ] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxSTYLE Tag" , Context { cName = "ctxSTYLE Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxSTYLE Block" ) ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxStyle Properties" , Context { cName = "ctxStyle Properties" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxC Style Comment" ) ] } , Rule { rMatcher = DetectChar ':' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "ColdFusion" , "ctxStyle Values" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxStyle Values" , Context { cName = "ctxStyle Values" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar ';' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar ',' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "#([0-9a-fA-F]{3})|([0-9a-fA-F]{6})" , reCompiled = Just (compileRegex True "#([0-9a-fA-F]{3})|([0-9a-fA-F]{6})") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxTable Tag" , Context { cName = "ctxTable Tag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ctxTag" , Context { cName = "ctxTag" , cSyntax = "ColdFusion" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '=' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[^\"]*\"" , reCompiled = Just (compileRegex True "\"[^\"]*\"") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'[^']*'" , reCompiled = Just (compileRegex True "'[^']*'") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.cfm" , "*.cfc" , "*.cfml" , "*.dbm" ] , sStartingContext = "Normal Text" }