{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Ini (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"INI Files\", sFilename = \"ini.xml\", sShortname = \"Ini\", sContexts = fromList [(\"Comment\",Context {cName = \"Comment\", cSyntax = \"INI Files\", 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}),(\"Value\",Context {cName = \"Value\", cSyntax = \"INI Files\", cRules = [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 = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"Default\",\"Defaults\",\"E_ALL\",\"E_COMPILE_ERROR\",\"E_COMPILE_WARNING\",\"E_CORE_ERROR\",\"E_CORE_WARNING\",\"E_ERROR\",\"E_NOTICE\",\"E_PARSE\",\"E_STRICT\",\"E_USER_ERROR\",\"E_USER_NOTICE\",\"E_USER_WARNING\",\"E_WARNING\",\"False\",\"Localhost\",\"No\",\"Normal\",\"Null\",\"Off\",\"On\",\"True\",\"Yes\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \";.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"ini\",Context {cName = \"ini\", cSyntax = \"INI Files\", cRules = [Rule {rMatcher = RangeDetect '[' ']', rAttribute = KeywordTok, 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 = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"INI Files\",\"Value\")]},Rule {rMatcher = DetectChar ';', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"INI Files\",\"Comment\")]},Rule {rMatcher = DetectChar '#', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"INI Files\",\"Comment\")]}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False})], sAuthor = \"Jan Janssen (medhefgo@web.de)\", sVersion = \"2\", sLicense = \"LGPL\", sExtensions = [\"*.ini\",\"*.pls\",\"*.kcfgc\"], sStartingContext = \"ini\"}"