{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Email (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Email\", sFilename = \"email.xml\", sShortname = \"Email\", sContexts = fromList [(\"headder\",Context {cName = \"headder\", cSyntax = \"Email\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[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:.*$\", 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]:.*$\", 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]:.*$\", 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:.*$\", 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:.*$\", 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:\", 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:\", 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]:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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]:\", 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]:\", 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]:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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]:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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:\", 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-.]+:\", 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.\\\\-]+\", 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.\\\\-]+>\", 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.\\\\-]+>\", reCaseSensitive = False}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\".*\\\"\", reCaseSensitive = False}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"'.*'\", 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*[|>].*\", 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*[|>].*\", 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*[|>].*\", 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*[|>].*\", 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*[|>].*\", reCaseSensitive = False}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[|>].*\", 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}$\", 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+=/]+=$\", reCaseSensitive = False}), rAttribute = RegionMarkerTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(- )?--(--.*)?\", 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\"}"