{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Mediawiki (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "MediaWiki" , sFilename = "mediawiki.xml" , sShortname = "Mediawiki" , sContexts = fromList [ ( "Bold" , Context { cName = "Bold" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "BoldItalic" ) ] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "BoldUnderlined" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBold" ) , 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 } ) , ( "BoldItalic" , Context { cName = "BoldItalic" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "BoldItalicUnderlined" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBoldItalic" ) , 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 } ) , ( "BoldItalicUnderlined" , Context { cName = "BoldItalicUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , 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 = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBoldItalicUnderlined" ) , 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 } ) , ( "BoldUnderlined" , Context { cName = "BoldUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , 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 = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "BoldUnderlinedItalic" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBoldUnderlined" ) , 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 } ) , ( "BoldUnderlinedItalic" , Context { cName = "BoldUnderlinedItalic" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBoldItalicUnderlined" ) , 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 } ) , ( "DefinitionListHeader" , Context { cName = "DefinitionListHeader" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = DetectChar ':' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = KeywordTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "DelimitedURL" , Context { cName = "DelimitedURL" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = DetectChar ']' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '[' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])" , reCompiled = Just (compileRegex True "(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "DelimitedUrlLink" ) ] } , Rule { rMatcher = DetectChar ' ' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "URLTag" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "DelimitedUrlLink" , Context { cName = "DelimitedUrlLink" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ' ' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar ']' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindHtmlEntities" , Context { cName = "FindHtmlEntities" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "&(#[0-9]+|#[xX][0-9A-Fa-f]+|(?![0-9])[\\w_:][\\w.:_-]*);" , reCompiled = Just (compileRegex True "&(#[0-9]+|#[xX][0-9A-Fa-f]+|(?![0-9])[\\w_:][\\w.:_-]*);") , reCaseSensitive = True } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindHtmlStartTagAttributes" , Context { cName = "FindHtmlStartTagAttributes" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(?![0-9])[\\w_:][\\w.:_-]*" , reCompiled = Just (compileRegex True "(?![0-9])[\\w_:][\\w.:_-]*") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "MediaWiki" , "HtmlAttribute" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s+(?![0-9])[\\w_:][\\w.:_-]*" , reCompiled = Just (compileRegex True "\\s+(?![0-9])[\\w_:][\\w.:_-]*") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "HtmlAttribute" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindListItem" , Context { cName = "FindListItem" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[*#;:\\s]*[*#:]+" , reCompiled = Just (compileRegex True "[*#;:\\s]*[*#:]+") , reCaseSensitive = True } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindSyntaxHighlightingHtmlElement" , Context { cName = "FindSyntaxHighlightingHtmlElement" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "Underlined" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindTextDecorationsInHeader" , Context { cName = "FindTextDecorationsInHeader" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = StringDetect "'''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "Bold" ) ] } , Rule { rMatcher = StringDetect "''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "BoldItalic" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindUrl" , Context { cName = "FindUrl" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])" , reCompiled = Just (compileRegex True "\\[(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])") , reCaseSensitive = True } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "DelimitedURL" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])" , reCompiled = Just (compileRegex True "(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "LooseURL" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindUrlWithinTemplate" , Context { cName = "FindUrlWithinTemplate" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])" , reCompiled = Just (compileRegex True "\\[(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])") , reCaseSensitive = True } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "DelimitedURL" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])" , reCompiled = Just (compileRegex True "(http:|https:|ftp:|mailto:)[^]| ]*(?=$|[]|\\s])") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "LooseURLWithinTemplate" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLink" , Context { cName = "FindWikiLink" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = Detect2Chars '[' '[' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLink" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingBold" , Context { cName = "FindWikiLinkBeingBold" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingBoldItalic" , Context { cName = "FindWikiLinkBeingBoldItalic" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldItalicWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldItalicWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingBoldItalicUnderlined" , Context { cName = "FindWikiLinkBeingBoldItalicUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldItalicUnderlinedWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldItalicUnderlinedWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingBoldUnderlined" , Context { cName = "FindWikiLinkBeingBoldUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldUnderlinedWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkBoldUnderlinedWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingItalic" , Context { cName = "FindWikiLinkBeingItalic" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkItalicWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkItalicWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingItalicUnderlined" , Context { cName = "FindWikiLinkBeingItalicUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkItalicUnderlinedWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkItalicUnderlinedWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindWikiLinkBeingUnderlined" , Context { cName = "FindWikiLinkBeingUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\|[^]]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\|[^]]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkUnderlinedWithDescription" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[[^]|]*\\]\\]" , reCompiled = Just (compileRegex True "\\[\\[[^]|]*\\]\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "WikiLinkUnderlinedWithoutDescription" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HtmlAttribute" , Context { cName = "HtmlAttribute" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = DetectChar '=' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "HtmlValue" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HtmlValue" , Context { cName = "HtmlValue" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "ValueWithDoubleQuotes" ) ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "ValueWithSingleQuotes" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Italic" , Context { cName = "Italic" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "ItalicBold" ) ] } , Rule { rMatcher = StringDetect "''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "ItalicUnderlined" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingItalic" ) , 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 } ) , ( "ItalicBold" , Context { cName = "ItalicBold" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "" , reCompiled = Just (compileRegex True "") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "BoldItalicUnderlined" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBoldItalic" ) , 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 } ) , ( "ItalicUnderlined" , Context { cName = "ItalicUnderlined" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , 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 = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "'''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "ItalicUnderlinedBold" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingItalicUnderlined" ) , 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 } ) , ( "ItalicUnderlinedBold" , Context { cName = "ItalicUnderlinedBold" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindWikiLinkBeingBoldItalicUnderlined" ) , 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 } ) , ( "JavaScriptSourceContent" , Context { cName = "JavaScriptSourceContent" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "SourceEnd" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "JavaScript" , "Normal" ) , 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 } ) , ( "JavaScriptSourceStartTag" , Context { cName = "JavaScriptSourceStartTag" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "JavaScriptSourceContent" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindHtmlStartTagAttributes" ) , 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 } ) , ( "JavaScriptSyntaxHighlightContent" , Context { cName = "JavaScriptSyntaxHighlightContent" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = StringDetect "" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "SyntaxHighlightEnd" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "JavaScript" , "Normal" ) , 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 } ) , ( "JavaScriptSyntaxHighlightStartTag" , Context { cName = "JavaScriptSyntaxHighlightStartTag" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MediaWiki" , "JavaScriptSyntaxHighlightContent" ) ] } , Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindHtmlStartTagAttributes" ) , 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 } ) , ( "LooseURL" , Context { cName = "LooseURL" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ' ' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "LooseURLWithinTemplate" , Context { cName = "LooseURLWithinTemplate" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = IncludeRules ( "MediaWiki" , "FindTemplate" ) , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '}' '}' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar ' ' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "NoWiki" , Context { cName = "NoWiki" , cSyntax = "MediaWiki" , cRules = [ 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 = StringDetect "" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[<][^>]+[>]" , reCompiled = Just (compileRegex True "[<][^>]+[>]") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "
"
                      , rAttribute = KeywordTok
                      , rIncludeAttribute = False
                      , rDynamic = False
                      , rCaseSensitive = True
                      , rChildren = []
                      , rLookahead = False
                      , rFirstNonspace = False
                      , rColumn = Nothing
                      , rContextSwitch = [ Push ( "MediaWiki" , "Pre" ) ]
                      }
                  ]
              , cAttribute = NormalTok
              , cLineEmptyContext = []
              , cLineEndContext = []
              , cLineBeginContext = []
              , cFallthrough = False
              , cFallthroughContext = []
              , cDynamic = False
              }
          )
        , ( "Pre"
          , Context
              { cName = "Pre"
              , cSyntax = "MediaWiki"
              , cRules =
                  [ Rule
                      { rMatcher = StringDetect "
" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Section2" , Context { cName = "Section2" , cSyntax = "MediaWiki" , 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 } ) , ( "normal" , Context { cName = "normal" , cSyntax = "MediaWiki" , cRules = [ Rule { rMatcher = StringDetect "