{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Xorg (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"x.org Configuration\", sFilename = \"xorg.xml\", sShortname = \"Xorg\", sContexts = fromList [(\"Comment\",Context {cName = \"Comment\", cSyntax = \"x.org Configuration\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Alerts\",\"\"), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectIdentifier, rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Keyword\",Context {cName = \"Keyword\", cSyntax = \"x.org Configuration\", cRules = [Rule {rMatcher = RangeDetect '\"' '\"', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RangeDetect '\\'' '\\'', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Float, rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Int, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\w\\\\d]+\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '#', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Comment\")]}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Section\",Context {cName = \"Section\", cSyntax = \"x.org Configuration\", cRules = [Rule {rMatcher = RangeDetect '\"' '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Section Content\")]},Rule {rMatcher = RangeDetect '\\'' '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Section Content\")]},Rule {rMatcher = DetectIdentifier, rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '#', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Comment\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Section Content\",Context {cName = \"Section Content\", cSyntax = \"x.org Configuration\", cRules = [Rule {rMatcher = StringDetect \"EndSection\", rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = StringDetect \"EndSubSection\", rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = StringDetect \"SubSection\", rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Section\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b\\\\w+\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Keyword\")]},Rule {rMatcher = DetectChar '#', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Comment\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"xorg\",Context {cName = \"xorg\", cSyntax = \"x.org Configuration\", cRules = [Rule {rMatcher = StringDetect \"Section\", rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Section\")]},Rule {rMatcher = DetectChar '#', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"x.org Configuration\",\"Comment\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False})], sAuthor = \"Jan Janssen (medhefgo@web.de)\", sVersion = \"2\", sLicense = \"LGPL\", sExtensions = [\"xorg.conf\"], sStartingContext = \"xorg\"}"