{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Relaxngcompact (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "RelaxNG-Compact" , sFilename = "relaxngcompact.xml" , sShortname = "Relaxngcompact" , sContexts = fromList [ ( "Comments" , Context { cName = "Comments" , cSyntax = "RelaxNG-Compact" , cRules = [] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Definitions" , Context { cName = "Definitions" , cSyntax = "RelaxNG-Compact" , cRules = [ Rule { rMatcher = DetectChar '=' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = FunctionTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Node Names" , Context { cName = "Node Names" , cSyntax = "RelaxNG-Compact" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal Text" , Context { cName = "Normal Text" , cSyntax = "RelaxNG-Compact" , cRules = [ Rule { rMatcher = DetectChar '#' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "RelaxNG-Compact" , "Comments" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "RelaxNG-Compact" , "String" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./;<=>?[\\]^{|}~" } (makeWordSet True [ "datatypes" , "default" , "div" , "empty" , "external" , "grammar" , "include" , "inherit" , "list" , "mixed" , "namespace" , "notAllowed" , "parent" , "start" , "token" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./;<=>?[\\]^{|}~" } (makeWordSet True [ "attribute" , "element" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "RelaxNG-Compact" , "Node Names" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,./;<=>?[\\]^{|}~" } (makeWordSet True [ "string" , "text" , "xsd:ENTITIES" , "xsd:ENTITY" , "xsd:ID" , "xsd:IDREF" , "xsd:IDREFS" , "xsd:NCName" , "xsd:NMTOKEN" , "xsd:NMTOKENS" , "xsd:NOTATION" , "xsd:Name" , "xsd:QName" , "xsd:anyURI" , "xsd:base64Binary" , "xsd:boolean" , "xsd:byte" , "xsd:date" , "xsd:dateTime" , "xsd:decimal" , "xsd:double" , "xsd:duration" , "xsd:float" , "xsd:gDay" , "xsd:gMonth" , "xsd:gMonthDay" , "xsd:gYear" , "xsd:gYearMonth" , "xsd:hexBinary" , "xsd:int" , "xsd:integer" , "xsd:language" , "xsd:long" , "xsd:negativeInteger" , "xsd:nonNegativeInteger" , "xsd:nonPositiveInteger" , "xsd:normalizedString" , "xsd:positiveInteger" , "xsd:short" , "xsd:string" , "xsd:time" , "xsd:token" , "xsd:unsignedByte" , "xsd:unsignedInt" , "xsd:unsignedLong" , "xsd:unsignedShort" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[\\w\\.-]+[\\s]+=" , reCompiled = Just (compileRegex True "[\\w\\.-]+[\\s]+=") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "RelaxNG-Compact" , "Definitions" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "String" , Context { cName = "String" , cSyntax = "RelaxNG-Compact" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Rintze Zelle" , sVersion = "1" , sLicense = "LGPL" , sExtensions = [ "*.rnc" ] , sStartingContext = "Normal Text" }