{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Rest (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "reStructuredText" , sFilename = "rest.xml" , sShortname = "Rest" , sContexts = fromList [ ( "Code" , Context { cName = "Code" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(.|$)" , reCompiled = Just (compileRegex True "(.|$)") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "CodeBlock" , Context { cName = "CodeBlock" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(\\s+)(?=\\S)" , reCompiled = Just (compileRegex True "(\\s+)(?=\\S)") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "reStructuredText" , "Code" ) ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment" , Context { cName = "Comment" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%1 " , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(.|$)" , reCompiled = Just (compileRegex True "(.|$)") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , 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 = True } ) , ( "Field" , Context { cName = "Field" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = DetectChar ':' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ':' , rAttribute = FunctionTok , 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 = FunctionTok , 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 = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "reStructuredText" , "InlineMarkup" ) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = FunctionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "InlineMarkup" , Context { cName = "InlineMarkup" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(^|[-\\s'\"\\(\\[{/:\\.,;!\\?\\\\]|$)" , reCompiled = Just (compileRegex True "(^|[-\\s'\"\\(\\[{/:\\.,;!\\?\\\\]|$)") , reCaseSensitive = True } , rAttribute = DataTypeTok , 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 = FunctionTok , 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 = FunctionTok , 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 = [] } , 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 = [] } , 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 = [] } , Rule { rMatcher = RegExpr RE { reString = "(^|[-\\s'\"\\(\\[{/:\\.,;!\\?\\\\]|$)" , reCompiled = Just (compileRegex True "(^|[-\\s'\"\\(\\[{/:\\.,;!\\?\\\\]|$)") , reCaseSensitive = True } , rAttribute = NormalTok , 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 = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "reStructuredText" , "InlineMarkup" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\.\\. \\[(\\d+|#|\\*|#[\\w_\\.:\\+\\-]+)\\]\\s" , reCompiled = Just (compileRegex True "\\s*\\.\\. \\[(\\d+|#|\\*|#[\\w_\\.:\\+\\-]+)\\]\\s") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\.\\. \\[[\\w_\\.:\\+\\-]+\\]\\s" , reCompiled = Just (compileRegex True "\\s*\\.\\. \\[[\\w_\\.:\\+\\-]+\\]\\s") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*(\\.\\. (__:|_[\\w_\\.:\\+\\- ]+:(\\s|$))|__ )" , reCompiled = Just (compileRegex True "\\s*(\\.\\. (__:|_[\\w_\\.:\\+\\- ]+:(\\s|$))|__ )") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\.\\. code-block::" , reCompiled = Just (compileRegex True "\\s*\\.\\. code-block::") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "reStructuredText" , "CodeBlock" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\.\\. [\\w-_\\.]+::(\\s|$)" , reCompiled = Just (compileRegex True "\\s*\\.\\. [\\w-_\\.]+::(\\s|$)") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "::$" , reCompiled = Just (compileRegex True "::$") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "reStructuredText" , "CodeBlock" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\.\\. \\|[\\w_\\.:\\+\\- ]+\\|\\s+[\\w_\\.:\\+\\-]+::\\s" , reCompiled = Just (compileRegex True "\\s*\\.\\. \\|[\\w_\\.:\\+\\- ]+\\|\\s+[\\w_\\.:\\+\\-]+::\\s") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = ":(?=([^:]*\\\\:)*[^:]*:(\\s|$))" , reCompiled = Just (compileRegex True ":(?=([^:]*\\\\:)*[^:]*:(\\s|$))") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "reStructuredText" , "Field" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(\\s*)\\.\\.\\s(?![\\w-_\\.]+::(\\s|$))" , reCompiled = Just (compileRegex True "(\\s*)\\.\\.\\s(?![\\w-_\\.]+::(\\s|$))") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "reStructuredText" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Role" , Context { cName = "Role" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = DetectChar '`' , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "reStructuredText" , "InterpretedText" ) ] } ] , cAttribute = KeywordTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "TrailingRole" , Context { cName = "TrailingRole" , cSyntax = "reStructuredText" , cRules = [ Rule { rMatcher = RegExpr RE { reString = ":[\\w-_\\.\\+]+:" , reCompiled = Just (compileRegex True ":[\\w-_\\.\\+]+:") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = KeywordTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.rst" ] , sStartingContext = "Normal" }