{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Bibtex (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"BibTeX\", sFilename = \"bibtex.xml\", sShortname = \"Bibtex\", sContexts = fromList [(\"CurlyBracket\",Context {cName = \"CurlyBracket\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"CurlyBracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\([a-zA-Z@]+|[^ ])\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"}$\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = DetectChar '}', rAttribute = NormalTok, 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}),(\"Entry\",Context {cName = \"Entry\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z0-9_@\\\\\\\\-\\\\\\\\:]+\", reCaseSensitive = True}), rAttribute = OtherTok, 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 (\"BibTeX\",\"Field\")]},Rule {rMatcher = DetectChar '}', rAttribute = NormalTok, 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}),(\"Field\",Context {cName = \"Field\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z0-9\\\\-_\\\\.]+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, 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 = []},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, 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 (\"BibTeX\",\"CurlyBracket\")]},Rule {rMatcher = DetectChar '}', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '\"', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"QuotedText\")]},Rule {rMatcher = DetectChar ',', rAttribute = NormalTok, 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 = []},Rule {rMatcher = RegExpr (RE {reString = \"[0-9]+\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z0-9\\\\-]+\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \".\", 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}),(\"Normal\",Context {cName = \"Normal\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[]^{|}~\"}) (CaseInsensitiveWords (fromList [\"@article\",\"@book\",\"@booklet\",\"@collection\",\"@company\",\"@conference\",\"@electronic\",\"@inbook\",\"@incollection\",\"@inproceedings\",\"@manual\",\"@mastersthesis\",\"@misc\",\"@online\",\"@patent\",\"@periodical\",\"@person\",\"@phdthesis\",\"@place\",\"@proceedings\",\"@report\",\"@set\",\"@techreport\",\"@thesis\",\"@unpublished\",\"@www\"])), rAttribute = VariableTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"Entry\")]},Rule {rMatcher = StringDetect \"@string\", rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"StringCommand\")]},Rule {rMatcher = StringDetect \"@preamble\", rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"PreambleCommand\")]},Rule {rMatcher = StringDetect \"@comment\", rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"PreambleCommand\",Context {cName = \"PreambleCommand\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"CurlyBracket\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"QuotedText\",Context {cName = \"QuotedText\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\([a-zA-Z@]+|[^ ])\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"StringCommand\",Context {cName = \"StringCommand\", cSyntax = \"BibTeX\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"CurlyBracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z0-9\\\\-]+\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"BibTeX\",\"CurlyBracket\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False})], sAuthor = \"Jeroen Wijnhout (Jeroen.Wijnhout@kdemail.net)+Thomas Braun (thomas.braun@virtuell-zuhause.de)\", sVersion = \"2\", sLicense = \"LGPL\", sExtensions = [\"*.bib\"], sStartingContext = \"Normal\"}"