{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Texinfo (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Texinfo\", sFilename = \"texinfo.xml\", sShortname = \"Texinfo\", sContexts = fromList [(\"Normal Text\",Context {cName = \"Normal Text\", cSyntax = \"Texinfo\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"@c(omment)?\\\\b\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Texinfo\",\"singleLineComment\")]},Rule {rMatcher = RegExpr (RE {reString = \"@ignore\\\\b\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Texinfo\",\"multiLineComment\")]},Rule {rMatcher = RegExpr (RE {reString = \"@node\\\\b\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Texinfo\",\"nodeFolding\")]},Rule {rMatcher = RegExpr (RE {reString = \"@(menu|smallexample|table|multitable)\\\\b\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Texinfo\",\"folding\")]},Rule {rMatcher = RegExpr (RE {reString = \"@[\\\\w]+(\\\\{([\\\\w]+[\\\\s]*)+\\\\})?\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"folding\",Context {cName = \"folding\", cSyntax = \"Texinfo\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"@end (menu|smallexample|table|multitable)\\\\b\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Texinfo\",\"Normal Text\"), 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}),(\"multiLineComment\",Context {cName = \"multiLineComment\", cSyntax = \"Texinfo\", cRules = [Rule {rMatcher = StringDetect \"@end ignore\", rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Alerts\",\"\"), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"nodeFolding\",Context {cName = \"nodeFolding\", cSyntax = \"Texinfo\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"@node\\\\b\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Texinfo\",\"Normal Text\"), 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}),(\"singleLineComment\",Context {cName = \"singleLineComment\", cSyntax = \"Texinfo\", cRules = [Rule {rMatcher = IncludeRules (\"Alerts\",\"\"), 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})], sAuthor = \"Daniel Franke (franke.daniel@gmail.com)\", sVersion = \"1\", sLicense = \"LGPL\", sExtensions = [\"*.texi\"], sStartingContext = \"Normal Text\"}"