{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Changelog (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "ChangeLog" , sFilename = "changelog.xml" , sShortname = "Changelog" , sContexts = fromList [ ( "Normal" , Context { cName = "Normal" , cSyntax = "ChangeLog" , cRules = [ Rule { rMatcher = DetectChar '*' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "ChangeLog" , "entry" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\d\\d\\d\\d\\s*-\\s*\\d\\d\\s*-\\s*\\d\\d\\s*" , reCompiled = Just (compileRegex True "\\d\\d\\d\\d\\s*-\\s*\\d\\d\\s*-\\s*\\d\\d\\s*") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "ChangeLog" , "line" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "entry" , Context { cName = "entry" , cSyntax = "ChangeLog" , cRules = [ Rule { rMatcher = RegExpr RE { reString = ".*:" , reCompiled = Just (compileRegex True ".*:") , reCaseSensitive = True } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "line" , Context { cName = "line" , cSyntax = "ChangeLog" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(\\w\\s*)+" , reCompiled = Just (compileRegex True "(\\w\\s*)+") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "<.*>\\s*$" , reCompiled = Just (compileRegex True "<.*>\\s*$") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Dominik Haumann (dhdev@gmx.de)" , sVersion = "2" , sLicense = "LGPL" , sExtensions = [ "ChangeLog" ] , sStartingContext = "Normal" }