{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Email (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "Email" , sFilename = "email.xml" , sShortname = "Email" , sContexts = fromList [ ( "headder" , Context { cName = "headder" , cSyntax = "Email" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[Tt]o:.*$" , reCompiled = Just (compileRegex False "[Tt]o:.*$") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ff]rom:.*$" , reCompiled = Just (compileRegex False "[Ff]rom:.*$") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Cc][Cc]:.*$" , reCompiled = Just (compileRegex False "[Cc][Cc]:.*$") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Bb][Cc][Cc]:.*$" , reCompiled = Just (compileRegex False "[Bb][Cc][Cc]:.*$") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ss]ubject:.*$" , reCompiled = Just (compileRegex False "[Ss]ubject:.*$") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Dd]ate:.*$" , reCompiled = Just (compileRegex False "[Dd]ate:.*$") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ss]ender:" , reCompiled = Just (compileRegex False "[Ss]ender:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]eply-[Tt]o:" , reCompiled = Just (compileRegex False "[Rr]eply-[Tt]o:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Mm]essage-[Ii][Dd]:" , reCompiled = Just (compileRegex False "[Mm]essage-[Ii][Dd]:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ii]n-[Rr]eply-[Tt]o:" , reCompiled = Just (compileRegex False "[Ii]n-[Rr]eply-[Tt]o:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]eferences:" , reCompiled = Just (compileRegex False "[Rr]eferences:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Cc]omments:" , reCompiled = Just (compileRegex False "[Cc]omments:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Kk]eywors:" , reCompiled = Just (compileRegex False "[Kk]eywors:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Dd]ate:" , reCompiled = Just (compileRegex False "[Rr]esent-[Dd]ate:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Ff]rom:" , reCompiled = Just (compileRegex False "[Rr]esent-[Ff]rom:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Ss]ender:" , reCompiled = Just (compileRegex False "[Rr]esent-[Ss]ender:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Tt]o:" , reCompiled = Just (compileRegex False "[Rr]esent-[Tt]o:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Cc][Cc]:" , reCompiled = Just (compileRegex False "[Rr]esent-[Cc][Cc]:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Bb][Cc][Cc]:" , reCompiled = Just (compileRegex False "[Rr]esent-[Bb][Cc][Cc]:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Mm]essage-[Ii][Dd]:" , reCompiled = Just (compileRegex False "[Rr]esent-[Mm]essage-[Ii][Dd]:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]esent-[Rr]eply-[Tt]o:" , reCompiled = Just (compileRegex False "[Rr]esent-[Rr]eply-[Tt]o:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]eturn-[Pp]ath:" , reCompiled = Just (compileRegex False "[Rr]eturn-[Pp]ath:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Rr]eceived:" , reCompiled = Just (compileRegex False "[Rr]eceived:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Mm]ozilla-[Ss]tatus:" , reCompiled = Just (compileRegex False "[Xx]-[Mm]ozilla-[Ss]tatus:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Mm]ozilla-[Ss]tatus2:" , reCompiled = Just (compileRegex False "[Xx]-[Mm]ozilla-[Ss]tatus2:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ee]nverlope-[Tt]o:" , reCompiled = Just (compileRegex False "[Ee]nverlope-[Tt]o:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Dd]elivery-[Dd]ate:" , reCompiled = Just (compileRegex False "[Dd]elivery-[Dd]ate:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Oo]riginating-[Ii][Pp]:" , reCompiled = Just (compileRegex False "[Xx]-[Oo]riginating-[Ii][Pp]:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Oo]riginating-[Ee]mail:" , reCompiled = Just (compileRegex False "[Xx]-[Oo]riginating-[Ee]mail:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Ss]ender:" , reCompiled = Just (compileRegex False "[Xx]-[Ss]ender:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Mm]ime-[Vv]ersion:" , reCompiled = Just (compileRegex False "[Mm]ime-[Vv]ersion:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Cc]ontent-[Tt]ype:" , reCompiled = Just (compileRegex False "[Cc]ontent-[Tt]ype:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Mm]ailing-[Ll]ist:" , reCompiled = Just (compileRegex False "[Xx]-[Mm]ailing-[Ll]ist:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Ll]oop:" , reCompiled = Just (compileRegex False "[Xx]-[Ll]oop:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ll]ist-[Pp]ost:" , reCompiled = Just (compileRegex False "[Ll]ist-[Pp]ost:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ll]ist-[Hh]elp:" , reCompiled = Just (compileRegex False "[Ll]ist-[Hh]elp:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Ll]ist-[Uu]nsubscribe:" , reCompiled = Just (compileRegex False "[Ll]ist-[Uu]nsubscribe:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Pp]recedence:" , reCompiled = Just (compileRegex False "[Pp]recedence:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Cc]ontent-[Tt]ransfer-[Ee]ncoding:" , reCompiled = Just (compileRegex False "[Cc]ontent-[Tt]ransfer-[Ee]ncoding:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Cc]ontent-[Tt]ype:" , reCompiled = Just (compileRegex False "[Cc]ontent-[Tt]ype:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Xx]-[Bb]ulkmail:" , reCompiled = Just (compileRegex False "[Xx]-[Bb]ulkmail:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Pp]recedence:" , reCompiled = Just (compileRegex False "[Pp]recedence:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[Cc]ontent-[Dd]isposition:" , reCompiled = Just (compileRegex False "[Cc]ontent-[Dd]isposition:") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[0-9a-zA-Z-.]+:" , reCompiled = Just (compileRegex False "[0-9a-zA-Z-.]+:") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z0-9.\\-]+\\@[a-zA-Z0-9.\\-]+" , reCompiled = Just (compileRegex False "[a-zA-Z0-9.\\-]+\\@[a-zA-Z0-9.\\-]+") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z0-9.\\-]*\\s*<[a-zA-Z0-9.\\-]+\\@[a-zA-Z0-9.\\-]+>" , reCompiled = Just (compileRegex False "[a-zA-Z0-9.\\-]*\\s*<[a-zA-Z0-9.\\-]+\\@[a-zA-Z0-9.\\-]+>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\"[a-zA-Z0-9. \\-]+\"\\s*<[a-zA-Z0-9.\\-]+\\@[a-zA-Z0-9.\\-]+>" , reCompiled = Just (compileRegex False "\"[a-zA-Z0-9. \\-]+\"\\s*<[a-zA-Z0-9.\\-]+\\@[a-zA-Z0-9.\\-]+>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\".*\"" , reCompiled = Just (compileRegex False "\".*\"") , reCaseSensitive = False } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "'.*'" , reCompiled = Just (compileRegex False "'.*'") , reCaseSensitive = False } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[|>]\\s*[|>]\\s*[|>]\\s*[|>]\\s*[|>]\\s*[|>].*" , reCompiled = Just (compileRegex False "[|>]\\s*[|>]\\s*[|>]\\s*[|>]\\s*[|>]\\s*[|>].*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[|>]\\s*[|>]\\s*[|>]\\s*[|>]\\s*[|>].*" , reCompiled = Just (compileRegex False "[|>]\\s*[|>]\\s*[|>]\\s*[|>]\\s*[|>].*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[|>]\\s*[|>]\\s*[|>]\\s*[|>].*" , reCompiled = Just (compileRegex False "[|>]\\s*[|>]\\s*[|>]\\s*[|>].*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[|>]\\s*[|>]\\s*[|>].*" , reCompiled = Just (compileRegex False "[|>]\\s*[|>]\\s*[|>].*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[|>]\\s*[|>].*" , reCompiled = Just (compileRegex False "[|>]\\s*[|>].*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[|>].*" , reCompiled = Just (compileRegex False "[|>].*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "([A-Za-z0-9+/][A-Za-z0-9+/][A-Za-z0-9+/][A-Za-z0-9+/]){10,20}$" , reCompiled = Just (compileRegex False "([A-Za-z0-9+/][A-Za-z0-9+/][A-Za-z0-9+/][A-Za-z0-9+/]){10,20}$") , reCaseSensitive = False } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[A-Za-z0-9+=/]+=$" , reCompiled = Just (compileRegex False "[A-Za-z0-9+=/]+=$") , reCaseSensitive = False } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(- )?--(--.*)?" , reCompiled = Just (compileRegex False "(- )?--(--.*)?") , reCaseSensitive = False } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Carl A Joslin (carl.joslin@joslin.dyndns.org)" , sVersion = "2" , sLicense = "GPL" , sExtensions = [ "*.eml" ] , sStartingContext = "headder" }