File add-rpmspec-syntax.patch of Package highlighting-kate

diff --git highlighting-kate-0.6/Text/Highlighting/Kate/Syntax/Rpmspec.hs highlighting-kate-0.6/Text/Highlighting/Kate/Syntax/Rpmspec.hs
new file mode 100644
index 0000000..66d0ee4
--- /dev/null
+++ highlighting-kate-0.6/Text/Highlighting/Kate/Syntax/Rpmspec.hs
@@ -0,0 +1,515 @@
+{- This module was generated from data in the Kate syntax
+   highlighting file rpmspec.xml, version 1.7, by  -}
+
+module Text.Highlighting.Kate.Syntax.Rpmspec
+          (highlight, parseExpression, syntaxName, syntaxExtensions)
+where
+import Text.Highlighting.Kate.Types
+import Text.Highlighting.Kate.Common
+import Text.ParserCombinators.Parsec hiding (State)
+import Control.Monad.State
+import Data.Char (isSpace)
+import qualified Data.Set as Set
+
+-- | Full name of language.
+syntaxName :: String
+syntaxName = "RPM Spec"
+
+-- | Filename extensions for this language.
+syntaxExtensions :: String
+syntaxExtensions = "*.spec"
+
+-- | Highlight source code using this syntax definition.
+highlight :: String -> [SourceLine]
+highlight input = evalState (mapM parseSourceLine $ lines input) startingState
+
+parseSourceLine :: String -> State SyntaxState SourceLine
+parseSourceLine = mkParseSourceLine (parseExpression Nothing)
+
+-- | Parse an expression using appropriate local context.
+parseExpression :: Maybe (String,String)
+                -> KateParser Token
+parseExpression mbcontext = do
+  (lang,cont) <- maybe currentContext return mbcontext
+  result <- parseRules (lang,cont)
+  optional $ do eof
+                updateState $ \st -> st{ synStPrevChar = '\n' }
+                pEndLine
+  return result
+
+startingState = SyntaxState {synStContexts = [("RPM Spec","package section")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []}
+
+pEndLine = do
+  updateState $ \st -> st{ synStPrevNonspace = False }
+  context <- currentContext
+  contexts <- synStContexts `fmap` getState
+  st <- getState
+  if length contexts >= 2
+    then case context of
+      _ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False }
+      ("RPM Spec","package section") -> return ()
+      ("RPM Spec","package section start line") -> pushContext ("RPM Spec","package section") >> return ()
+      ("RPM Spec","command section") -> return ()
+      ("RPM Spec","changelog section") -> return ()
+      ("RPM Spec","description section start line") -> pushContext ("RPM Spec","description section") >> return ()
+      ("RPM Spec","description section") -> return ()
+      ("RPM Spec","Comment") -> (popContext) >> pEndLine
+      ("RPM Spec","every_non_whitespace_is_error") -> (popContext) >> pEndLine
+      ("RPM Spec","every_non_whitespace_is_warning") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_value") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_string") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_string_only_one_word") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_integer") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_integer_without_syntax_check") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_arch") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_package") -> (popContext) >> pEndLine
+      ("RPM Spec","tag_line_switch") -> (popContext) >> pEndLine
+      ("RPM Spec","changelog_generic") -> (popContext) >> pEndLine
+      ("RPM Spec","changelog_weekday") -> (popContext) >> pEndLine
+      ("RPM Spec","changelog_month") -> (popContext) >> pEndLine
+      ("RPM Spec","changelog_day") -> (popContext) >> pEndLine
+      ("RPM Spec","changelog_year") -> (popContext) >> pEndLine
+      ("RPM Spec","changelog_header") -> (popContext) >> pEndLine
+      ("RPM Spec","parameters after ifos") -> (popContext) >> pEndLine
+      ("RPM Spec","parameters after ifarch") -> (popContext) >> pEndLine
+      ("RPM Spec","expression after _if_ statement") -> (popContext) >> pEndLine
+      ("RPM Spec","quoted strings in if statements") -> (popContext) >> pEndLine
+      ("RPM Spec","macro defination") -> (popContext) >> pEndLine
+      ("RPM Spec","macro defination content") -> (popContext) >> pEndLine
+      ("RPM Spec","macro defination content switch") -> return ()
+      ("RPM Spec","macro defination content without line break") -> (popContext >> popContext) >> pEndLine
+      ("RPM Spec","macro defination content with line break") -> (popContext) >> pEndLine
+      ("RPM Spec","undefine macro") -> (popContext) >> pEndLine
+      ("RPM Spec","handle_percent") -> (popContext) >> pEndLine
+      ("RPM Spec","macro content in parenthesis") -> (popContext >> popContext) >> pEndLine
+      ("RPM Spec","macro content in braces") -> (popContext >> popContext) >> pEndLine
+      _ -> return ()
+    else return ()
+
+withAttribute attr txt = do
+  when (null txt) $ fail "Parser matched no text"
+  updateState $ \st -> st { synStPrevChar = last txt
+                          , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) }
+  return (attr, txt)
+
+list_weekdays = Set.fromList $ words $ "Mon Tue Wed Thu Fri Sat Sun"
+list_month_names = Set.fromList $ words $ "Jan Feb Mar Apr May Jun Jul Aug Sep Oct Nov Dec"
+list_days = Set.fromList $ words $ "1 2 3 4 5 6 7 8 9 01 02 03 04 05 06 07 08 09 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31"
+
+regex_'28'28Icon'7cExclusiveOs'7cExcludeOs'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((Icon|ExclusiveOs|ExcludeOs)[ \\t]*:[ \\t]*)"
+regex_'28'28BuildArch'7cBuildArchitectures'7cExclusiveArch'7cExcludeArch'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((BuildArch|BuildArchitectures|ExclusiveArch|ExcludeArch)[ \\t]*:[ \\t]*)"
+regex_'28'28Conflicts'7cObsoletes'7cProvides'7cRequires'7cRequires'5c'28'2e'2a'5c'29'7cEnhances'7cSuggests'7cBuildConflicts'7cBuildRequires'7cRecommends'7cPreReq'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((Conflicts|Obsoletes|Provides|Requires|Requires\\(.*\\)|Enhances|Suggests|BuildConflicts|BuildRequires|Recommends|PreReq)[ \\t]*:[ \\t]*)"
+regex_'28'28Epoch'7cSerial'7cNosource'7cNopatch'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((Epoch|Serial|Nosource|Nopatch)[ \\t]*:[ \\t]*)"
+regex_'28'28AutoReq'7cAutoProv'7cAutoReqProv'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((AutoReq|AutoProv|AutoReqProv)[ \\t]*:[ \\t]*)"
+regex_'28'28Copyright'7cLicense'7cSummary'7cSummary'5c'28'2e'2a'5c'29'7cDistribution'7cVendor'7cPackager'7cGroup'7cSource'5cd'2a'7cPatch'5cd'2a'7cBuildRoot'7cPrefix'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((Copyright|License|Summary|Summary\\(.*\\)|Distribution|Vendor|Packager|Group|Source\\d*|Patch\\d*|BuildRoot|Prefix)[ \\t]*:[ \\t]*)"
+regex_'28'28Name'7cVersion'7cRelease'7cUrl'7cURL'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 = compileRegex True "((Name|Version|Release|Url|URL)[ \\t]*:[ \\t]*)"
+regex_'5b_'5ct'5d'2a'23 = compileRegex True "[ \\t]*#"
+regex_'5c'5c'2e = compileRegex True "\\\\."
+regex_'5b_'5ct'5d'2b'28'3f'3d'23'29 = compileRegex True "[ \\t]+(?=#)"
+regex_'23'5b_'5ct'5d'2anorootforbuild = compileRegex True "#[ \\t]*norootforbuild"
+regex_'5b'5e'5cs'5d = compileRegex True "[^\\s]"
+regex_'5c'5c'5b'5e'25'5d = compileRegex True "\\\\[^%]"
+regex_'5c'5c'28'3f'3d'28'5c'25'29'29 = compileRegex True "\\\\(?=(\\%))"
+regex_'2e = compileRegex True "."
+regex_'28i386'7ci486'7ci586'7ci686'7cathlon'7cia64'7calpha'7calphaev5'7calphaev56'7calphapca56'7calphaev6'7calphaev67'7csparc'7csparcv9'7csparc64armv3l'7carmv4b'7carmv4lm'7cips'7cmipsel'7cppc'7cppc'7ciseries'7cppcpseries'7cppc64'7cm68k'7cm68kmint'7cSgi'7crs6000'7ci370'7cs390x'7cs390'7cnoarch'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "(i386|i486|i586|i686|athlon|ia64|alpha|alphaev5|alphaev56|alphapca56|alphaev6|alphaev67|sparc|sparcv9|sparc64armv3l|armv4b|armv4lm|ips|mipsel|ppc|ppc|iseries|ppcpseries|ppc64|m68k|m68kmint|Sgi|rs6000|i370|s390x|s390|noarch)(?=($| |\\t))"
+regex_'5cS'2a = compileRegex True "\\S*"
+regex_'28'5cd'7b4'7d'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "(\\d{4})(?=($| |\\t))"
+regex_'5c'5c'5b'5e'22'5d = compileRegex True "\\\\[^\"]"
+regex_'5bA'2dZa'2dz0'2d9'5f'5d'2a'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "[A-Za-z0-9_]*(?=($| |\\t))"
+regex_'5b'5e_'5ct'5d'2a = compileRegex True "[^ \\t]*"
+regex_'2e'2a = compileRegex True ".*"
+regex_'28'2e'2a'29'28'5c'5c'29'28'3f'3d'28'24'29'29 = compileRegex True "(.*)(\\\\)(?=($))"
+regex_'5c'5c'28'3f'3d'28'2e'29'29 = compileRegex True "\\\\(?=(.))"
+regex_'25'28if'21'3f'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%(if!?)(?=($| |\\t))"
+regex_'25'28ifarch'7cifnarch'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%(ifarch|ifnarch)(?=($| |\\t))"
+regex_'25'28ifos'7cifnos'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%(ifos|ifnos)(?=($| |\\t))"
+regex_'25else'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%else(?=($| |\\t))"
+regex_'25endif'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%endif(?=($| |\\t))"
+regex_'25'28define'7cglobal'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%(define|global)(?=($| |\\t))"
+regex_'25undefine'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%undefine(?=($| |\\t))"
+regex_'25package'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%package(?=($| |\\t))"
+regex_'25description'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%description(?=($| |\\t))"
+regex_'25'28prep'7cbuild'7cpre'7cpreun'7cinstall'7cpost'7cpostun'7cclean'7cfiles'7ctrigger'7ctriggerin'7ctriggerun'7ctriggerpostun'7cverifyscript'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%(prep|build|pre|preun|install|post|postun|clean|files|trigger|triggerin|triggerun|triggerpostun|verifyscript)(?=($| |\\t))"
+regex_'25changelog'28'3f'3d'28'24'7c_'7c'5ct'29'29 = compileRegex True "%changelog(?=($| |\\t))"
+regex_'25'28'5b'5c'7b'5c'28'5d'5b_'5ct'5d'7b0'2c'7d'29'7b0'2c1'7d'28if'7c'28ifarch'7cifnarch'29'7c'28ifos'7cifnos'29'7celse'7cendif'7cdefine'7cglobal'7cundefine'7cpackage'7cdescription'7c'28prep'7cbuild'7cpre'7cpreun'7cinstall'7cpost'7cpostun'7cclean'7cfiles'7ctrigger'7ctriggerin'7ctriggerun'7ctriggerpostun'7cverifyscript'29'7cchangelog'29'28'3f'3d'28'24'7c'5b'5eA'2dZa'2dz0'2d9'5f'5d'29'29 = compileRegex True "%([\\{\\(][ \\t]{0,}){0,1}(if|(ifarch|ifnarch)|(ifos|ifnos)|else|endif|define|global|undefine|package|description|(prep|build|pre|preun|install|post|postun|clean|files|trigger|triggerin|triggerun|triggerpostun|verifyscript)|changelog)(?=($|[^A-Za-z0-9_]))"
+regex_'25'5bA'2dZa'2dz0'2d9'5f'5d'2a'5c'28 = compileRegex True "%[A-Za-z0-9_]*\\("
+regex_'28'25'7c'5c'24'29'5c'7b = compileRegex True "(%|\\$)\\{"
+regex_'28'25'7c'5c'24'29'28'5bA'2dZa'2dz0'2d9'5f'5d'7b1'2c'7d'7c'5c'2a'7c'5c'23'29'28'3f'3d'28'24'7c'5b'5eA'2dZa'2dz0'2d9'5f'5d'29'29 = compileRegex True "(%|\\$)([A-Za-z0-9_]{1,}|\\*|\\#)(?=($|[^A-Za-z0-9_]))"
+regex_'28'25'7c'5c'24'29'28'5bA'2dZa'2dz0'2d9'5f'5d'7b1'2c'7d'7c'5c'2a'7c'5c'23'29 = compileRegex True "(%|\\$)([A-Za-z0-9_]{1,}|\\*|\\#)"
+
+parseRules ("RPM Spec","package section") =
+  (((pColumn 0 >> pRegExpr regex_'28'28Icon'7cExclusiveOs'7cExcludeOs'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_value"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'28'28BuildArch'7cBuildArchitectures'7cExclusiveArch'7cExcludeArch'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_arch"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'28'28Conflicts'7cObsoletes'7cProvides'7cRequires'7cRequires'5c'28'2e'2a'5c'29'7cEnhances'7cSuggests'7cBuildConflicts'7cBuildRequires'7cRecommends'7cPreReq'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_package"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'28'28Epoch'7cSerial'7cNosource'7cNopatch'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_integer"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'28'28AutoReq'7cAutoProv'7cAutoReqProv'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_switch"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'28'28Copyright'7cLicense'7cSummary'7cSummary'5c'28'2e'2a'5c'29'7cDistribution'7cVendor'7cPackager'7cGroup'7cSource'5cd'2a'7cPatch'5cd'2a'7cBuildRoot'7cPrefix'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_string"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'28'28Name'7cVersion'7cRelease'7cUrl'7cURL'29'5b_'5ct'5d'2a'3a'5b_'5ct'5d'2a'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","tag_line_string_only_one_word"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   ((pColumn 0 >> lookAhead (pRegExpr regex_'5b_'5ct'5d'2a'23) >> pushContext ("RPM Spec","Comment") >> currentContext >>= parseRules))
+   <|>
+   ((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","package section")) >> pDefault >>= withAttribute ErrorTok))
+
+parseRules ("RPM Spec","package section start line") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","package section start line")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","command section") =
+  (((pRegExpr regex_'5c'5c'2e >>= withAttribute CharTok))
+   <|>
+   ((pDetectChar False '\\' >>= withAttribute KeywordTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   ((pColumn 0 >> lookAhead (pRegExpr regex_'5b_'5ct'5d'2a'23) >> pushContext ("RPM Spec","Comment") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","command section")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","changelog section") =
+  (((pColumn 0 >> pDetectChar False '*' >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","changelog_weekday"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   ((pColumn 0 >> lookAhead (pRegExpr regex_'5b_'5ct'5d'2a'23) >> pushContext ("RPM Spec","Comment") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog section")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","description section start line") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","description section start line")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","description section") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   ((pColumn 0 >> lookAhead (pRegExpr regex_'5b_'5ct'5d'2a'23) >> pushContext ("RPM Spec","Comment") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","description section")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","Comment") =
+  (((pColumn 0 >> pRegExpr regex_'5b_'5ct'5d'2b'28'3f'3d'23'29 >>= withAttribute ErrorTok))
+   <|>
+   ((pColumn 0 >> pString False "# norootforbuild" >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_warning"))
+   <|>
+   ((pRegExpr regex_'23'5b_'5ct'5d'2anorootforbuild >>= withAttribute ErrorTok))
+   <|>
+   ((pDetect2Chars False '%' '%' >>= withAttribute CommentTok))
+   <|>
+   ((pDetectChar False '%' >>= withAttribute ErrorTok))
+   <|>
+   ((pString False "TODO" >>= withAttribute AlertTok))
+   <|>
+   ((pString False "FIXME" >>= withAttribute AlertTok))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","Comment")) >> pDefault >>= withAttribute CommentTok))
+
+parseRules ("RPM Spec","every_non_whitespace_is_error") =
+  (((pRegExpr regex_'5b'5e'5cs'5d >>= withAttribute ErrorTok))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","every_non_whitespace_is_error")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","every_non_whitespace_is_warning") =
+  (((pRegExpr regex_'5b'5e'5cs'5d >>= withAttribute ErrorTok))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","every_non_whitespace_is_warning")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","tag_line_value") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_value")) >> pDefault >>= withAttribute OtherTok))
+
+parseRules ("RPM Spec","tag_line_string") =
+  (((pRegExpr regex_'5c'5c'5b'5e'25'5d >>= withAttribute CharTok))
+   <|>
+   ((pRegExpr regex_'5c'5c'28'3f'3d'28'5c'25'29'29 >>= withAttribute CharTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_string")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","tag_line_string_only_one_word") =
+  (((pRegExpr regex_'5c'5c'5b'5e'25'5d >>= withAttribute CharTok))
+   <|>
+   ((pRegExpr regex_'5c'5c'28'3f'3d'28'5c'25'29'29 >>= withAttribute CharTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","tag_line_string") >> currentContext >>= parseRules))
+   <|>
+   ((pDetectSpaces >>= withAttribute StringTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_string_only_one_word")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","tag_line_integer") =
+  (((pInt >>= withAttribute DecValTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","tag_line_integer_without_syntax_check") >> currentContext >>= parseRules))
+   <|>
+   ((lookAhead (pRegExpr regex_'2e) >> pushContext ("RPM Spec","every_non_whitespace_is_error") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_integer")) >> pDefault >>= withAttribute ErrorTok))
+
+parseRules ("RPM Spec","tag_line_integer_without_syntax_check") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_integer_without_syntax_check")) >> pDefault >>= withAttribute DecValTok))
+
+parseRules ("RPM Spec","tag_line_arch") =
+  (((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   ((pRegExpr regex_'28i386'7ci486'7ci586'7ci686'7cathlon'7cia64'7calpha'7calphaev5'7calphaev56'7calphapca56'7calphaev6'7calphaev67'7csparc'7csparcv9'7csparc64armv3l'7carmv4b'7carmv4lm'7cips'7cmipsel'7cppc'7cppc'7ciseries'7cppcpseries'7cppc64'7cm68k'7cm68kmint'7cSgi'7crs6000'7ci370'7cs390x'7cs390'7cnoarch'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute OtherTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","tag_line_value") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_arch")) >> pDefault >>= withAttribute ErrorTok))
+
+parseRules ("RPM Spec","tag_line_package") =
+  (((pAnyChar "()" >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '<' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '>' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '=' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pAnyChar "=<>," >>= withAttribute KeywordTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_package")) >> pDefault >>= withAttribute OtherTok))
+
+parseRules ("RPM Spec","tag_line_switch") =
+  (((pAnyChar "01" >>= withAttribute OtherTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((pDetect2Chars False 'n' 'o' >>= withAttribute OtherTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((pString False "yes" >>= withAttribute OtherTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","tag_line_value") >> currentContext >>= parseRules))
+   <|>
+   ((lookAhead (pRegExpr regex_'2e) >> pushContext ("RPM Spec","every_non_whitespace_is_error") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","tag_line_switch")) >> pDefault >>= withAttribute ErrorTok))
+
+parseRules ("RPM Spec","changelog_generic") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog_generic")) >> pDefault >>= withAttribute DataTypeTok))
+
+parseRules ("RPM Spec","changelog_weekday") =
+  (((pDetectSpaces >>= withAttribute DataTypeTok))
+   <|>
+   ((pKeyword " \n\t" list_weekdays >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","changelog_month"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","changelog_generic") >> currentContext >>= parseRules))
+   <|>
+   ((pRegExpr regex_'5cS'2a >>= withAttribute ErrorTok) >>~ pushContext ("RPM Spec","changelog_month"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog_weekday")) >> pDefault >>= withAttribute DataTypeTok))
+
+parseRules ("RPM Spec","changelog_month") =
+  (((pDetectSpaces >>= withAttribute DataTypeTok))
+   <|>
+   ((pKeyword " \n\t" list_month_names >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","changelog_day"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","changelog_generic") >> currentContext >>= parseRules))
+   <|>
+   ((pRegExpr regex_'5cS'2a >>= withAttribute ErrorTok) >>~ pushContext ("RPM Spec","changelog_day"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog_month")) >> pDefault >>= withAttribute DataTypeTok))
+
+parseRules ("RPM Spec","changelog_day") =
+  (((pDetectSpaces >>= withAttribute DataTypeTok))
+   <|>
+   ((pKeyword " \n\t" list_days >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","changelog_year"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","changelog_generic") >> currentContext >>= parseRules))
+   <|>
+   ((pRegExpr regex_'5cS'2a >>= withAttribute ErrorTok) >>~ pushContext ("RPM Spec","changelog_year"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog_day")) >> pDefault >>= withAttribute DataTypeTok))
+
+parseRules ("RPM Spec","changelog_year") =
+  (((pDetectSpaces >>= withAttribute DataTypeTok))
+   <|>
+   ((pRegExpr regex_'28'5cd'7b4'7d'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute DataTypeTok) >>~ pushContext ("RPM Spec","changelog_header"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","changelog_generic") >> currentContext >>= parseRules))
+   <|>
+   ((pRegExpr regex_'5cS'2a >>= withAttribute ErrorTok) >>~ pushContext ("RPM Spec","changelog_header"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog_year")) >> pDefault >>= withAttribute DataTypeTok))
+
+parseRules ("RPM Spec","changelog_header") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","changelog_header")) >> pDefault >>= withAttribute DataTypeTok))
+
+parseRules ("RPM Spec","parameters after ifos") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","parameters after ifos")) >> pDefault >>= withAttribute OtherTok))
+
+parseRules ("RPM Spec","parameters after ifarch") =
+  (((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   ((pRegExpr regex_'28i386'7ci486'7ci586'7ci686'7cathlon'7cia64'7calpha'7calphaev5'7calphaev56'7calphapca56'7calphaev6'7calphaev67'7csparc'7csparcv9'7csparc64armv3l'7carmv4b'7carmv4lm'7cips'7cmipsel'7cppc'7cppc'7ciseries'7cppcpseries'7cppc64'7cm68k'7cm68kmint'7cSgi'7crs6000'7ci370'7cs390x'7cs390'7cnoarch'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute OtherTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","parameters after ifarch")) >> pDefault >>= withAttribute ErrorTok))
+
+parseRules ("RPM Spec","expression after _if_ statement") =
+  (((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   ((pAnyChar "()" >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '&' '&' >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '<' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '>' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '=' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '!' '=' >>= withAttribute KeywordTok))
+   <|>
+   ((pAnyChar "!<>" >>= withAttribute KeywordTok))
+   <|>
+   ((pDetect2Chars False '|' '|' >>= withAttribute KeywordTok))
+   <|>
+   ((pInt >>= withAttribute DecValTok))
+   <|>
+   ((pDetectIdentifier >>= withAttribute StringTok))
+   <|>
+   ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("RPM Spec","quoted strings in if statements"))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","expression after _if_ statement")) >> pDefault >>= withAttribute ErrorTok))
+
+parseRules ("RPM Spec","quoted strings in if statements") =
+  (((pRegExpr regex_'5c'5c'5b'5e'22'5d >>= withAttribute CharTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","quoted strings in if statements")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","macro defination") =
+  (((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   ((pRegExpr regex_'5bA'2dZa'2dz0'2d9'5f'5d'2a'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute OtherTok) >>~ pushContext ("RPM Spec","macro defination content"))
+   <|>
+   ((pRegExpr regex_'5b'5e_'5ct'5d'2a >>= withAttribute ErrorTok) >>~ pushContext ("RPM Spec","macro defination content"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro defination")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","macro defination content") =
+  (((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   ((lookAhead (pRegExpr regex_'2e'2a) >> pushContext ("RPM Spec","macro defination content switch") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro defination content")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","macro defination content switch") =
+  (((lookAhead (pRegExpr regex_'28'2e'2a'29'28'5c'5c'29'28'3f'3d'28'24'29'29) >> pushContext ("RPM Spec","macro defination content with line break") >> currentContext >>= parseRules))
+   <|>
+   ((lookAhead (pRegExpr regex_'2e'2a) >> pushContext ("RPM Spec","macro defination content without line break") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro defination content switch")) >> pDefault >>= withAttribute DecValTok))
+
+parseRules ("RPM Spec","macro defination content without line break") =
+  (((pDetectChar False '\\' >>= withAttribute ErrorTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro defination content without line break")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","macro defination content with line break") =
+  (((pRegExpr regex_'5c'5c'28'3f'3d'28'2e'29'29 >>= withAttribute ErrorTok))
+   <|>
+   ((pDetectChar False '\\' >>= withAttribute KeywordTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro defination content with line break")) >> pDefault >>= withAttribute StringTok))
+
+parseRules ("RPM Spec","undefine macro") =
+  (((pDetectSpaces >>= withAttribute NormalTok))
+   <|>
+   ((pRegExpr regex_'5bA'2dZa'2dz0'2d9'5f'5d'2a'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute OtherTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((pRegExpr regex_'2e >>= withAttribute ErrorTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","undefine macro")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","handle_percent") =
+  (((pDetect2Chars False '%' '%' >>= withAttribute CharTok) >>~ (popContext))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25'28if'21'3f'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","expression after _if_ statement"))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25'28ifarch'7cifnarch'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","parameters after ifarch"))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25'28ifos'7cifnos'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","parameters after ifos"))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25else'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25endif'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","every_non_whitespace_is_error"))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25'28define'7cglobal'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","macro defination"))
+   <|>
+   ((pFirstNonSpace >> pRegExpr regex_'25undefine'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute KeywordTok) >>~ pushContext ("RPM Spec","undefine macro"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'25package'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute RegionMarkerTok) >>~ pushContext ("RPM Spec","package section start line"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'25description'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute RegionMarkerTok) >>~ pushContext ("RPM Spec","description section start line"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'25'28prep'7cbuild'7cpre'7cpreun'7cinstall'7cpost'7cpostun'7cclean'7cfiles'7ctrigger'7ctriggerin'7ctriggerun'7ctriggerpostun'7cverifyscript'29'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute RegionMarkerTok) >>~ pushContext ("RPM Spec","command section"))
+   <|>
+   ((pColumn 0 >> pRegExpr regex_'25changelog'28'3f'3d'28'24'7c_'7c'5ct'29'29 >>= withAttribute RegionMarkerTok) >>~ pushContext ("RPM Spec","changelog section"))
+   <|>
+   ((pRegExpr regex_'25'28'5b'5c'7b'5c'28'5d'5b_'5ct'5d'7b0'2c'7d'29'7b0'2c1'7d'28if'7c'28ifarch'7cifnarch'29'7c'28ifos'7cifnos'29'7celse'7cendif'7cdefine'7cglobal'7cundefine'7cpackage'7cdescription'7c'28prep'7cbuild'7cpre'7cpreun'7cinstall'7cpost'7cpostun'7cclean'7cfiles'7ctrigger'7ctriggerin'7ctriggerun'7ctriggerpostun'7cverifyscript'29'7cchangelog'29'28'3f'3d'28'24'7c'5b'5eA'2dZa'2dz0'2d9'5f'5d'29'29 >>= withAttribute ErrorTok) >>~ (popContext))
+   <|>
+   ((pRegExpr regex_'25'5bA'2dZa'2dz0'2d9'5f'5d'2a'5c'28 >>= withAttribute FunctionTok) >>~ pushContext ("RPM Spec","macro content in parenthesis"))
+   <|>
+   ((pRegExpr regex_'28'25'7c'5c'24'29'5c'7b >>= withAttribute FunctionTok) >>~ pushContext ("RPM Spec","macro content in braces"))
+   <|>
+   ((pRegExpr regex_'28'25'7c'5c'24'29'28'5bA'2dZa'2dz0'2d9'5f'5d'7b1'2c'7d'7c'5c'2a'7c'5c'23'29'28'3f'3d'28'24'7c'5b'5eA'2dZa'2dz0'2d9'5f'5d'29'29 >>= withAttribute FunctionTok) >>~ (popContext))
+   <|>
+   ((pRegExpr regex_'28'25'7c'5c'24'29'28'5bA'2dZa'2dz0'2d9'5f'5d'7b1'2c'7d'7c'5c'2a'7c'5c'23'29 >>= withAttribute ErrorTok) >>~ (popContext))
+   <|>
+   ((pAnyChar "%$" >>= withAttribute ErrorTok) >>~ (popContext))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","handle_percent")) >> pDefault >>= withAttribute NormalTok))
+
+parseRules ("RPM Spec","macro content in parenthesis") =
+  (((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   ((pDetectChar False ')' >>= withAttribute FunctionTok) >>~ (popContext >> popContext))
+   <|>
+   ((pAnyChar "({}" >>= withAttribute ErrorTok))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro content in parenthesis")) >> pDefault >>= withAttribute FunctionTok))
+
+parseRules ("RPM Spec","macro content in braces") =
+  (((pDetectChar False '}' >>= withAttribute FunctionTok) >>~ (popContext >> popContext))
+   <|>
+   ((pAnyChar "({)" >>= withAttribute ErrorTok))
+   <|>
+   ((lookAhead (pAnyChar "%$") >> pushContext ("RPM Spec","handle_percent") >> currentContext >>= parseRules))
+   <|>
+   (currentContext >>= \x -> guard (x == ("RPM Spec","macro content in braces")) >> pDefault >>= withAttribute FunctionTok))
+
+
+parseRules x = parseRules ("RPM Spec","package section") <|> fail ("Unknown context" ++ show x)
diff --git highlighting-kate-0.6.orig/Text/Highlighting/Kate/Syntax.hs highlighting-kate-0.6/Text/Highlighting/Kate/Syntax.hs
index 9346210..df6ba08 100644
--- highlighting-kate-0.6.orig/Text/Highlighting/Kate/Syntax.hs
+++ highlighting-kate-0.6/Text/Highlighting/Kate/Syntax.hs
@@ -111,6 +111,7 @@ import qualified Text.Highlighting.Kate.Syntax.Relaxngcompact as Relaxngcompact
 import qualified Text.Highlighting.Kate.Syntax.Rest as Rest
 import qualified Text.Highlighting.Kate.Syntax.Rhtml as Rhtml
 import qualified Text.Highlighting.Kate.Syntax.Roff as Roff
+import qualified Text.Highlighting.Kate.Syntax.Rpmspec as Rpmspec
 import qualified Text.Highlighting.Kate.Syntax.Ruby as Ruby
 import qualified Text.Highlighting.Kate.Syntax.Rust as Rust
 import qualified Text.Highlighting.Kate.Syntax.Scala as Scala
@@ -136,11 +137,11 @@ import qualified Text.Highlighting.Kate.Syntax.Zsh as Zsh
 
 -- | List of supported languages.
 languages :: [String]
-languages = ["Abc","Actionscript","Ada","Agda","Alert","Alert_indent","Apache","Asn1","Asp","Awk","Bash","Bibtex","Boo","C","Changelog","Clojure","Cmake","Coffee","Coldfusion","Commonlisp","Cpp","Cs","Css","Curry","D","Diff","Djangotemplate","Dockerfile","Dot","Doxygen","Doxygenlua","Dtd","Eiffel","Email","Erlang","Fasm","Fortran","Fsharp","Gcc","Glsl","Gnuassembler","Go","Haskell","Haxe","Html","Idris","Ini","Isocpp","Java","Javadoc","Javascript","Json","Jsp","Julia","Kotlin","Latex","Lex","Lilypond","LiterateCurry","LiterateHaskell","Lua","M4","Makefile","Mandoc","Markdown","Mathematica","Matlab","Maxima","Mediawiki","Metafont","Mips","Modelines","Modula2","Modula3","Monobasic","Nasm","Noweb","Objectivec","Objectivecpp","Ocaml","Octave","Opencl","Pascal","Perl","Php","Pike","Postscript","Prolog","Pure","Python","R","Relaxng","Relaxngcompact","Rest","Rhtml","Roff","Ruby","Rust","Scala","Scheme","Sci","Sed","Sgml","Sql","SqlMysql","SqlPostgresql","Tcl","Tcsh","Texinfo","Verilog","Vhdl","Xml","Xorg","Xslt","Xul","Yacc","Yaml","Zsh"]
+languages = ["Abc","Actionscript","Ada","Agda","Alert","Alert_indent","Apache","Asn1","Asp","Awk","Bash","Bibtex","Boo","C","Changelog","Clojure","Cmake","Coffee","Coldfusion","Commonlisp","Cpp","Cs","Css","Curry","D","Diff","Djangotemplate","Dockerfile","Dot","Doxygen","Doxygenlua","Dtd","Eiffel","Email","Erlang","Fasm","Fortran","Fsharp","Gcc","Glsl","Gnuassembler","Go","Haskell","Haxe","Html","Idris","Ini","Isocpp","Java","Javadoc","Javascript","Json","Jsp","Julia","Kotlin","Latex","Lex","Lilypond","LiterateCurry","LiterateHaskell","Lua","M4","Makefile","Mandoc","Markdown","Mathematica","Matlab","Maxima","Mediawiki","Metafont","Mips","Modelines","Modula2","Modula3","Monobasic","Nasm","Noweb","Objectivec","Objectivecpp","Ocaml","Octave","Opencl","Pascal","Perl","Php","Pike","Postscript","Prolog","Pure","Python","R","Relaxng","Relaxngcompact","Rest","Rhtml","Roff","Rpmspec","Ruby","Rust","Scala","Scheme","Sci","Sed","Sgml","Sql","SqlMysql","SqlPostgresql","Tcl","Tcsh","Texinfo","Verilog","Vhdl","Xml","Xorg","Xslt","Xul","Yacc","Yaml","Zsh"]
 
 -- | List of language extensions.
 languageExtensions :: [(String, String)]
-languageExtensions = [("Abc", Abc.syntaxExtensions), ("Actionscript", Actionscript.syntaxExtensions), ("Ada", Ada.syntaxExtensions), ("Agda", Agda.syntaxExtensions), ("Alert", Alert.syntaxExtensions), ("Alert_indent", Alert_indent.syntaxExtensions), ("Apache", Apache.syntaxExtensions), ("Asn1", Asn1.syntaxExtensions), ("Asp", Asp.syntaxExtensions), ("Awk", Awk.syntaxExtensions), ("Bash", Bash.syntaxExtensions), ("Bibtex", Bibtex.syntaxExtensions), ("Boo", Boo.syntaxExtensions), ("C", C.syntaxExtensions), ("Changelog", Changelog.syntaxExtensions), ("Clojure", Clojure.syntaxExtensions), ("Cmake", Cmake.syntaxExtensions), ("Coffee", Coffee.syntaxExtensions), ("Coldfusion", Coldfusion.syntaxExtensions), ("Commonlisp", Commonlisp.syntaxExtensions), ("Cpp", Cpp.syntaxExtensions), ("Cs", Cs.syntaxExtensions), ("Css", Css.syntaxExtensions), ("Curry", Curry.syntaxExtensions), ("D", D.syntaxExtensions), ("Diff", Diff.syntaxExtensions), ("Djangotemplate", Djangotemplate.syntaxExtensions), ("Dockerfile", Dockerfile.syntaxExtensions), ("Dot", Dot.syntaxExtensions), ("Doxygen", Doxygen.syntaxExtensions), ("Doxygenlua", Doxygenlua.syntaxExtensions), ("Dtd", Dtd.syntaxExtensions), ("Eiffel", Eiffel.syntaxExtensions), ("Email", Email.syntaxExtensions), ("Erlang", Erlang.syntaxExtensions), ("Fasm", Fasm.syntaxExtensions), ("Fortran", Fortran.syntaxExtensions), ("Fsharp", Fsharp.syntaxExtensions), ("Gcc", Gcc.syntaxExtensions), ("Glsl", Glsl.syntaxExtensions), ("Gnuassembler", Gnuassembler.syntaxExtensions), ("Go", Go.syntaxExtensions), ("Haskell", Haskell.syntaxExtensions), ("Haxe", Haxe.syntaxExtensions), ("Html", Html.syntaxExtensions), ("Idris", Idris.syntaxExtensions), ("Ini", Ini.syntaxExtensions), ("Isocpp", Isocpp.syntaxExtensions), ("Java", Java.syntaxExtensions), ("Javadoc", Javadoc.syntaxExtensions), ("Javascript", Javascript.syntaxExtensions), ("Json", Json.syntaxExtensions), ("Jsp", Jsp.syntaxExtensions), ("Julia", Julia.syntaxExtensions), ("Kotlin", Kotlin.syntaxExtensions), ("Latex", Latex.syntaxExtensions), ("Lex", Lex.syntaxExtensions), ("Lilypond", Lilypond.syntaxExtensions), ("LiterateCurry", LiterateCurry.syntaxExtensions), ("LiterateHaskell", LiterateHaskell.syntaxExtensions), ("Lua", Lua.syntaxExtensions), ("M4", M4.syntaxExtensions), ("Makefile", Makefile.syntaxExtensions), ("Mandoc", Mandoc.syntaxExtensions), ("Markdown", Markdown.syntaxExtensions), ("Mathematica", Mathematica.syntaxExtensions), ("Matlab", Matlab.syntaxExtensions), ("Maxima", Maxima.syntaxExtensions), ("Mediawiki", Mediawiki.syntaxExtensions), ("Metafont", Metafont.syntaxExtensions), ("Mips", Mips.syntaxExtensions), ("Modelines", Modelines.syntaxExtensions), ("Modula2", Modula2.syntaxExtensions), ("Modula3", Modula3.syntaxExtensions), ("Monobasic", Monobasic.syntaxExtensions), ("Nasm", Nasm.syntaxExtensions), ("Noweb", Noweb.syntaxExtensions), ("Objectivec", Objectivec.syntaxExtensions), ("Objectivecpp", Objectivecpp.syntaxExtensions), ("Ocaml", Ocaml.syntaxExtensions), ("Octave", Octave.syntaxExtensions), ("Opencl", Opencl.syntaxExtensions), ("Pascal", Pascal.syntaxExtensions), ("Perl", Perl.syntaxExtensions), ("Php", Php.syntaxExtensions), ("Pike", Pike.syntaxExtensions), ("Postscript", Postscript.syntaxExtensions), ("Prolog", Prolog.syntaxExtensions), ("Pure", Pure.syntaxExtensions), ("Python", Python.syntaxExtensions), ("R", R.syntaxExtensions), ("Relaxng", Relaxng.syntaxExtensions), ("Relaxngcompact", Relaxngcompact.syntaxExtensions), ("Rest", Rest.syntaxExtensions), ("Rhtml", Rhtml.syntaxExtensions), ("Roff", Roff.syntaxExtensions), ("Ruby", Ruby.syntaxExtensions), ("Rust", Rust.syntaxExtensions), ("Scala", Scala.syntaxExtensions), ("Scheme", Scheme.syntaxExtensions), ("Sci", Sci.syntaxExtensions), ("Sed", Sed.syntaxExtensions), ("Sgml", Sgml.syntaxExtensions), ("Sql", Sql.syntaxExtensions), ("SqlMysql", SqlMysql.syntaxExtensions), ("SqlPostgresql", SqlPostgresql.syntaxExtensions), ("Tcl", Tcl.syntaxExtensions), ("Tcsh", Tcsh.syntaxExtensions), ("Texinfo", Texinfo.syntaxExtensions), ("Verilog", Verilog.syntaxExtensions), ("Vhdl", Vhdl.syntaxExtensions), ("Xml", Xml.syntaxExtensions), ("Xorg", Xorg.syntaxExtensions), ("Xslt", Xslt.syntaxExtensions), ("Xul", Xul.syntaxExtensions), ("Yacc", Yacc.syntaxExtensions), ("Yaml", Yaml.syntaxExtensions), ("Zsh", Zsh.syntaxExtensions)]
+languageExtensions = [("Abc", Abc.syntaxExtensions), ("Actionscript", Actionscript.syntaxExtensions), ("Ada", Ada.syntaxExtensions), ("Agda", Agda.syntaxExtensions), ("Alert", Alert.syntaxExtensions), ("Alert_indent", Alert_indent.syntaxExtensions), ("Apache", Apache.syntaxExtensions), ("Asn1", Asn1.syntaxExtensions), ("Asp", Asp.syntaxExtensions), ("Awk", Awk.syntaxExtensions), ("Bash", Bash.syntaxExtensions), ("Bibtex", Bibtex.syntaxExtensions), ("Boo", Boo.syntaxExtensions), ("C", C.syntaxExtensions), ("Changelog", Changelog.syntaxExtensions), ("Clojure", Clojure.syntaxExtensions), ("Cmake", Cmake.syntaxExtensions), ("Coffee", Coffee.syntaxExtensions), ("Coldfusion", Coldfusion.syntaxExtensions), ("Commonlisp", Commonlisp.syntaxExtensions), ("Cpp", Cpp.syntaxExtensions), ("Cs", Cs.syntaxExtensions), ("Css", Css.syntaxExtensions), ("Curry", Curry.syntaxExtensions), ("D", D.syntaxExtensions), ("Diff", Diff.syntaxExtensions), ("Djangotemplate", Djangotemplate.syntaxExtensions), ("Dockerfile", Dockerfile.syntaxExtensions), ("Dot", Dot.syntaxExtensions), ("Doxygen", Doxygen.syntaxExtensions), ("Doxygenlua", Doxygenlua.syntaxExtensions), ("Dtd", Dtd.syntaxExtensions), ("Eiffel", Eiffel.syntaxExtensions), ("Email", Email.syntaxExtensions), ("Erlang", Erlang.syntaxExtensions), ("Fasm", Fasm.syntaxExtensions), ("Fortran", Fortran.syntaxExtensions), ("Fsharp", Fsharp.syntaxExtensions), ("Gcc", Gcc.syntaxExtensions), ("Glsl", Glsl.syntaxExtensions), ("Gnuassembler", Gnuassembler.syntaxExtensions), ("Go", Go.syntaxExtensions), ("Haskell", Haskell.syntaxExtensions), ("Haxe", Haxe.syntaxExtensions), ("Html", Html.syntaxExtensions), ("Idris", Idris.syntaxExtensions), ("Ini", Ini.syntaxExtensions), ("Isocpp", Isocpp.syntaxExtensions), ("Java", Java.syntaxExtensions), ("Javadoc", Javadoc.syntaxExtensions), ("Javascript", Javascript.syntaxExtensions), ("Json", Json.syntaxExtensions), ("Jsp", Jsp.syntaxExtensions), ("Julia", Julia.syntaxExtensions), ("Kotlin", Kotlin.syntaxExtensions), ("Latex", Latex.syntaxExtensions), ("Lex", Lex.syntaxExtensions), ("Lilypond", Lilypond.syntaxExtensions), ("LiterateCurry", LiterateCurry.syntaxExtensions), ("LiterateHaskell", LiterateHaskell.syntaxExtensions), ("Lua", Lua.syntaxExtensions), ("M4", M4.syntaxExtensions), ("Makefile", Makefile.syntaxExtensions), ("Mandoc", Mandoc.syntaxExtensions), ("Markdown", Markdown.syntaxExtensions), ("Mathematica", Mathematica.syntaxExtensions), ("Matlab", Matlab.syntaxExtensions), ("Maxima", Maxima.syntaxExtensions), ("Mediawiki", Mediawiki.syntaxExtensions), ("Metafont", Metafont.syntaxExtensions), ("Mips", Mips.syntaxExtensions), ("Modelines", Modelines.syntaxExtensions), ("Modula2", Modula2.syntaxExtensions), ("Modula3", Modula3.syntaxExtensions), ("Monobasic", Monobasic.syntaxExtensions), ("Nasm", Nasm.syntaxExtensions), ("Noweb", Noweb.syntaxExtensions), ("Objectivec", Objectivec.syntaxExtensions), ("Objectivecpp", Objectivecpp.syntaxExtensions), ("Ocaml", Ocaml.syntaxExtensions), ("Octave", Octave.syntaxExtensions), ("Opencl", Opencl.syntaxExtensions), ("Pascal", Pascal.syntaxExtensions), ("Perl", Perl.syntaxExtensions), ("Php", Php.syntaxExtensions), ("Pike", Pike.syntaxExtensions), ("Postscript", Postscript.syntaxExtensions), ("Prolog", Prolog.syntaxExtensions), ("Pure", Pure.syntaxExtensions), ("Python", Python.syntaxExtensions), ("R", R.syntaxExtensions), ("Relaxng", Relaxng.syntaxExtensions), ("Relaxngcompact", Relaxngcompact.syntaxExtensions), ("Rest", Rest.syntaxExtensions), ("Rhtml", Rhtml.syntaxExtensions), ("Roff", Roff.syntaxExtensions),  ("Rpmspec", Rpmspec.syntaxExtensions), ("Ruby", Ruby.syntaxExtensions), ("Rust", Rust.syntaxExtensions), ("Scala", Scala.syntaxExtensions), ("Scheme", Scheme.syntaxExtensions), ("Sci", Sci.syntaxExtensions), ("Sed", Sed.syntaxExtensions), ("Sgml", Sgml.syntaxExtensions), ("Sql", Sql.syntaxExtensions), ("SqlMysql", SqlMysql.syntaxExtensions), ("SqlPostgresql", SqlPostgresql.syntaxExtensions), ("Tcl", Tcl.syntaxExtensions), ("Tcsh", Tcsh.syntaxExtensions), ("Texinfo", Texinfo.syntaxExtensions), ("Verilog", Verilog.syntaxExtensions), ("Vhdl", Vhdl.syntaxExtensions), ("Xml", Xml.syntaxExtensions), ("Xorg", Xorg.syntaxExtensions), ("Xslt", Xslt.syntaxExtensions), ("Xul", Xul.syntaxExtensions), ("Yacc", Yacc.syntaxExtensions), ("Yaml", Yaml.syntaxExtensions), ("Zsh", Zsh.syntaxExtensions)]
 
 -- | Returns a list of languages appropriate for the given file extension.
 languagesByExtension :: String -> [String]
@@ -156,7 +157,7 @@ languagesByFilename fn = [lang | (lang, globs) <- languageExtensions, matchGlobs
 -- extension (if unique).
 -- The parsers read the input lazily and parse line by line;
 -- results are returned immediately.
--- Supported languages: @abc@, @actionscript@, @ada@, @agda@, @alert@, @alert_indent@, @apache@, @asn1@, @asp@, @awk@, @bash@, @bibtex@, @boo@, @c@, @changelog@, @clojure@, @cmake@, @coffee@, @coldfusion@, @commonlisp@, @cpp@, @cs@, @css@, @curry@, @d@, @diff@, @djangotemplate@, @dockerfile@, @dot@, @doxygen@, @doxygenlua@, @dtd@, @eiffel@, @email@, @erlang@, @fasm@, @fortran@, @fsharp@, @gcc@, @glsl@, @gnuassembler@, @go@, @haskell@, @haxe@, @html@, @idris@, @ini@, @isocpp@, @java@, @javadoc@, @javascript@, @json@, @jsp@, @julia@, @kotlin@, @latex@, @lex@, @lilypond@, @literatecurry@, @literatehaskell@, @lua@, @m4@, @makefile@, @mandoc@, @markdown@, @mathematica@, @matlab@, @maxima@, @mediawiki@, @metafont@, @mips@, @modelines@, @modula2@, @modula3@, @monobasic@, @nasm@, @noweb@, @objectivec@, @objectivecpp@, @ocaml@, @octave@, @opencl@, @pascal@, @perl@, @php@, @pike@, @postscript@, @prolog@, @pure@, @python@, @r@, @relaxng@, @relaxngcompact@, @rest@, @rhtml@, @roff@, @ruby@, @rust@, @scala@, @scheme@, @sci@, @sed@, @sgml@, @sql@, @sqlmysql@, @sqlpostgresql@, @tcl@, @tcsh@, @texinfo@, @verilog@, @vhdl@, @xml@, @xorg@, @xslt@, @xul@, @yacc@, @yaml@, @zsh@.
+-- Supported languages: @abc@, @actionscript@, @ada@, @agda@, @alert@, @alert_indent@, @apache@, @asn1@, @asp@, @awk@, @bash@, @bibtex@, @boo@, @c@, @changelog@, @clojure@, @cmake@, @coffee@, @coldfusion@, @commonlisp@, @cpp@, @cs@, @css@, @curry@, @d@, @diff@, @djangotemplate@, @dockerfile@, @dot@, @doxygen@, @doxygenlua@, @dtd@, @eiffel@, @email@, @erlang@, @fasm@, @fortran@, @fsharp@, @gcc@, @glsl@, @gnuassembler@, @go@, @haskell@, @haxe@, @html@, @idris@, @ini@, @isocpp@, @java@, @javadoc@, @javascript@, @json@, @jsp@, @julia@, @kotlin@, @latex@, @lex@, @lilypond@, @literatecurry@, @literatehaskell@, @lua@, @m4@, @makefile@, @mandoc@, @markdown@, @mathematica@, @matlab@, @maxima@, @mediawiki@, @metafont@, @mips@, @modelines@, @modula2@, @modula3@, @monobasic@, @nasm@, @noweb@, @objectivec@, @objectivecpp@, @ocaml@, @octave@, @opencl@, @pascal@, @perl@, @php@, @pike@, @postscript@, @prolog@, @pure@, @python@, @r@, @relaxng@, @relaxngcompact@, @rest@, @rhtml@, @roff@, @rpmspec@, @ruby@, @rust@, @scala@, @scheme@, @sci@, @sed@, @sgml@, @sql@, @sqlmysql@, @sqlpostgresql@, @tcl@, @tcsh@, @texinfo@, @verilog@, @vhdl@, @xml@, @xorg@, @xslt@, @xul@, @yacc@, @yaml@, @zsh@.
 highlightAs :: String         -- ^ Language syntax (e.g. "haskell") or extension (e.g. "hs").
             -> String         -- ^ Source code to highlight
             -> [SourceLine]   -- ^ List of highlighted source lines
@@ -264,6 +265,7 @@ highlightAs lang =
         "rest" -> Rest.highlight
         "rhtml" -> Rhtml.highlight
         "roff" -> Roff.highlight
+        "rpmspec" -> Rpmspec.highlight
         "ruby" -> Ruby.highlight
         "rust" -> Rust.highlight
         "scala" -> Scala.highlight
diff --git highlighting-kate-0.6.orig/highlighting-kate.cabal highlighting-kate-0.6/highlighting-kate.cabal
index 9ee1982..0a793f0 100644
--- highlighting-kate-0.6.orig/highlighting-kate.cabal
+++ highlighting-kate-0.6/highlighting-kate.cabal
@@ -212,6 +212,7 @@ Library
                      Text.Highlighting.Kate.Syntax.Rest
                      Text.Highlighting.Kate.Syntax.Rhtml
                      Text.Highlighting.Kate.Syntax.Roff
+                     Text.Highlighting.Kate.Syntax.Rpmspec
                      Text.Highlighting.Kate.Syntax.Ruby
                      Text.Highlighting.Kate.Syntax.Rust
                      Text.Highlighting.Kate.Syntax.Scala
diff --git highlighting-kate-0.6/xml/rpmspec.xml highlighting-kate-0.6/xml/rpmspec.xml
new file mode 100644
index 0000000..385aae8
--- /dev/null
+++ highlighting-kate-0.6/xml/rpmspec.xml
@@ -0,0 +1,506 @@
+<?xml version="1.0" encoding="UTF-8"?>
+<!DOCTYPE language SYSTEM "language.dtd" [
+  <!ENTITY a_valid_char_in_macro_names "A-Za-z0-9_">
+  <!ENTITY command_section_name "(prep|build|pre|preun|install|post|postun|clean|files|trigger|triggerin|triggerun|triggerpostun|verifyscript)">
+  <!ENTITY arch "(i386|i486|i586|i686|athlon|ia64|alpha|alphaev5|alphaev56|alphapca56|alphaev6|alphaev67|sparc|sparcv9|sparc64armv3l|armv4b|armv4lm|ips|mipsel|ppc|ppc|iseries|ppcpseries|ppc64|m68k|m68kmint|Sgi|rs6000|i370|s390x|s390|noarch)">
+  <!ENTITY arch_conditionals_names "(ifarch|ifnarch)">
+  <!ENTITY os_conditionals_names "(ifos|ifnos)">
+  <!ENTITY lookahead_whitespace_eol "(?=($| |\t))">
+]>
+<language name="RPM Spec" version="1.7" kateversion="2.4" section="Other" extensions="*.spec" mimetype="" license="public domain">
+
+  <highlighting>
+
+    <list name="weekdays">
+      <item> Mon </item>
+      <item> Tue </item>
+      <item> Wed </item>
+      <item> Thu </item>
+      <item> Fri </item>
+      <item> Sat </item>
+      <item> Sun </item>
+    </list>
+
+    <list name="month names">
+      <item> Jan </item>
+      <item> Feb </item>
+      <item> Mar </item>
+      <item> Apr </item>
+      <item> May </item>
+      <item> Jun </item>
+      <item> Jul </item>
+      <item> Aug </item>
+      <item> Sep </item>
+      <item> Oct </item>
+      <item> Nov </item>
+      <item> Dec </item>
+    </list>
+
+    <list name="days">
+      <item> 1 </item>
+      <item> 2 </item>
+      <item> 3 </item>
+      <item> 4 </item>
+      <item> 5 </item>
+      <item> 6 </item>
+      <item> 7 </item>
+      <item> 8 </item>
+      <item> 9 </item>
+      <item> 01 </item>
+      <item> 02 </item>
+      <item> 03 </item>
+      <item> 04 </item>
+      <item> 05 </item>
+      <item> 06 </item>
+      <item> 07 </item>
+      <item> 08 </item>
+      <item> 09 </item>
+      <item> 10 </item>
+      <item> 11 </item>
+      <item> 12 </item>
+      <item> 13 </item>
+      <item> 14 </item>
+      <item> 15 </item>
+      <item> 16 </item>
+      <item> 17 </item>
+      <item> 18 </item>
+      <item> 19 </item>
+      <item> 20 </item>
+      <item> 21 </item>
+      <item> 22 </item>
+      <item> 23 </item>
+      <item> 24 </item>
+      <item> 25 </item>
+      <item> 26 </item>
+      <item> 27 </item>
+      <item> 28 </item>
+      <item> 29 </item>
+      <item> 30 </item>
+      <item> 31 </item>
+    </list>
+
+    <contexts>
+      <!-- "package section" is the context for the package defination. As it is the first context
+      in this file, it is also the context with which the interpreter starts. -->
+      <context attribute="Error" lineEndContext="#stay" name="package section">
+        <!-- Handle tags: -->
+        <RegExpr attribute="Tag" context="tag_line_value" String="((Icon|ExclusiveOs|ExcludeOs)[ \t]*:[ \t]*)" column="0" />
+        <RegExpr attribute="Tag" context="tag_line_arch" String="((BuildArch|BuildArchitectures|ExclusiveArch|ExcludeArch)[ \t]*:[ \t]*)" column="0" />
+        <RegExpr attribute="Tag" context="tag_line_package" String="((Conflicts|Obsoletes|Provides|Requires|Requires\(.*\)|Enhances|Suggests|BuildConflicts|BuildRequires|Recommends|PreReq)[ \t]*:[ \t]*)" column="0" />
+        <RegExpr attribute="Tag" context="tag_line_integer" String="((Epoch|Serial|Nosource|Nopatch)[ \t]*:[ \t]*)" column="0" />
+        <RegExpr attribute="Tag" context="tag_line_switch" String="((AutoReq|AutoProv|AutoReqProv)[ \t]*:[ \t]*)" column="0" />
+        <RegExpr attribute="Tag" context="tag_line_string" String="((Copyright|License|Summary|Summary\(.*\)|Distribution|Vendor|Packager|Group|Source\d*|Patch\d*|BuildRoot|Prefix)[ \t]*:[ \t]*)" column="0" />
+        <RegExpr attribute="Tag" context="tag_line_string_only_one_word" String="((Name|Version|Release|Url|URL)[ \t]*:[ \t]*)" column="0" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+        <!-- Handle comments. "# norootforbuild" is displayed like a tag. -->
+        <RegExpr context="Comment" String="[ \t]*#" column="0" lookAhead="true" />
+                <!-- Spaces are okay -->
+        <DetectSpaces attribute="Fallback for separator spaces" />
+        <!-- Fallback value for every non-space -->
+        <!--RegExpr attribute="Error" context="#stay" String="[^\s]" /-->
+      </context>
+
+      <!-- "package section start line" simply is used for the parameters after the
+      "%package" macro. With the next line break, it will switch to the
+      "package section" context which will handle everything else. -->
+      <context attribute="Shell commands" lineEndContext="package section" name="package section start line">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "command section" is a generic context for all secions (like %prep, %build, %install...)
+      where you can enter shell commands. -->
+      <context attribute="Shell commands" lineEndContext="#stay" name="command section">
+        <!-- Handle \ -->
+        <RegExpr attribute="Escaped character" String="\\." />
+        <DetectChar attribute="Line break" char="\" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+        <!-- Handle comments. "# norootforbuild" is displayed like a tag. -->
+        <RegExpr context="Comment" String="[ \t]*#" column="0" lookAhead="true" />
+      </context>
+
+      <!-- "changelog section" is the context for the changelog. By default, everything that is
+      not recognized especially, is interpretated as changelog text. -->
+      <context attribute="String" lineEndContext="#stay" name="changelog section">
+        <!-- Handle calender date -->
+        <DetectChar attribute="Tag" context="changelog_weekday" char="*" column="0" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+        <!-- Handle comments. "# norootforbuild" is displayed like a tag. -->
+        <RegExpr context="Comment" String="[ \t]*#" column="0" lookAhead="true" />
+      </context>
+
+      <!-- "description section start line" simply is used for the parameters after the
+      "%description" macro. With the next line break, it will switch to the
+      "description section" context which will handle the content of the description. -->
+      <context attribute="Shell commands" lineEndContext="description section" name="description section start line">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "description section" is a follow-up context of "description section start line". See
+      there for further details. -->
+      <context attribute="String" lineEndContext="#stay" name="description section">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+        <!-- Handle comments. "# norootforbuild" is displayed like a tag. -->
+        <RegExpr context="Comment" String="[ \t]*#" column="0" lookAhead="true" />
+      </context>
+
+      <!-- This is a convenience context that is handling comments automatically. Furthermore it
+      handles "# norootforbuild" because it looks like a comment. If a context supports comments,
+      simple use "<RegExpr context="Comment" String="[ \t]*#" column="0" lookAhead="true" />".
+      (This context relies on the asumption that # is the first non-whitespace. We have to
+      guarantee this when calling this context! -->
+      <context attribute="Comment" lineEndContext="#pop" name="Comment">
+        <!-- While indeeted comments are not allowed by the standard (see section "Comments" at
+        http://docs.fedoraproject.org/en-US/Fedora_Draft_Documentation/0.1/html/RPM_Guide/ch-specfile-syntax.html#id1961462),
+        rpmbuild accepts them nevertheless. We highlight them as comments, but we mark the
+        indeet. -->
+        <RegExpr attribute="Hint" context="#stay" String="[ \t]+(?=#)" column="0" />
+	<!-- Handle "# norootforbuild" and some of its miss-spellings. -->
+        <StringDetect attribute="Tag" context="every_non_whitespace_is_warning" String="# norootforbuild" column="0" />
+        <RegExpr attribute="Warning" context="#stay" String="#[ \t]*norootforbuild" />
+        <!-- Warning on single percent ("%"), but not on double percent ("%%"): -->
+        <Detect2Chars attribute="Comment" char="%" char1="%"/>
+        <DetectChar attribute="Warning" char="%"/>
+        <!-- Alert -->
+        <StringDetect attribute="Alert" String="TODO" insensitive="true" />
+        <StringDetect attribute="Alert" String="FIXME" insensitive="true" />
+      </context>
+
+      <!-- "every_non_whitespace_is_error" is a simple helper context. It switchs back to the
+      previous context at the end of the line. -->
+      <context attribute="Fallback for separator spaces" lineEndContext="#pop" name="every_non_whitespace_is_error">
+        <RegExpr attribute="Error" context="#stay" String="[^\s]" />
+      </context>
+
+      <!-- "every_non_whitespace_is_warning" is a simple helper context. It switchs back to the
+      previous context at the end of the line. -->
+      <context attribute="Fallback for separator spaces" lineEndContext="#pop" name="every_non_whitespace_is_warning">
+        <RegExpr attribute="Warning" context="#stay" String="[^\s]" />
+      </context>
+
+      <!-- "tag_line_value" is a context for enumeration values. It makes no further syntax
+      check. -->
+      <context attribute="Enumeration" lineEndContext="#pop" name="tag_line_value">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "tag_line_string" is a context for string values. It makes no further syntax
+      check. -->
+      <context attribute="String" lineEndContext="#pop" name="tag_line_string">
+        <!-- Handle \ -->
+        <RegExpr attribute="Escaped character" String="\\[^%]" />
+        <RegExpr attribute="Escaped character" String="\\(?=(\%))" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "tag_line_string_only_one_word" is a context for string values. The first word is
+      highlighted as string, but after the first space (normal space, tab...), all other
+      words are highlighted as error. WARNING: This context requieres that there is no space at
+      the begin! -->
+      <context attribute="String" lineEndContext="#pop" name="tag_line_string_only_one_word">
+        <!-- Handle \ -->
+        <RegExpr attribute="Escaped character" String="\\[^%]" />
+        <RegExpr attribute="Escaped character" String="\\(?=(\%))" />
+        <!-- Handle % -->
+        <AnyChar context="tag_line_string" String="%$" lookAhead="true" />
+        <!-- Handle spaces -->
+        <DetectSpaces context="every_non_whitespace_is_error" />
+      </context>
+
+      <!-- "tag_line_integer" is a context for integer values. Non-integer context is marked as
+      error. -->
+      <context attribute="Error" lineEndContext="#pop" name="tag_line_integer">
+        <Int attribute="Integer" context="every_non_whitespace_is_error" />
+        <!-- Handle % -->
+        <AnyChar context="tag_line_integer_without_syntax_check" String="%$" lookAhead="true" />
+        <RegExpr context="every_non_whitespace_is_error" String="." lookAhead="true" />
+      </context>
+
+      <!-- "tag_line_integer_without_syntax_check" is a context that is used internally by
+      "tag_line_integer" after macros. -->
+      <context attribute="Integer" lineEndContext="#pop" name="tag_line_integer_without_syntax_check">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "tag_line_arch" is a context for values that define the computer type. Unknown values
+      are marked as error. -->
+      <context attribute="Warning" lineEndContext="#pop" name="tag_line_arch">
+        <DetectSpaces attribute="Fallback for separator spaces" />
+        <!-- list from http://docs.fedoraproject.org/drafts/rpm-guide-en/ch01s03.html -->
+        <RegExpr attribute="Enumeration" String="&arch;&lookahead_whitespace_eol;" />
+        <!-- Handle % -->
+        <AnyChar context="tag_line_value" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "tag_line_package" is a context for dependency handling. The keywords <= >= == < > are
+      recognized and highlighted as keywords. Thee rest is simply highlighted as enumeration. See
+      http://docs.fedoraproject.org/drafts/rpm-guide-en/ch-specfile-syntax.html#id3045258 and
+      http://docs.fedoraproject.org/drafts/rpm-guide-en/ch-advanced-packaging.html#id2979270 for
+      details -->
+      <context attribute="Enumeration" lineEndContext="#pop" name="tag_line_package">
+        <AnyChar attribute="Keyword" context="#stay" String="()" /> <!-- See http://rpm5.org/docs/api/dependencies.html about the parentheses -->
+        <Detect2Chars attribute="Keyword" context="#stay" char="&lt;" char1="="/>
+        <Detect2Chars attribute="Keyword" context="#stay" char="&gt;" char1="="/>
+        <Detect2Chars attribute="Keyword" context="#stay" char="=" char1="="/>
+        <AnyChar attribute="Keyword" context="#stay" String="=&lt;&gt;," />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- "tag_line_switch" is a context that accepts "0", "1", "yes" and "no" as value.
+      Everything else is an error. See http://www.rpm.org/max-rpm-snapshot/s1-rpm-depend-auto-depend.html
+      and http://www.rpm.org/max-rpm/s1-rpm-inside-tags.html#S3-RPM-INSIDE-AUTOREQPROV-TAG -->
+      <context attribute="Error" lineEndContext="#pop" name="tag_line_switch">
+        <AnyChar attribute="Enumeration" context="every_non_whitespace_is_error" String="01" />
+        <Detect2Chars attribute="Enumeration" context="every_non_whitespace_is_error" char="n" char1="o"/>
+        <StringDetect attribute="Enumeration" context="every_non_whitespace_is_error" String="yes" />
+        <!-- Handle % -->
+        <AnyChar context="tag_line_value" String="%$" lookAhead="true" />
+        <RegExpr context="every_non_whitespace_is_error" String="." lookAhead="true" />
+      </context>
+
+      <!-- A context that doesn't test for format errors in the changelog date anymore. Necessary
+      if macros are used. -->
+      <context attribute="Tag" lineEndContext="#pop" name="changelog_generic">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+     <!-- A context that handles the weekday in the changelog date. -->
+      <context attribute="Tag" lineEndContext="#pop" name="changelog_weekday">
+        <DetectSpaces/>
+        <keyword context="changelog_month" attribute="Tag" String="weekdays" />
+        <!-- % handling without format errors in the date of the changelog -->
+        <AnyChar context="changelog_generic" String="%$" lookAhead="true" />
+        <RegExpr context="changelog_month" attribute="Error" String="\S*" />
+      </context>
+
+     <!-- A context that handles the month in the changelog date. -->
+      <context attribute="Tag" lineEndContext="#pop" name="changelog_month">
+        <DetectSpaces/>
+        <keyword context="changelog_day" attribute="Tag" String="month names" />
+        <!-- % handling without format errors in the date of the changelog -->
+        <AnyChar context="changelog_generic" String="%$" lookAhead="true" />
+        <RegExpr context="changelog_day" attribute="Error" String="\S*" />
+      </context>
+
+     <!-- A context that handles the day in the changelog date. -->
+      <context attribute="Tag" lineEndContext="#pop" name="changelog_day">
+        <DetectSpaces/>
+        <keyword context="changelog_year" attribute="Tag" String="days" />
+        <!-- % handling without format errors in the date of the changelog -->
+        <AnyChar context="changelog_generic" String="%$" lookAhead="true" />
+        <RegExpr context="changelog_year" attribute="Error" String="\S*" />
+      </context>
+
+     <!-- A context that handles the year in the changelog date. -->
+      <context attribute="Tag" lineEndContext="#pop" name="changelog_year">
+        <DetectSpaces/>
+        <RegExpr context="changelog_header" attribute="Tag" String="(\d{4})&lookahead_whitespace_eol;" />
+        <!-- % handling without format errors in the date of the changelog -->
+        <AnyChar context="changelog_generic" String="%$" lookAhead="true" />
+        <RegExpr context="changelog_header" attribute="Error" String="\S*" />
+      </context>
+
+     <!-- A context that handles the text after the date in a changelog (name, e-mail...). -->
+      <context attribute="Tag" lineEndContext="#pop" name="changelog_header">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- Handles everything that comes after %ifos etc...
+      No further check is done because we don't have a complete list with supportet operation systems. -->
+      <context attribute="Enumeration" lineEndContext="#pop" name="parameters after ifos">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- Handles everything that comes after %ifarch etc... -->
+      <context attribute="Warning" lineEndContext="#pop" name="parameters after ifarch">
+        <!-- Spaces are okay -->
+        <DetectSpaces attribute="Fallback for separator spaces" />
+        <!-- Recognize valid values -->
+        <RegExpr attribute="Enumeration" String="&arch;&lookahead_whitespace_eol;" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- Handles expressions after conditionals. -->
+      <context attribute="Error" lineEndContext="#pop" name="expression after _if_ statement">
+        <!-- spaces should not be "Error" (which is the default for unrecognized entities) -->
+        <DetectSpaces attribute="Fallback for separator spaces" context="#stay" />
+        <!-- %if recognizes && || > < >= <= == != ! and () -->
+        <AnyChar attribute="Keyword" context="#stay" String="()" />
+        <Detect2Chars attribute="Keyword" context="#stay" char="&amp;" char1="&amp;"/>
+        <Detect2Chars attribute="Keyword" context="#stay" char="&lt;" char1="="/>
+        <Detect2Chars attribute="Keyword" context="#stay" char="&gt;" char1="="/>
+        <Detect2Chars attribute="Keyword" context="#stay" char="=" char1="="/>
+        <Detect2Chars attribute="Keyword" context="#stay" char="!" char1="="/>
+        <AnyChar attribute="Keyword" context="#stay" String="!&lt;&gt;" />
+        <Detect2Chars attribute="Keyword" context="#stay" char="|" char1="|"/>
+        <!-- %if interpretates values either as integer or as string -->
+        <Int attribute="Integer" context="#stay" />
+        <DetectIdentifier attribute="String" context="#stay" />
+        <DetectChar attribute="String" context="quoted strings in if statements" char="&quot;" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- This context handles quoted strings in %if statements. WARNING: Make sure that you
+      switch to this context _after_ parsing the starting ", because at the first occurence
+      of " this context switches back. -->
+      <context attribute="String" lineEndContext="#pop" name="quoted strings in if statements">
+        <!-- Handle \ -->
+        <RegExpr attribute="Escaped character" String="\\[^&quot;]" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+        <!-- Switch back at the end of the quoted string -->
+        <DetectChar attribute="String" context="#pop" char="&quot;" />
+      </context>
+
+      <!-- Context for %define -->
+      <context attribute="Fallback for separator spaces" lineEndContext="#pop" name="macro defination">
+        <DetectSpaces />
+        <RegExpr attribute="Enumeration" context="macro defination content" String="[&a_valid_char_in_macro_names;]*&lookahead_whitespace_eol;" />
+        <RegExpr attribute="Error" context="macro defination content" String="[^ \t]*" />
+      </context>
+
+      <!-- Context for the content of a macro defination. -->
+      <context attribute="Fallback for separator spaces" lineEndContext="#pop" name="macro defination content">
+        <DetectSpaces />
+        <!-- If the line has any content -->
+        <RegExpr context="macro defination content switch" String=".*" lookAhead="true" />
+      </context>
+
+      <!-- Internal context for the content of a macro defination.
+      WARNING: Only switch to this context if there is at least 1 character (may be space or whatever...) -->
+      <context attribute="Integer" lineEndContext="#stay" name="macro defination content switch">
+        <!-- If the line terminates with \ -->
+        <RegExpr context="macro defination content with line break" String="(.*)(\\)(?=($))" lookAhead="true" />
+        <!-- If the line does not terminate with \ -->
+        <RegExpr context="macro defination content without line break" String=".*" lookAhead="true" />
+      </context>
+
+      <!-- Internal context for the content of a macro defination-->
+      <context attribute="String" lineEndContext="#pop#pop" name="macro defination content without line break">
+        <!-- Handle \ -->
+        <DetectChar attribute="Warning" char="\" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- Internal context for the content of a macro defination-->
+      <context attribute="String" lineEndContext="#pop" name="macro defination content with line break">
+        <!-- Handle \ -->
+        <RegExpr attribute="Warning" String="\\(?=(.))" />
+        <DetectChar attribute="Line break" char="\" />
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+      <!-- Context for %undefine -->
+      <context attribute="Fallback for separator spaces" lineEndContext="#pop" name="undefine macro">
+        <DetectSpaces />
+        <RegExpr attribute="Enumeration" context="every_non_whitespace_is_error" String="[&a_valid_char_in_macro_names;]*&lookahead_whitespace_eol;" />
+        <RegExpr attribute="Error" context="every_non_whitespace_is_error" String="." />
+      </context>
+
+      <!-- This context handles automatically all type of macros, keywords and so on that start with % or $.
+      It expects a string starting with % or $ (otherwise, this context will fail!). -->
+      <context attribute="Fallback for separator spaces" lineEndContext="#pop" name="handle_percent">
+        <Detect2Chars attribute="Escaped character" context="#pop" char="%" char1="%"/>
+        <!-- Keywords: -->
+        <RegExpr attribute="Keyword" context="expression after _if_ statement" String="%(if!?)&lookahead_whitespace_eol;" firstNonSpace="true" beginRegion="if_block" />
+        <RegExpr attribute="Keyword" context="parameters after ifarch" String="%&arch_conditionals_names;&lookahead_whitespace_eol;" firstNonSpace="true" beginRegion="if_block" />
+        <RegExpr attribute="Keyword" context="parameters after ifos" String="%&os_conditionals_names;&lookahead_whitespace_eol;" firstNonSpace="true" beginRegion="if_block" />
+        <RegExpr attribute="Keyword" context="every_non_whitespace_is_error" String="%else&lookahead_whitespace_eol;" firstNonSpace="true" endRegion="if_block" beginRegion="if_block" />
+        <RegExpr attribute="Keyword" context="every_non_whitespace_is_error" String="%endif&lookahead_whitespace_eol;" firstNonSpace="true" endRegion="if_block" />
+        <RegExpr attribute="Keyword" context="macro defination" String="%(define|global)&lookahead_whitespace_eol;" firstNonSpace="true" />
+        <RegExpr attribute="Keyword" context="undefine macro" String="%undefine&lookahead_whitespace_eol;" firstNonSpace="true" />
+        <!-- If a command section starts (=section macro at begin of the line), we switch
+             to the corresponding context. There will never be a return to THIS context...: -->
+        <RegExpr attribute="Section" context="package section start line" String="%package&lookahead_whitespace_eol;" column="0" />
+        <RegExpr attribute="Section" context="description section start line" String="%description&lookahead_whitespace_eol;" column="0" />
+        <RegExpr attribute="Section" context="command section" String="%&command_section_name;&lookahead_whitespace_eol;" column="0" />
+        <RegExpr attribute="Section" context="changelog section" String="%changelog&lookahead_whitespace_eol;" column="0" />
+        <!-- Handle normal macros -->
+        <RegExpr attribute="Error" context="#pop" String="%([\{\(][ \t]{0,}){0,1}(if|&arch_conditionals_names;|&os_conditionals_names;|else|endif|define|global|undefine|package|description|&command_section_name;|changelog)(?=($|[^&a_valid_char_in_macro_names;]))" />
+        <RegExpr attribute="Macro call" context="macro content in parenthesis" String="%[&a_valid_char_in_macro_names;]*\(" />
+        <RegExpr attribute="Macro call" context="macro content in braces" String="(%|\$)\{" />
+        <RegExpr attribute="Macro call" context="#pop" String="(%|\$)([&a_valid_char_in_macro_names;]{1,}|\*|\#)(?=($|[^&a_valid_char_in_macro_names;]))" /> <!-- ')' and '}' are only allowed as macro terminator in the lookahead because when you do something like %__make %{?jobs:-j %jobs}, then the "%jobs" is a valid macro. However, the disadvantage is that a line like "%abc} isn't marked as error. But it is to complicate to distinguish this properly. -->
+        <RegExpr attribute="Error" context="#pop" String="(%|\$)([&a_valid_char_in_macro_names;]{1,}|\*|\#)" />
+        <AnyChar attribute="Error" context="#pop" String="%$" /> <!-- a single % or $ is also an error -->
+      </context>
+
+      <!-- Used internally by "handle_percent" -->
+      <context attribute="Macro call" lineEndContext="#pop#pop" name="macro content in parenthesis">
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+        <DetectChar attribute="Macro call" context="#pop#pop" char=")" />
+        <AnyChar attribute="Error" context="#stay" String="({}" />
+      </context>
+
+      <!-- Used internally by "handle_percent" -->
+      <context attribute="Macro call" lineEndContext="#pop#pop" name="macro content in braces">
+        <DetectChar attribute="Macro call" context="#pop#pop" char="}" />
+        <AnyChar attribute="Error" context="#stay" String="({)" />
+        <!--(This seems to be confusing instead of helping)AnyChar attribute="Keyword" context="#stay" String="!?:" /-->
+        <!-- Handle % -->
+        <AnyChar context="handle_percent" String="%$" lookAhead="true" />
+      </context>
+
+    </contexts>
+
+    <itemDatas>
+      <!-- "Shell commands" is used for the sections like %prep, %build or %install, where you write
+      shell commands. -->
+      <itemData name="Shell commands" defStyleNum="dsNormal"/>
+      <!-- "Fallback for separator spaces" is used as a fallback context for spaces between
+      different contexts. For example: "%if 1 <= %number" has the contexts Keyword,
+      Integer, Keyword and Macro call. But the spaces between? They are using THIS
+      context. -->
+      <itemData name="Fallback for separator spaces" defStyleNum="dsNormal"/>
+      <itemData name="Keyword" defStyleNum="dsKeyword"/>
+      <itemData name="Comment" defStyleNum="dsComment"/>
+      <itemData name="Tag" defStyleNum="dsDataType"/>
+      <!-- "Enumeration" is used for data types where you can't use arbitrary strings but have 
+      to use predefined values (like in "Provides:" or "%undefine"). -->
+      <itemData name="Enumeration" defStyleNum="dsOthers"/>
+      <itemData name="String" defStyleNum="dsString"/>
+      <itemData name="Integer" defStyleNum="dsDecVal"/>
+      <!-- "Error" is used for problems that will always produce an error in the interpretation
+      process. -->
+      <itemData name="Error" defStyleNum="dsError"/>
+      <!-- "Warning" is used for problems that will maybe produce an error in the interpretation
+      process or will lead to unexpected results. -->
+      <itemData name="Warning" defStyleNum="dsError"/>
+      <!-- "Hint" is used for problems that will never produce an error in the interpretation
+      process and will always work like expected (the interpreter has error tolerance),
+      but that are claimed as bad or invalid .spec following the documentation. -->
+      <itemData name="Hint" defStyleNum="dsError"/>
+      <itemData name="Macro call" defStyleNum="dsFunction"/>
+      <itemData name="Section" defStyleNum="dsRegionMarker"/>
+      <itemData name="Alert" defStyleNum="dsAlert"/>
+      <itemData name="Escaped character" defStyleNum="dsChar"/>
+      <itemData name="Line break" defStyleNum="dsKeyword"/>
+    </itemDatas>
+
+  </highlighting>
+
+  <general>
+    <!-- defining all word deliminators except space and tab as weak -->
+    <keywords casesensitive="1" weakDeliminator=".():!+,-&lt;=&gt;%&amp;*/;?[]^{|}~\," />
+    <comments>
+      <comment name="singleLine" start="#"/>
+    </comments>
+  </general>
+
+</language>
openSUSE Build Service is sponsored by