{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Diff (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "Diff" , sFilename = "diff.xml" , sShortname = "Diff" , sContexts = fromList [ ( "Added" , Context { cName = "Added" , cSyntax = "Diff" , cRules = [] , cAttribute = VariableTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ChangedNew" , Context { cName = "ChangedNew" , cSyntax = "Diff" , cRules = [] , cAttribute = VariableTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ChangedOld" , Context { cName = "ChangedOld" , cSyntax = "Diff" , cRules = [] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Chunk" , Context { cName = "Chunk" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = IncludeRules ( "Diff" , "FindDiff" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(\\@\\@|\\d).*$" , reCompiled = Just (compileRegex True "(\\@\\@|\\d).*$") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '!' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "ChangedOld" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ChunkInFile" , Context { cName = "ChunkInFile" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = IncludeRules ( "Diff" , "FindDiff" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(\\@\\@|\\d).*$" , reCompiled = Just (compileRegex True "(\\@\\@|\\d).*$") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "Index:.*" , reCompiled = Just (compileRegex True "Index:.*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$" , reCompiled = Just (compileRegex True "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '!' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "ChangedOld" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "File" , Context { cName = "File" , cSyntax = "Diff" , cRules = [] , cAttribute = KeywordTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindDiff" , Context { cName = "FindDiff" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\-\\-\\-.*$" , reCompiled = Just (compileRegex True "\\-\\-\\-.*$") , reCaseSensitive = True } , rAttribute = KeywordTok , 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 = Just 0 , rContextSwitch = [] } , Rule { rMatcher = AnyChar "+>" , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "Added" ) ] } , Rule { rMatcher = AnyChar "-<" , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "Removed" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(\\@\\@|\\d).*$" , reCompiled = Just (compileRegex True "(\\@\\@|\\d).*$") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "Chunk" ) ] } , 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 = Just 0 , rContextSwitch = [ Push ( "Diff" , "RChunk" ) ] } , Rule { rMatcher = RegExpr RE { reString = "Only in .*:.*$" , reCompiled = Just (compileRegex True "Only in .*:.*$") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "diff.*$" , reCompiled = Just (compileRegex True "diff.*$") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "RFile" ) ] } , Rule { rMatcher = RegExpr RE { reString = "====.*$" , reCompiled = Just (compileRegex True "====.*$") , reCaseSensitive = True } , rAttribute = KeywordTok , 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 = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "File" ) ] } , Rule { rMatcher = IncludeRules ( "Diff" , "FindDiff" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '!' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "ChangedOld" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "RChunk" , Context { cName = "RChunk" , cSyntax = "Diff" , cRules = [ 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 = 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 = Just 0 , rContextSwitch = [ Push ( "Diff" , "RChunkNew" ) ] } , Rule { rMatcher = IncludeRules ( "Diff" , "Chunk" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "RChunkInFile" , Context { cName = "RChunkInFile" , cSyntax = "Diff" , cRules = [ 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 = 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 = Just 0 , rContextSwitch = [ Push ( "Diff" , "RChunkInFileNew" ) ] } , Rule { rMatcher = IncludeRules ( "Diff" , "ChunkInFile" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "RChunkInFileNew" , Context { cName = "RChunkInFileNew" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(\\@\\@|\\d).*$" , reCompiled = Just (compileRegex True "(\\@\\@|\\d).*$") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$" , reCompiled = Just (compileRegex True "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = DetectChar '!' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "ChangedNew" ) ] } , Rule { rMatcher = IncludeRules ( "Diff" , "FindDiff" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "RChunkNew" , Context { cName = "RChunkNew" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(\\@\\@|\\d).*$" , reCompiled = Just (compileRegex True "(\\@\\@|\\d).*$") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = DetectChar '!' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Diff" , "ChangedNew" ) ] } , Rule { rMatcher = IncludeRules ( "Diff" , "FindDiff" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "RFile" , Context { cName = "RFile" , cSyntax = "Diff" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(diff|Only in .*:).*$" , reCompiled = Just (compileRegex True "(diff|Only in .*:).*$") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$" , reCompiled = Just (compileRegex True "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$") , 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 = Just 0 , rContextSwitch = [ Push ( "Diff" , "RChunkInFile" ) ] } , Rule { rMatcher = IncludeRules ( "Diff" , "File" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Removed" , Context { cName = "Removed" , cSyntax = "Diff" , cRules = [] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.diff" , "*patch" ] , sStartingContext = "Normal" }