{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Lilypond (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"LilyPond\", sFilename = \"lilypond.xml\", sShortname = \"Lilypond\", sContexts = fromList [(\"assignment\",Context {cName = \"assignment\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(dash(Hat|Plus|Dash|Bar|Larger|Dot|Underscore)|fermataMarkup|pipeSymbol|slashSeparator)\\\\b\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"[a-z]+\", reCaseSensitive = False}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"basic\",Context {cName = \"basic\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Detect2Chars '%' '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"commentblock\")]},Rule {rMatcher = DetectChar '%', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"commentline\")]},Rule {rMatcher = DetectChar '\"', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"string\")]},Rule {rMatcher = DetectChar '#', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"scheme\")]},Rule {rMatcher = DetectChar '$', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemesub\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"chord\",Context {cName = \"chord\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '>', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chordend\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z]))\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chordpitch\")]},Rule {rMatcher = AnyChar \"<{}srR\", rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"music\"), 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}),(\"chordend\",Context {cName = \"chordend\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\\\\\(longa|breve)\\\\b|(1|2|4|8|16|32|64|128|256|512|1024|2048)(?!\\\\d))(\\\\s*\\\\.+)?(\\\\s*\\\\*\\\\s*\\\\d+(/\\\\d+)?)*\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop,Pop], cDynamic = False}),(\"chordmode\",Context {cName = \"chordmode\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chordmode2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"chordmode2\",Context {cName = \"chordmode2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"chordrules\"), 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}),(\"chordpitch\",Context {cName = \"chordpitch\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"=\\\\s*('+|,+)?\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\\\\\(longa|breve)\\\\b|(1|2|4|8|16|32|64|128|256|512|1024|2048)(?!\\\\d))(\\\\s*\\\\.+)?(\\\\s*\\\\*\\\\s*\\\\d+(/\\\\d+)?)*\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\d+\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"chordrules\",Context {cName = \"chordrules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chordrules\")]},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \":?([\\\\.^]?\\\\d+[-+]?|(m|dim|aug|maj|sus)(?![A-Za-z]))*(/\\\\+?\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z])))?\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"music\"), 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}),(\"command\",Context {cName = \"command\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\note(mode|s)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"notemode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\drum(mode|s)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"drummode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\chord(mode|s)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chordmode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\figure(mode|s)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"figuremode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(lyric(mode|s)|addlyrics)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricmode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\lyricsto(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricsto\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\markup(lines)?(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"markup\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(header|paper|layout|midi|with)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"section\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(new|context|change)\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"context\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(un)?set\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"set\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(override(Property)?|revert)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"override\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\skip(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"duration\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\tempo(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"tempo\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(accepts|alias|consists|defaultchild|denies|description|grobdescriptions|include|invalid|language|name|objectid|once|remove|sequential|simultaneous|type|version|score|book|bookpart)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\((aiken|funk|sacredHarp|southernHarmony|walker)Heads(Minor)?)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(acciaccatura|addQuote|afterGrace|allowPageTurn|alternative|apply(Context|Music|Output)|appoggiatura|arpeggio(Arrow(Down|Up)|Bracket|Normal|Parenthesis)?|(a|de)scendens|auctum|augmentum|autoBeamO(ff|n)|autochange|balloon(Grob)?Text|bar|barNumberCheck|bendAfter|breathe|break|cadenzaO(ff|n)|cavum|clef(\\\\s+(treble|violin|G|alto|C|tenor|(sub)?bass|F|french|(mezzo)?soprano|(var)?baritone|percussion|tab))?|(end)?(de)?cr|cresc(TextCresc|Hairpin))(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\((cue|transposedCue)During|default|deminutum|dim(Text(Decresc|Decr|Dim)|Hairpin)|display(Lily)?Music|divisio(Maior|Maxima|Minima)|(dynamic|dots|phrasingSlur|slur|stem|tie|tuplet)(Down|Neutral|Up)|(balloon|text)LengthO(ff|n)|featherDurations|figure(mode|s)|finalis|flexa|(french|german|italian|semiGerman)Chords|glissando|grace|harmonic|(unH|h)ideNotes|(hide|show)StaffSwitch|inclinatum|(keep|remove)WithTag|key(\\\\s+\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z])))?|killCues)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(label|laissezVibrer|linea|makeClusters|mark|maxima|melisma(End)?|mergeDifferently(Head|Dott)edO(ff|n)|newSpacingSection|no(Beam|Break|PageBreak|PageTurn)|normalsize|numericTimeSignature|octaveCheck|oneVoice|oriscus|ottava|page(-ref|Break|Turn)|parallelMusic|parenthesize|partcombine|partial(\\\\s*(\\\\\\\\(longa|breve)\\\\b|(1|2|4|8|16|32|64|128|256|512|1024|2048)(?!\\\\d))(\\\\s*\\\\.+)?(\\\\s*\\\\*\\\\s*\\\\d+(/\\\\d+)?)*)?|pes|pitchedTrill)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(pointAndClickO(ff|n)|quilisma|quoteDuring|relative(\\\\s+\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z])))?|RemoveEmptyStaffContext|repeat(\\\\s+(unfold|volta|tremolo|percent)(\\\\s+\\\\d+)?)?|repeatTie|resetRelativeOctave|rest|scaleDurations|scoreTweak|easyHeadsO(ff|n)|shift(Durations|Off|On{1,3})|(slur|tie)(Both|Dashed|Dotted|Solid)|small|spacingTweaks)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\((start|stop)(Group|(Text|Trill)Span|Staff)|stemBoth|stropha|super|(sustain|sostenuto)O(ff|n)|table-of-contents|tag|times?(\\\\s*\\\\d+/\\\\d+)?|tiny|tocItem)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(transpose(\\\\s+\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z]))\\\\s*\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z])))?|transposition(\\\\s+\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z]))))(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(tweak|unfoldRepeats|virg(ul)?a|voice(One|Two|Three|Four)|withMusicProperty|cm|mm|in|pt|major|minor|ionian|locrian|aeolian|mixolydian|lydian|phrygian|dorian)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(dash(Hat|Plus|Dash|Bar|Larger|Dot|Underscore)|fermataMarkup|pipeSymbol|slashSeparator)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(consistsend)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(arpeggio(Up|Down|Neutral)|newpage|script(Up|Down|Both)|(empty|fat)Text|setEasyHeads|(default|voice|modernVoice|piano|forget)Accidentals|(modern(Voice)?|piano)Cautionaries|noResetKey|compressMusic|octave|(sustain|sostenuto)(Down|Up)|set(Hairpin|Text)(Cresc|Decresc|Dim)|setTextDecr)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(translator|newcontext)\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"context\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\property(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"override\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[A-Za-z]+\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '\\\\', rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"commentblock\",Context {cName = \"commentblock\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Detect2Chars '%' '}', 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}),(\"commentline\",Context {cName = \"commentline\", cSyntax = \"LilyPond\", 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}),(\"connect\",Context {cName = \"connect\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = AnyChar \".-+|>^_12345\", rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"context\",Context {cName = \"context\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"ChoirStaff\",\"ChordNames\",\"CueVoice\",\"Devnull\",\"DrumStaff\",\"DrumVoice\",\"Dynamics\",\"FiguredBass\",\"FretBoards\",\"Global\",\"GrandStaff\",\"GregorianTranscriptionStaff\",\"GregorianTranscriptionVoice\",\"Lyrics\",\"MensuralStaff\",\"MensuralVoice\",\"NoteNames\",\"PianoStaff\",\"RhythmicStaff\",\"Score\",\"Staff\",\"StaffGroup\",\"TabStaff\",\"TabVoice\",\"Timing\",\"VaticanaStaff\",\"VaticanaVoice\",\"Voice\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"context2\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"InnerChoirStaff\",\"InnerStaffGroup\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"context2\")]},Rule {rMatcher = RegExpr (RE {reString = \"[A-Za-z]+\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"context2\")]},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"section2\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"context2\",Context {cName = \"context2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"=(\\\\s*[A-Za-z]+)?\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop,Pop], cDynamic = False}),(\"default\",Context {cName = \"default\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Detect2Chars '<' '<', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '>' '>', rAttribute = KeywordTok, 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 = []},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, 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 = []},Rule {rMatcher = DetectChar '\\\\', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"command\")]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"basic\"), 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}),(\"drumchord\",Context {cName = \"drumchord\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"acousticbassdrum\",\"acousticsnare\",\"agh\",\"agl\",\"bassdrum\",\"bd\",\"bda\",\"boh\",\"bohm\",\"boho\",\"bol\",\"bolm\",\"bolo\",\"cab\",\"cabasa\",\"cb\",\"cgh\",\"cghm\",\"cgho\",\"cgl\",\"cglm\",\"cglo\",\"chinesecymbal\",\"cl\",\"claves\",\"closedhihat\",\"cowbell\",\"crashcymbal\",\"crashcymbala\",\"crashcymbalb\",\"cuim\",\"cuio\",\"cymc\",\"cymca\",\"cymcb\",\"cymch\",\"cymr\",\"cymra\",\"cymrb\",\"cyms\",\"da\",\"db\",\"dc\",\"dd\",\"de\",\"electricsnare\",\"fivedown\",\"fiveup\",\"fourdown\",\"fourup\",\"gui\",\"guil\",\"guiro\",\"guis\",\"halfopenhihat\",\"handclap\",\"hc\",\"hh\",\"hhc\",\"hhho\",\"hho\",\"hhp\",\"hiagogo\",\"hibongo\",\"hiconga\",\"highfloortom\",\"hightom\",\"hihat\",\"himidtom\",\"hisidestick\",\"hitimbale\",\"hiwoodblock\",\"loagogo\",\"lobongo\",\"loconga\",\"longguiro\",\"longwhistle\",\"losidestick\",\"lotimbale\",\"lowfloortom\",\"lowmidtom\",\"lowoodblock\",\"lowtom\",\"mar\",\"maracas\",\"mutecuica\",\"mutehibongo\",\"mutehiconga\",\"mutelobongo\",\"muteloconga\",\"mutetriangle\",\"onedown\",\"oneup\",\"opencuica\",\"openhibongo\",\"openhiconga\",\"openhihat\",\"openlobongo\",\"openloconga\",\"opentriangle\",\"pedalhihat\",\"rb\",\"ridebell\",\"ridecymbal\",\"ridecymbala\",\"ridecymbalb\",\"shortguiro\",\"shortwhistle\",\"sidestick\",\"sn\",\"sna\",\"snare\",\"sne\",\"splashcymbal\",\"ss\",\"ssh\",\"ssl\",\"tamb\",\"tambourine\",\"tamtam\",\"threedown\",\"threeup\",\"timh\",\"timl\",\"tomfh\",\"tomfl\",\"tomh\",\"toml\",\"tommh\",\"tomml\",\"tri\",\"triangle\",\"trim\",\"trio\",\"tt\",\"twodown\",\"twoup\",\"ua\",\"ub\",\"uc\",\"ud\",\"ue\",\"vibraslap\",\"vibs\",\"wbh\",\"wbl\",\"whl\",\"whs\"])), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"chord\"), 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}),(\"drummode\",Context {cName = \"drummode\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"drummode2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"drummode2\",Context {cName = \"drummode2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"drumrules\"), 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}),(\"drumrules\",Context {cName = \"drumrules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"drumrules\")]},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"<(?!<)\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"drumchord\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"acousticbassdrum\",\"acousticsnare\",\"agh\",\"agl\",\"bassdrum\",\"bd\",\"bda\",\"boh\",\"bohm\",\"boho\",\"bol\",\"bolm\",\"bolo\",\"cab\",\"cabasa\",\"cb\",\"cgh\",\"cghm\",\"cgho\",\"cgl\",\"cglm\",\"cglo\",\"chinesecymbal\",\"cl\",\"claves\",\"closedhihat\",\"cowbell\",\"crashcymbal\",\"crashcymbala\",\"crashcymbalb\",\"cuim\",\"cuio\",\"cymc\",\"cymca\",\"cymcb\",\"cymch\",\"cymr\",\"cymra\",\"cymrb\",\"cyms\",\"da\",\"db\",\"dc\",\"dd\",\"de\",\"electricsnare\",\"fivedown\",\"fiveup\",\"fourdown\",\"fourup\",\"gui\",\"guil\",\"guiro\",\"guis\",\"halfopenhihat\",\"handclap\",\"hc\",\"hh\",\"hhc\",\"hhho\",\"hho\",\"hhp\",\"hiagogo\",\"hibongo\",\"hiconga\",\"highfloortom\",\"hightom\",\"hihat\",\"himidtom\",\"hisidestick\",\"hitimbale\",\"hiwoodblock\",\"loagogo\",\"lobongo\",\"loconga\",\"longguiro\",\"longwhistle\",\"losidestick\",\"lotimbale\",\"lowfloortom\",\"lowmidtom\",\"lowoodblock\",\"lowtom\",\"mar\",\"maracas\",\"mutecuica\",\"mutehibongo\",\"mutehiconga\",\"mutelobongo\",\"muteloconga\",\"mutetriangle\",\"onedown\",\"oneup\",\"opencuica\",\"openhibongo\",\"openhiconga\",\"openhihat\",\"openlobongo\",\"openloconga\",\"opentriangle\",\"pedalhihat\",\"rb\",\"ridebell\",\"ridecymbal\",\"ridecymbala\",\"ridecymbalb\",\"shortguiro\",\"shortwhistle\",\"sidestick\",\"sn\",\"sna\",\"snare\",\"sne\",\"splashcymbal\",\"ss\",\"ssh\",\"ssl\",\"tamb\",\"tambourine\",\"tamtam\",\"threedown\",\"threeup\",\"timh\",\"timl\",\"tomfh\",\"tomfl\",\"tomh\",\"toml\",\"tommh\",\"tomml\",\"tri\",\"triangle\",\"trim\",\"trio\",\"tt\",\"twodown\",\"twoup\",\"ua\",\"ub\",\"uc\",\"ud\",\"ue\",\"vibraslap\",\"vibs\",\"wbh\",\"wbl\",\"whl\",\"whs\"])), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"duration\")]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"music\"), 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}),(\"duration\",Context {cName = \"duration\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\\\\\(longa|breve)\\\\b|(1|2|4|8|16|32|64|128|256|512|1024|2048)(?!\\\\d))(\\\\s*\\\\.+)?(\\\\s*\\\\*\\\\s*\\\\d+(/\\\\d+)?)*\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\d+\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"figure\",Context {cName = \"figure\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '>', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chordend\")]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"basic\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\markup(lines)?(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"markup\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\skip(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"duration\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"figuremode\",Context {cName = \"figuremode\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"figuremode2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"figuremode2\",Context {cName = \"figuremode2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"figurerules\"), 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}),(\"figurerules\",Context {cName = \"figurerules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"figurerules\")]},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '<', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"figure\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b[srR](?![A-Za-z])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"duration\")]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"default\"), 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}),(\"lilypond\",Context {cName = \"lilypond\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = IncludeRules (\"LilyPond\",\"music\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b[a-z]+\\\\s*=\", reCaseSensitive = False}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"assignment\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"lyricmode\",Context {cName = \"lyricmode\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricmode2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"lyricmode2\",Context {cName = \"lyricmode2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"lyricrules\"), 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}),(\"lyricrules\",Context {cName = \"lyricrules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricrules\")]},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\w+-{2,}|\\\\w+_{2,}|-{2,}\\\\w+|_{2,}\\\\w+)\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\\\\\(longa|breve)\\\\b|(1|2|4|8|16|32|64|128|256|512|1024|2048)(?!\\\\d))(\\\\s*\\\\.+)?(\\\\s*\\\\*\\\\s*\\\\d+(/\\\\d+)?)*\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(--|__|_)\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"default\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\S+\\\\}\", reCaseSensitive = True}), rAttribute = ErrorTok, 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}),(\"lyricsto\",Context {cName = \"lyricsto\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\"(\\\\\\\\[\\\"\\\\\\\\]|[^\\\"\\\\\\\\])+\\\"\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricsto2\")]},Rule {rMatcher = RegExpr (RE {reString = \"[A-Za-z]+\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricsto2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"lyricsto2\",Context {cName = \"lyricsto2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"lyricsto3\")]},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop,Pop], cDynamic = False}),(\"lyricsto3\",Context {cName = \"lyricsto3\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"lyricrules\"), 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}),(\"markup\",Context {cName = \"markup\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"markup2\")]},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\score\\\\b\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"notemode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(markup|bold|(rounded-)?box|bracket|caps|(center|general|left|right)-align|circle|((center|dir|left|right)-)?column|combine|concat|dynamic|fill-line|finger|fontCaps|(abs-)?fontsize|fraction|halign|hbracket|hcenter-in|hcenter|hspace|huge|italic|justify|larger?|line|lower|magnify|medium|normal-size-(sub|super)|normal-text|normalsize|number|on-the-fly|override|pad-(around|markup|to-box|x)|page-ref|postscript|put-adjacent|raise|roman|rotate|sans|small(er)?|smallCaps|sub|super|teeny|text|tiny|translate(-scaled)?|transparent|typewriter|underline|upright|vcenter|whiteout|with-(color|dimensions|url)|wordwrap|(markup|column-|justified-|override-|wordwrap-)lines|wordwrap-(string-)?internal)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(arrow-head|beam|char|(semi|sesqui|double)?(flat|sharp)|draw-(circle|line)|epsfile|eyeglasses|filled-box|fret-diagram(-terse|-verbose)?|fromproperty|harp-pedal|(justify|wordwrap)-(field|string)|left-brace|lookup|markalphabet|markletter|musicglyph|natural|note-by-number|note|null|path|right-brace|simple|(back)?slashed-digit|stencil|strut|tied-lyric|triangle|verbatim-file)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, 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 (\"LilyPond\",\"scheme\")]},Rule {rMatcher = RegExpr (RE {reString = \"[^\\\"\\\\s\\\\\\\\#%{}$]+\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"markup2\",Context {cName = \"markup2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"markuprules\"), 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}),(\"markuprules\",Context {cName = \"markuprules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"markuprules\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\score\\\\b\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"notemode\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(arrow-head|beam|char|(semi|sesqui|double)?(flat|sharp)|draw-(circle|line)|epsfile|eyeglasses|filled-box|fret-diagram(-terse|-verbose)?|fromproperty|harp-pedal|(justify|wordwrap)-(field|string)|left-brace|lookup|markalphabet|markletter|musicglyph|natural|note-by-number|note|null|path|right-brace|simple|(back)?slashed-digit|stencil|strut|tied-lyric|triangle|verbatim-file|markup|bold|(rounded-)?box|bracket|caps|(center|general|left|right)-align|circle|((center|dir|left|right)-)?column|combine|concat|dynamic|fill-line|finger|fontCaps|(abs-)?fontsize|fraction|halign|hbracket|hcenter-in|hcenter|hspace|huge|italic|justify|larger?|line|lower|magnify|medium|normal-size-(sub|super)|normal-text|normalsize|number|on-the-fly|override|pad-(around|markup|to-box|x)|page-ref|postscript|put-adjacent|raise|roman|rotate|sans|small(er)?|smallCaps|sub|super|teeny|text|tiny|translate(-scaled)?|transparent|typewriter|underline|upright|vcenter|whiteout|with-(color|dimensions|url)|wordwrap|(markup|column-|justified-|override-|wordwrap-)lines|wordwrap-(string-)?internal)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(bigger|h?center)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[A-Za-z]+(-[A-Za-z]+)*\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"basic\"), 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}),(\"music\",Context {cName = \"music\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = AnyChar \"()~\", rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"[]\", rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"-_^\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"connect\")]},Rule {rMatcher = DetectChar '\\\\', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"musiccommand\")]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"default\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '<', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"chord\")]},Rule {rMatcher = DetectChar '>', rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[a-z]+\\\\d+\\\\.*[,']+\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\b[srR](?![A-Za-z])|\\\\b([a-h]((iss){1,2}|(ess){1,2}|(is){1,2}|(es){1,2}|(sharp){1,2}|(flat){1,2}|ss?|ff?)?|(do|re|mi|fa|sol|la|si)(dd?|bb?|ss?|kk?)?|q)('+|,+|(?![A-Za-z])))\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"pitch\")]},Rule {rMatcher = RegExpr (RE {reString = \":\\\\d*\", reCaseSensitive = True}), 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}),(\"musiccommand\",Context {cName = \"musiccommand\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(p{1,5}|mp|mf|f{1,5}|s?fp|sff?|spp?|[sr]?fz|cresc|decresc|dim)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[]\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\(\\\\d+|accent|marcato|staccat(issim)?o|espressivo|tenuto|portato|(up|down)(bow|mordent|prall)|flageolet|thumb|[lr](heel|toe)|open|stopped|turn|reverseturn|trill|mordent|prall(prall|mordent|down|up)?|lineprall|signumcongruentiae|(short|long|verylong)?fermata|segno|(var)?coda|snappizzicato|halfopen)(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[()]\", 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 = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"command\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"notemode\",Context {cName = \"notemode\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"notemode2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"notemode2\",Context {cName = \"notemode2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"noterules\"), 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}),(\"noterules\",Context {cName = \"noterules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"noterules\")]},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"music\"), 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}),(\"override\",Context {cName = \"override\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"ChoirStaff\",\"ChordNames\",\"CueVoice\",\"Devnull\",\"DrumStaff\",\"DrumVoice\",\"Dynamics\",\"FiguredBass\",\"FretBoards\",\"Global\",\"GrandStaff\",\"GregorianTranscriptionStaff\",\"GregorianTranscriptionVoice\",\"Lyrics\",\"MensuralStaff\",\"MensuralVoice\",\"NoteNames\",\"PianoStaff\",\"RhythmicStaff\",\"Score\",\"Staff\",\"StaffGroup\",\"TabStaff\",\"TabVoice\",\"Timing\",\"VaticanaStaff\",\"VaticanaVoice\",\"Voice\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"InnerChoirStaff\",\"InnerStaffGroup\"])), rAttribute = DataTypeTok, 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 = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"Accidental\",\"AccidentalCautionary\",\"AccidentalPlacement\",\"AccidentalSuggestion\",\"Ambitus\",\"AmbitusAccidental\",\"AmbitusLine\",\"AmbitusNoteHead\",\"Arpeggio\",\"BalloonTextItem\",\"BarLine\",\"BarNumber\",\"BassFigure\",\"BassFigureAlignment\",\"BassFigureAlignmentPositioning\",\"BassFigureBracket\",\"BassFigureContinuation\",\"BassFigureLine\",\"Beam\",\"BendAfter\",\"BreakAlignGroup\",\"BreakAlignment\",\"BreathingSign\",\"ChordName\",\"Clef\",\"ClusterSpanner\",\"ClusterSpannerBeacon\",\"CombineTextScript\",\"Custos\",\"DotColumn\",\"Dots\",\"DoublePercentRepeat\",\"DoublePercentRepeatCounter\",\"DynamicLineSpanner\",\"DynamicText\",\"DynamicTextSpanner\",\"Episema\",\"Fingering\",\"FretBoard\",\"Glissando\",\"GraceSpacing\",\"GridLine\",\"GridPoint\",\"Hairpin\",\"HarmonicParenthesesItem\",\"HorizontalBracket\",\"InstrumentName\",\"InstrumentSwitch\",\"KeyCancellation\",\"KeySignature\",\"LaissezVibrerTie\",\"LaissezVibrerTieColumn\",\"LedgerLineSpanner\",\"LeftEdge\",\"LigatureBracket\",\"LyricExtender\",\"LyricHyphen\",\"LyricSpace\",\"LyricText\",\"MeasureGrouping\",\"MelodyItem\",\"MensuralLigature\",\"MetronomeMark\",\"MultiMeasureRest\",\"MultiMeasureRestNumber\",\"MultiMeasureRestText\",\"NonMusicalPaperColumn\",\"NoteCollision\",\"NoteColumn\",\"NoteHead\",\"NoteName\",\"NoteSpacing\",\"OctavateEight\",\"OttavaBracket\",\"PaperColumn\",\"ParenthesesItem\",\"PercentRepeat\",\"PercentRepeatCounter\",\"PhrasingSlur\",\"PianoPedalBracket\",\"RehearsalMark\",\"RepeatSlash\",\"RepeatTie\",\"RepeatTieColumn\",\"Rest\",\"RestCollision\",\"Script\",\"ScriptColumn\",\"ScriptRow\",\"SeparationItem\",\"Slur\",\"SostenutoPedal\",\"SostenutoPedalLineSpanner\",\"SpacingSpanner\",\"SpanBar\",\"StaffGrouper\",\"StaffSpacing\",\"StaffSymbol\",\"StanzaNumber\",\"Stem\",\"StemTremolo\",\"StringNumber\",\"StrokeFinger\",\"SustainPedal\",\"SustainPedalLineSpanner\",\"System\",\"SystemStartBar\",\"SystemStartBrace\",\"SystemStartBracket\",\"SystemStartSquare\",\"TabNoteHead\",\"TextScript\",\"TextSpanner\",\"Tie\",\"TieColumn\",\"TimeSignature\",\"TrillPitchAccidental\",\"TrillPitchGroup\",\"TrillPitchHead\",\"TrillSpanner\",\"TupletBracket\",\"TupletNumber\",\"UnaCordaPedal\",\"UnaCordaPedalLineSpanner\",\"VaticanaLigature\",\"VerticalAlignment\",\"VerticalAxisGroup\",\"VoiceFollower\",\"VoltaBracket\",\"VoltaBracketSpanner\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"[A-Za-z]+(?=\\\\s*\\\\.)\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[A-Za-z]+\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"pitch\",Context {cName = \"pitch\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"=\\\\s*('+|,+)?\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"!?\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"duration\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"scheme\",Context {cName = \"scheme\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Push (\"LilyPond\",\"scheme2\")], cDynamic = False}),(\"scheme2\",Context {cName = \"scheme2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '(', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"scheme3\")]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"schemerules\"), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectSpaces, rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [Pop,Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"scheme3\",Context {cName = \"scheme3\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"schemerules\"), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"schemecommentblock\",Context {cName = \"schemecommentblock\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Detect2Chars '!' '#', 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}),(\"schemecommentline\",Context {cName = \"schemecommentline\", cSyntax = \"LilyPond\", 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}),(\"schemelily\",Context {cName = \"schemelily\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = Detect2Chars '#' '}', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"lilypond\"), 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}),(\"schemequote\",Context {cName = \"schemequote\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(define|defined\\\\?|define\\\\*(-public)?|define-(\\\\*|builtin-markup-(list-)?command|class|(extra-)?display-method|fonts?|grob-property|ly-syntax(-loc|-simple)?|macro(-public)?|markup-(list-)command|method|module|music-function|post-event-display-method|public(-macro|-toplevel)?|safe-public|span-event-display-method)|defmacro(\\\\*(-public)?)?|lambda\\\\*?|and|or|if|cond|case|let\\\\*?|letrec|begin|do|delay|set!|else|(quasi)?quote|unquote(-splicing)?|(define|let|letrec)-syntax|syntax-rules)(?=($|\\\\s|\\\\)))\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(not|boolean\\\\?|eq\\\\?|eqv\\\\?|equal\\\\?|pair\\\\?|cons|set-c[ad]r!|c[ad]{1,4}r|null\\\\?|list\\\\?|list|length|append|reverse|list-ref|mem[qv]|member|ass[qv]|assoc|symbol\\\\?|symbol->string|string->symbol|number\\\\?|complex\\\\?|real\\\\?|rational\\\\?|integer\\\\?|exact\\\\?|inexact\\\\?|zero\\\\?|positive\\\\?|negative\\\\?|odd\\\\?|even\\\\?|max|min|abs|quotient|remainder|modulo|gcd|lcm|numerator|denominator|floor|ceiling|truncate|round|rationalize|exp|log|sin|cos|tan|asin|acos|atan|sqrt|expt|make-rectangular|make-polar|real-part|imag-part|magnitude|angle|exact->inexact|inexact->exact|number->string|string->number)(?=($|\\\\s|\\\\)))\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(char((-ci)?(=\\\\?|<\\\\?|>\\\\?|<=\\\\?|>=\\\\?)|-alphabetic\\\\?|\\\\?|-numeric\\\\?|-whitespace\\\\?|-upper-case\\\\?|-lower-case\\\\?|->integer|-upcase|-downcase|-ready\\\\?)|integer->char|make-string|string(\\\\?|-copy|-fill!|-length|-ref|-set!|(-ci)?(=\\\\?|<\\\\?|>\\\\?|<=\\\\?|>=\\\\?)|-append)|substring|make-vector|vector(\\\\?|-length|-ref|-set!|-fill!)?|procedure\\\\?|apply|map|for-each|force|call-with-(current-continuation|(in|out)put-file)|(in|out)put-port\\\\?|current-(in|out)put-port|open-(in|out)put-file|close-(in|out)put-port|eof-object\\\\?|read|(read|peek)-char|write(-char)?|display|newline|call/cc|list-tail|string->list|list->string|vector->list|list->vector|with-input-from-file|with-output-to-file|load|transcript-(on|off)|eval|dynamic-wind|port\\\\?|values|call-with-values|(scheme-report-|null-|interaction-)environment)(?=($|\\\\s|\\\\)))\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"schemerules\",Context {cName = \"schemerules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '(', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemerules\")]},Rule {rMatcher = DetectChar ')', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '\"', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemestring\")]},Rule {rMatcher = DetectChar ';', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemecommentline\")]},Rule {rMatcher = DetectChar '$', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemesub\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemequote\")]},Rule {rMatcher = Detect2Chars '#' '!', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemecommentblock\")]},Rule {rMatcher = Detect2Chars '#' '{', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"schemelily\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"AbsoluteDynamicEvent\",\"AnnotateOutputEvent\",\"ApplyContext\",\"ApplyOutputEvent\",\"ArpeggioEvent\",\"ArticulationEvent\",\"AutoChangeMusic\",\"BarCheck\",\"BassFigureEvent\",\"BeamEvent\",\"BeamForbidEvent\",\"BendAfterEvent\",\"BreathingEvent\",\"ClusterNoteEvent\",\"ContextChange\",\"ContextSpeccedMusic\",\"CrescendoEvent\",\"DecrescendoEvent\",\"Event\",\"EventChord\",\"ExtenderEvent\",\"FingeringEvent\",\"GlissandoEvent\",\"GraceMusic\",\"HarmonicEvent\",\"HyphenEvent\",\"KeyChangeEvent\",\"LabelEvent\",\"LaissezVibrerEvent\",\"LigatureEvent\",\"LineBreakEvent\",\"LyricCombineMusic\",\"LyricEvent\",\"MarkEvent\",\"MultiMeasureRestEvent\",\"MultiMeasureRestMusic\",\"MultiMeasureTextEvent\",\"Music\",\"NoteEvent\",\"NoteGroupingEvent\",\"OverrideProperty\",\"PageBreakEvent\",\"PageTurnEvent\",\"PartCombineMusic\",\"PercentEvent\",\"PercentRepeatedMusic\",\"PesOrFlexaEvent\",\"PhrasingSlurEvent\",\"PropertySet\",\"PropertyUnset\",\"QuoteMusic\",\"RelativeOctaveCheck\",\"RelativeOctaveMusic\",\"RepeatTieEvent\",\"RepeatedMusic\",\"RestEvent\",\"RevertProperty\",\"ScriptEvent\",\"SequentialMusic\",\"SimultaneousMusic\",\"SkipEvent\",\"SkipMusic\",\"SlurEvent\",\"SoloOneEvent\",\"SoloTwoEvent\",\"SostenutoEvent\",\"SpacingSectionEvent\",\"SpanEvent\",\"StaffSpanEvent\",\"StringNumberEvent\",\"StrokeFingerEvent\",\"SustainEvent\",\"TextScriptEvent\",\"TextSpanEvent\",\"TieEvent\",\"TimeScaledMusic\",\"TransposedMusic\",\"TremoloEvent\",\"TremoloRepeatedMusic\",\"TremoloSpanEvent\",\"TrillSpanEvent\",\"TupletSpanEvent\",\"UnaCordaEvent\",\"UnfoldedRepeatedMusic\",\"UnisonoEvent\",\"UnrelativableMusic\",\"VoiceSeparator\",\"VoltaRepeatedMusic\"])), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"ChoirStaff\",\"ChordNames\",\"CueVoice\",\"Devnull\",\"DrumStaff\",\"DrumVoice\",\"Dynamics\",\"FiguredBass\",\"FretBoards\",\"Global\",\"GrandStaff\",\"GregorianTranscriptionStaff\",\"GregorianTranscriptionVoice\",\"Lyrics\",\"MensuralStaff\",\"MensuralVoice\",\"NoteNames\",\"PianoStaff\",\"RhythmicStaff\",\"Score\",\"Staff\",\"StaffGroup\",\"TabStaff\",\"TabVoice\",\"Timing\",\"VaticanaStaff\",\"VaticanaVoice\",\"Voice\"])), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"Accidental\",\"AccidentalCautionary\",\"AccidentalPlacement\",\"AccidentalSuggestion\",\"Ambitus\",\"AmbitusAccidental\",\"AmbitusLine\",\"AmbitusNoteHead\",\"Arpeggio\",\"BalloonTextItem\",\"BarLine\",\"BarNumber\",\"BassFigure\",\"BassFigureAlignment\",\"BassFigureAlignmentPositioning\",\"BassFigureBracket\",\"BassFigureContinuation\",\"BassFigureLine\",\"Beam\",\"BendAfter\",\"BreakAlignGroup\",\"BreakAlignment\",\"BreathingSign\",\"ChordName\",\"Clef\",\"ClusterSpanner\",\"ClusterSpannerBeacon\",\"CombineTextScript\",\"Custos\",\"DotColumn\",\"Dots\",\"DoublePercentRepeat\",\"DoublePercentRepeatCounter\",\"DynamicLineSpanner\",\"DynamicText\",\"DynamicTextSpanner\",\"Episema\",\"Fingering\",\"FretBoard\",\"Glissando\",\"GraceSpacing\",\"GridLine\",\"GridPoint\",\"Hairpin\",\"HarmonicParenthesesItem\",\"HorizontalBracket\",\"InstrumentName\",\"InstrumentSwitch\",\"KeyCancellation\",\"KeySignature\",\"LaissezVibrerTie\",\"LaissezVibrerTieColumn\",\"LedgerLineSpanner\",\"LeftEdge\",\"LigatureBracket\",\"LyricExtender\",\"LyricHyphen\",\"LyricSpace\",\"LyricText\",\"MeasureGrouping\",\"MelodyItem\",\"MensuralLigature\",\"MetronomeMark\",\"MultiMeasureRest\",\"MultiMeasureRestNumber\",\"MultiMeasureRestText\",\"NonMusicalPaperColumn\",\"NoteCollision\",\"NoteColumn\",\"NoteHead\",\"NoteName\",\"NoteSpacing\",\"OctavateEight\",\"OttavaBracket\",\"PaperColumn\",\"ParenthesesItem\",\"PercentRepeat\",\"PercentRepeatCounter\",\"PhrasingSlur\",\"PianoPedalBracket\",\"RehearsalMark\",\"RepeatSlash\",\"RepeatTie\",\"RepeatTieColumn\",\"Rest\",\"RestCollision\",\"Script\",\"ScriptColumn\",\"ScriptRow\",\"SeparationItem\",\"Slur\",\"SostenutoPedal\",\"SostenutoPedalLineSpanner\",\"SpacingSpanner\",\"SpanBar\",\"StaffGrouper\",\"StaffSpacing\",\"StaffSymbol\",\"StanzaNumber\",\"Stem\",\"StemTremolo\",\"StringNumber\",\"StrokeFinger\",\"SustainPedal\",\"SustainPedalLineSpanner\",\"System\",\"SystemStartBar\",\"SystemStartBrace\",\"SystemStartBracket\",\"SystemStartSquare\",\"TabNoteHead\",\"TextScript\",\"TextSpanner\",\"Tie\",\"TieColumn\",\"TimeSignature\",\"TrillPitchAccidental\",\"TrillPitchGroup\",\"TrillPitchHead\",\"TrillSpanner\",\"TupletBracket\",\"TupletNumber\",\"UnaCordaPedal\",\"UnaCordaPedalLineSpanner\",\"VaticanaLigature\",\"VerticalAlignment\",\"VerticalAxisGroup\",\"VoiceFollower\",\"VoltaBracket\",\"VoltaBracketSpanner\"])), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[-+]?(\\\\d+(\\\\.\\\\d+)?|\\\\.\\\\d+)\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"#(t|f|b[-+]?[01.]+|o[-+]?[0-7.]+|d[-+]?[0-9.]+|x[-+]?[0-9a-f.]+)\", reCaseSensitive = False}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = False, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[+-](inf|nan)\\\\.0\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(define|defined\\\\?|define\\\\*(-public)?|define-(\\\\*|builtin-markup-(list-)?command|class|(extra-)?display-method|fonts?|grob-property|ly-syntax(-loc|-simple)?|macro(-public)?|markup-(list-)command|method|module|music-function|post-event-display-method|public(-macro|-toplevel)?|safe-public|span-event-display-method)|defmacro(\\\\*(-public)?)?|lambda\\\\*?|and|or|if|cond|case|let\\\\*?|letrec|begin|do|delay|set!|else|(quasi)?quote|unquote(-splicing)?|(define|let|letrec)-syntax|syntax-rules)(?=($|\\\\s|\\\\)))\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(not|boolean\\\\?|eq\\\\?|eqv\\\\?|equal\\\\?|pair\\\\?|cons|set-c[ad]r!|c[ad]{1,4}r|null\\\\?|list\\\\?|list|length|append|reverse|list-ref|mem[qv]|member|ass[qv]|assoc|symbol\\\\?|symbol->string|string->symbol|number\\\\?|complex\\\\?|real\\\\?|rational\\\\?|integer\\\\?|exact\\\\?|inexact\\\\?|zero\\\\?|positive\\\\?|negative\\\\?|odd\\\\?|even\\\\?|max|min|abs|quotient|remainder|modulo|gcd|lcm|numerator|denominator|floor|ceiling|truncate|round|rationalize|exp|log|sin|cos|tan|asin|acos|atan|sqrt|expt|make-rectangular|make-polar|real-part|imag-part|magnitude|angle|exact->inexact|inexact->exact|number->string|string->number)(?=($|\\\\s|\\\\)))\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(char((-ci)?(=\\\\?|<\\\\?|>\\\\?|<=\\\\?|>=\\\\?)|-alphabetic\\\\?|\\\\?|-numeric\\\\?|-whitespace\\\\?|-upper-case\\\\?|-lower-case\\\\?|->integer|-upcase|-downcase|-ready\\\\?)|integer->char|make-string|string(\\\\?|-copy|-fill!|-length|-ref|-set!|(-ci)?(=\\\\?|<\\\\?|>\\\\?|<=\\\\?|>=\\\\?)|-append)|substring|make-vector|vector(\\\\?|-length|-ref|-set!|-fill!)?|procedure\\\\?|apply|map|for-each|force|call-with-(current-continuation|(in|out)put-file)|(in|out)put-port\\\\?|current-(in|out)put-port|open-(in|out)put-file|close-(in|out)put-port|eof-object\\\\?|read|(read|peek)-char|write(-char)?|display|newline|call/cc|list-tail|string->list|list->string|vector->list|list->vector|with-input-from-file|with-output-to-file|load|transcript-(on|off)|eval|dynamic-wind|port\\\\?|values|call-with-values|(scheme-report-|null-|interaction-)environment)(?=($|\\\\s|\\\\)))\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z#][^\\\\s(){}[\\\\];$\\\"]*\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"schemestring\",Context {cName = \"schemestring\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[0fnrtav\\\\\\\\\\\"]\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"schemesub\",Context {cName = \"schemesub\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z#][^\\\\s(){}[\\\\];$\\\"]*\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = DecValTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"section\",Context {cName = \"section\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"section2\")]},Rule {rMatcher = DetectSpaces, rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = KeywordTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"section2\",Context {cName = \"section2\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"LilyPond\",\"sectionrules\"), 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}),(\"sectionrules\",Context {cName = \"sectionrules\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"sectionrules\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"ChoirStaff\",\"ChordNames\",\"CueVoice\",\"Devnull\",\"DrumStaff\",\"DrumVoice\",\"Dynamics\",\"FiguredBass\",\"FretBoards\",\"Global\",\"GrandStaff\",\"GregorianTranscriptionStaff\",\"GregorianTranscriptionVoice\",\"Lyrics\",\"MensuralStaff\",\"MensuralVoice\",\"NoteNames\",\"PianoStaff\",\"RhythmicStaff\",\"Score\",\"Staff\",\"StaffGroup\",\"TabStaff\",\"TabVoice\",\"Timing\",\"VaticanaStaff\",\"VaticanaVoice\",\"Voice\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"InnerChoirStaff\",\"InnerStaffGroup\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\"?)\\\\b((Accidental|Ambitus|Arpeggio|Auto_beam|Axis_group|Balloon|Bar|Bar_number|Beam|Bend|Break_align|Breathing_sign|Chord_name|Chord_tremolo|Clef|Cluster_spanner|Collision|Completion_heads|Custos|Default_bar_line|Dot_column|Dots|Drum_notes|Dynami_align|Dynamic|Episema|Extender|Figured_bass|Figured_bass_position|Fingering|Font_size|Forbid_line_break|Fretboard|Glissando|Grace_beam|Grace|Grace_spacing|Grid_line_span|Grid_point|Grob_pq|Hara_kiri|Horizontal_bracket)_engraver)\\\\b\\\\1\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\"?)\\\\b((Hyphen|Instrument_name|Instrument_switch|Key|Laissez_vibrer|Ledger_line|Ligature_bracket|Lyric|Mark|Measure_grouping|Melody|Mensural_ligature|Metronome_mark|Multi_measure_rest|New_dynamic|New_fingering|Note_head_line|Note_heads|Note_name|Note_spacing|Ottava_spanner|Output_property|Page_turn|Paper_column|Parenthesis|Part_combine|Percent_repeat|Phrasing_slur|Piano_pedal_align|Piano_pedal|Pitch_squash|Pitched_trill|Repeat_acknowledge|Repeat_tie|Rest_collision|Rest|Rhythmic_column|Scheme|Script_column|Script|Script_row)_engraver)\\\\b\\\\1\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\"?)\\\\b((Separating_line_group|Slash_repeat|Slur|Spacing|Span_arpeggio|Span_bar|Spanner_break_forbid|Staff_collecting|Staff_symbol|Stanza_number_align|Stanza_number|Stem|String_number|Swallow|System_start_delimiter|Tab_harmonic|Tab_note_heads|Tab_staff_symbol|Text|Text_spanner|Tie|Time_signature|Trill_spanner|Tuplet|Tweak|Vaticana_ligature|Vertical_align|Vertically_spaced_contexts|Volta)_engraver)\\\\b\\\\1\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\"?)\\\\b((Beam|Control_track|Drum_note|Dynamic|Key|Lyric|Note|Piano_pedal|Slur|Staff|Swallow|Tempo|Tie|Time_signature)_performer)\\\\b\\\\1\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\"?)\\\\b((Note_swallow|Rest_swallow|Skip_event_swallow|Timing)_translator)\\\\b\\\\1\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"Accidental\",\"AccidentalCautionary\",\"AccidentalPlacement\",\"AccidentalSuggestion\",\"Ambitus\",\"AmbitusAccidental\",\"AmbitusLine\",\"AmbitusNoteHead\",\"Arpeggio\",\"BalloonTextItem\",\"BarLine\",\"BarNumber\",\"BassFigure\",\"BassFigureAlignment\",\"BassFigureAlignmentPositioning\",\"BassFigureBracket\",\"BassFigureContinuation\",\"BassFigureLine\",\"Beam\",\"BendAfter\",\"BreakAlignGroup\",\"BreakAlignment\",\"BreathingSign\",\"ChordName\",\"Clef\",\"ClusterSpanner\",\"ClusterSpannerBeacon\",\"CombineTextScript\",\"Custos\",\"DotColumn\",\"Dots\",\"DoublePercentRepeat\",\"DoublePercentRepeatCounter\",\"DynamicLineSpanner\",\"DynamicText\",\"DynamicTextSpanner\",\"Episema\",\"Fingering\",\"FretBoard\",\"Glissando\",\"GraceSpacing\",\"GridLine\",\"GridPoint\",\"Hairpin\",\"HarmonicParenthesesItem\",\"HorizontalBracket\",\"InstrumentName\",\"InstrumentSwitch\",\"KeyCancellation\",\"KeySignature\",\"LaissezVibrerTie\",\"LaissezVibrerTieColumn\",\"LedgerLineSpanner\",\"LeftEdge\",\"LigatureBracket\",\"LyricExtender\",\"LyricHyphen\",\"LyricSpace\",\"LyricText\",\"MeasureGrouping\",\"MelodyItem\",\"MensuralLigature\",\"MetronomeMark\",\"MultiMeasureRest\",\"MultiMeasureRestNumber\",\"MultiMeasureRestText\",\"NonMusicalPaperColumn\",\"NoteCollision\",\"NoteColumn\",\"NoteHead\",\"NoteName\",\"NoteSpacing\",\"OctavateEight\",\"OttavaBracket\",\"PaperColumn\",\"ParenthesesItem\",\"PercentRepeat\",\"PercentRepeatCounter\",\"PhrasingSlur\",\"PianoPedalBracket\",\"RehearsalMark\",\"RepeatSlash\",\"RepeatTie\",\"RepeatTieColumn\",\"Rest\",\"RestCollision\",\"Script\",\"ScriptColumn\",\"ScriptRow\",\"SeparationItem\",\"Slur\",\"SostenutoPedal\",\"SostenutoPedalLineSpanner\",\"SpacingSpanner\",\"SpanBar\",\"StaffGrouper\",\"StaffSpacing\",\"StaffSymbol\",\"StanzaNumber\",\"Stem\",\"StemTremolo\",\"StringNumber\",\"StrokeFinger\",\"SustainPedal\",\"SustainPedalLineSpanner\",\"System\",\"SystemStartBar\",\"SystemStartBrace\",\"SystemStartBracket\",\"SystemStartSquare\",\"TabNoteHead\",\"TextScript\",\"TextSpanner\",\"Tie\",\"TieColumn\",\"TimeSignature\",\"TrillPitchAccidental\",\"TrillPitchGroup\",\"TrillPitchHead\",\"TrillSpanner\",\"TupletBracket\",\"TupletNumber\",\"UnaCordaPedal\",\"UnaCordaPedalLineSpanner\",\"VaticanaLigature\",\"VerticalAlignment\",\"VerticalAxisGroup\",\"VoiceFollower\",\"VoltaBracket\",\"VoltaBracketSpanner\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"aDueText\",\"alignAboveContext\",\"alignBassFigureAccidentals\",\"alignBelowContext\",\"allowBeamBreak\",\"associatedVoice\",\"autoAccidentals\",\"autoBeamCheck\",\"autoBeamSettings\",\"autoBeaming\",\"autoCautionaries\",\"automaticBars\",\"barAlways\",\"barCheckSynchronize\",\"barNumberVisibility\",\"baseMoment\",\"bassFigureFormatFunction\",\"bassStaffProperties\",\"beamExceptions\",\"beatGrouping\",\"beatLength\",\"beatStructure\",\"chordChanges\",\"chordNameExceptions\",\"chordNameExceptionsFull\",\"chordNameExceptionsPartial\",\"chordNameFunction\",\"chordNameSeparator\",\"chordNoteNamer\",\"chordPrefixSpacer\",\"chordRootNamer\",\"clefGlyph\",\"clefOctavation\",\"clefPosition\",\"connectArpeggios\",\"countPercentRepeats\",\"createKeyOnClefChange\",\"createSpacing\",\"crescendoSpanner\",\"crescendoText\",\"currentBarNumber\",\"decrescendoSpanner\",\"decrescendoText\",\"defaultBarType\",\"doubleRepeatType\",\"doubleSlurs\",\"drumPitchTable\",\"drumStyleTable\",\"dynamicAbsoluteVolumeFunction\",\"explicitClefVisibility\",\"explicitKeySignatureVisibility\",\"extendersOverRests\",\"extraNatural\",\"figuredBassAlterationDirection\",\"figuredBassCenterContinuations\",\"figuredBassFormatter\",\"figuredBassPlusDirection\",\"fingeringOrientations\",\"firstClef\",\"followVoice\",\"fontSize\",\"forbidBreak\",\"forceClef\",\"gridInterval\",\"hairpinToBarline\",\"harmonicAccidentals\",\"highStringOne\",\"ignoreBarChecks\",\"ignoreFiguredBassRest\",\"ignoreMelismata\",\"implicitBassFigures\",\"implicitTimeSignatureVisibility\",\"instrumentCueName\",\"instrumentEqualizer\",\"instrumentName\",\"instrumentTransposition\",\"internalBarNumber\",\"keepAliveInterfaces\",\"keyAlterationOrder\",\"keySignature\",\"lyricMelismaAlignment\",\"majorSevenSymbol\",\"markFormatter\",\"maximumFretStretch\",\"measureLength\",\"measurePosition\",\"melismaBusyProperties\",\"metronomeMarkFormatter\",\"middleCClefPosition\",\"middleCOffset\",\"middleCPosition\",\"midiInstrument\",\"midiMaximumVolume\",\"midiMinimumVolume\",\"minimumFret\",\"minimumPageTurnLength\",\"minimumRepeatLengthForPageTurn\",\"noteToFretFunction\",\"ottavation\",\"output\",\"pedalSostenutoStrings\",\"pedalSostenutoStyle\",\"pedalSustainStrings\",\"pedalSustainStyle\",\"pedalUnaCordaStrings\",\"pedalUnaCordaStyle\",\"printKeyCancellation\",\"printOctaveNames\",\"printPartCombineTexts\",\"proportionalNotationDuration\",\"recordEventSequence\",\"rehearsalMark\",\"repeatCommands\",\"restNumberThreshold\",\"scriptDefinitions\",\"shapeNoteStyles\",\"shortInstrumentName\",\"shortVocalName\",\"skipBars\",\"skipTypesetting\",\"soloIIText\",\"soloText\",\"squashedPosition\",\"staffLineLayoutFunction\",\"stanza\",\"stemLeftBeamCount\",\"stemRightBeamCount\",\"stringNumberOrientations\",\"stringOneTopmost\",\"stringTunings\",\"strokeFingerOrientations\",\"subdivideBeams\",\"suggestAccidentals\",\"systemStartDelimiter\",\"systemStartDelimiterHierarchy\",\"tablatureFormat\",\"tempoUnitCount\",\"tempoUnitDuration\",\"tempoWholesPerMinute\",\"tieWaitForNote\",\"timeSignatureFraction\",\"timing\",\"tonic\",\"topLevelAlignment\",\"trebleStaffProperties\",\"tremoloFlags\",\"tupletFullLength\",\"tupletFullLengthNote\",\"tupletSpannerDuration\",\"useBassFigureExtenders\",\"verticallySpacedContexts\",\"vocalName\",\"voltaOnThisStaff\",\"voltaSpannerDuration\",\"whichBar\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(dedication|(sub){,2}title|poet|composer|meter|opus|arranger|instrument|piece|breakbefore|copyright|tagline|mutopia(title|composer|poet|opus|instrument)|date|enteredby|source|style|maintainer(Email|Web)?|moreInfo|lastupdated|texidoc|footer|(top|bottom|left|right)-margin|(foot|head)-separation|indent|short-indent|paper-(height|width)|horizontal-shift|line-width|(inner|outer)-margin|two-sided|binding-offset|(after|before|between)-title-space|between-system-(space|padding)|page-top-space|page-breaking-between-system-padding|(after|before|between)-title-spacing|between-(scores-)?system-spacing|bottom-system-spacing|top-title-spacing|top-system-spacing|page-breaking-between-system-spacing|system-count|(min-|max-)?systems-per-page|annotate-spacing|auto-first-page-number|blank-(last-)?page-force|first-page-number|page-count|page-limit-inter-system-space|page-limit-inter-system-space-factor|page-spacing-weight|print-all-headers|print-first-page-number|print-page-number|ragged-(bottom|right)|ragged-last(-bottom)?|system-separator-markup|force-assignment|input-encoding|output-scale|((even|odd)(Footer|Header)|(book|score|toc)Title|tocItem)Markup|system-count|(short-)?indent)\\\\b\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"barNumberAlignSymbol\",\"centralCPosition\",\"extraVerticalExtent\",\"fingerHorizontalDirection\",\"instr\",\"instrument\",\"keyAccidentalOrder\",\"minimumVerticalExtent\",\"rehearsalMarkAlignSymbol\",\"soloADue\",\"tupletNumberFormatFunction\",\"vocNam\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"default\"), 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}),(\"set\",Context {cName = \"set\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"ChoirStaff\",\"ChordNames\",\"CueVoice\",\"Devnull\",\"DrumStaff\",\"DrumVoice\",\"Dynamics\",\"FiguredBass\",\"FretBoards\",\"Global\",\"GrandStaff\",\"GregorianTranscriptionStaff\",\"GregorianTranscriptionVoice\",\"Lyrics\",\"MensuralStaff\",\"MensuralVoice\",\"NoteNames\",\"PianoStaff\",\"RhythmicStaff\",\"Score\",\"Staff\",\"StaffGroup\",\"TabStaff\",\"TabVoice\",\"Timing\",\"VaticanaStaff\",\"VaticanaVoice\",\"Voice\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"InnerChoirStaff\",\"InnerStaffGroup\"])), rAttribute = DataTypeTok, 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 = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"aDueText\",\"alignAboveContext\",\"alignBassFigureAccidentals\",\"alignBelowContext\",\"allowBeamBreak\",\"associatedVoice\",\"autoAccidentals\",\"autoBeamCheck\",\"autoBeamSettings\",\"autoBeaming\",\"autoCautionaries\",\"automaticBars\",\"barAlways\",\"barCheckSynchronize\",\"barNumberVisibility\",\"baseMoment\",\"bassFigureFormatFunction\",\"bassStaffProperties\",\"beamExceptions\",\"beatGrouping\",\"beatLength\",\"beatStructure\",\"chordChanges\",\"chordNameExceptions\",\"chordNameExceptionsFull\",\"chordNameExceptionsPartial\",\"chordNameFunction\",\"chordNameSeparator\",\"chordNoteNamer\",\"chordPrefixSpacer\",\"chordRootNamer\",\"clefGlyph\",\"clefOctavation\",\"clefPosition\",\"connectArpeggios\",\"countPercentRepeats\",\"createKeyOnClefChange\",\"createSpacing\",\"crescendoSpanner\",\"crescendoText\",\"currentBarNumber\",\"decrescendoSpanner\",\"decrescendoText\",\"defaultBarType\",\"doubleRepeatType\",\"doubleSlurs\",\"drumPitchTable\",\"drumStyleTable\",\"dynamicAbsoluteVolumeFunction\",\"explicitClefVisibility\",\"explicitKeySignatureVisibility\",\"extendersOverRests\",\"extraNatural\",\"figuredBassAlterationDirection\",\"figuredBassCenterContinuations\",\"figuredBassFormatter\",\"figuredBassPlusDirection\",\"fingeringOrientations\",\"firstClef\",\"followVoice\",\"fontSize\",\"forbidBreak\",\"forceClef\",\"gridInterval\",\"hairpinToBarline\",\"harmonicAccidentals\",\"highStringOne\",\"ignoreBarChecks\",\"ignoreFiguredBassRest\",\"ignoreMelismata\",\"implicitBassFigures\",\"implicitTimeSignatureVisibility\",\"instrumentCueName\",\"instrumentEqualizer\",\"instrumentName\",\"instrumentTransposition\",\"internalBarNumber\",\"keepAliveInterfaces\",\"keyAlterationOrder\",\"keySignature\",\"lyricMelismaAlignment\",\"majorSevenSymbol\",\"markFormatter\",\"maximumFretStretch\",\"measureLength\",\"measurePosition\",\"melismaBusyProperties\",\"metronomeMarkFormatter\",\"middleCClefPosition\",\"middleCOffset\",\"middleCPosition\",\"midiInstrument\",\"midiMaximumVolume\",\"midiMinimumVolume\",\"minimumFret\",\"minimumPageTurnLength\",\"minimumRepeatLengthForPageTurn\",\"noteToFretFunction\",\"ottavation\",\"output\",\"pedalSostenutoStrings\",\"pedalSostenutoStyle\",\"pedalSustainStrings\",\"pedalSustainStyle\",\"pedalUnaCordaStrings\",\"pedalUnaCordaStyle\",\"printKeyCancellation\",\"printOctaveNames\",\"printPartCombineTexts\",\"proportionalNotationDuration\",\"recordEventSequence\",\"rehearsalMark\",\"repeatCommands\",\"restNumberThreshold\",\"scriptDefinitions\",\"shapeNoteStyles\",\"shortInstrumentName\",\"shortVocalName\",\"skipBars\",\"skipTypesetting\",\"soloIIText\",\"soloText\",\"squashedPosition\",\"staffLineLayoutFunction\",\"stanza\",\"stemLeftBeamCount\",\"stemRightBeamCount\",\"stringNumberOrientations\",\"stringOneTopmost\",\"stringTunings\",\"strokeFingerOrientations\",\"subdivideBeams\",\"suggestAccidentals\",\"systemStartDelimiter\",\"systemStartDelimiterHierarchy\",\"tablatureFormat\",\"tempoUnitCount\",\"tempoUnitDuration\",\"tempoWholesPerMinute\",\"tieWaitForNote\",\"timeSignatureFraction\",\"timing\",\"tonic\",\"topLevelAlignment\",\"trebleStaffProperties\",\"tremoloFlags\",\"tupletFullLength\",\"tupletFullLengthNote\",\"tupletSpannerDuration\",\"useBassFigureExtenders\",\"verticallySpacedContexts\",\"vocalName\",\"voltaOnThisStaff\",\"voltaSpannerDuration\",\"whichBar\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&'()*+,-./0123456789:;<=>?[\\\\]^_{|}~\"}) (CaseSensitiveWords (fromList [\"barNumberAlignSymbol\",\"centralCPosition\",\"extraVerticalExtent\",\"fingerHorizontalDirection\",\"instr\",\"instrument\",\"keyAccidentalOrder\",\"minimumVerticalExtent\",\"rehearsalMarkAlignSymbol\",\"soloADue\",\"tupletNumberFormatFunction\",\"vocNam\"])), rAttribute = DataTypeTok, 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 = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"string\",Context {cName = \"string\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"tempo\",Context {cName = \"tempo\", cSyntax = \"LilyPond\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\markup(lines)?(?![A-Za-z])\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"LilyPond\",\"markup\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\d+\\\\.*\\\\s*=\\\\s*\\\\d+\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"LilyPond\",\"basic\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False})], sAuthor = \"Wilbert Berendsen (info@wilbertberendsen.nl)\", sVersion = \"4\", sLicense = \"LGPL\", sExtensions = [\"*.ly\",\"*.LY\",\"*.ily\",\"*.ILY\",\"*.lyi\",\"*.LYI\"], sStartingContext = \"lilypond\"}"