{- This module was generated from data in the Kate syntax highlighting file diff.xml, version 1.11, by -} module Text.Highlighting.Kate.Syntax.Diff (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec hiding (State) import Data.Map (fromList) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) -- | Full name of language. syntaxName :: String syntaxName = "Diff" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.diff;*patch" -- | 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 parseExpressionInternal pEndLine -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "Diff" } context <- currentContext <|> (pushContext "Normal" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("Diff",["Normal"])], synStLanguage = "Diff", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do context <- currentContext case context of "Normal" -> return () "FindDiff" -> return () "File" -> return () "Chunk" -> return () "ChunkInFile" -> return () "RFile" -> return () "RChunk" -> return () "RChunkInFile" -> return () "RChunkNew" -> return () "RChunkInFileNew" -> return () "File" -> (popContext) >> pEndLine "Removed" -> (popContext) >> pEndLine "Added" -> (popContext) >> pEndLine "ChangedOld" -> (popContext) >> pEndLine "ChangedNew" -> (popContext) >> pEndLine _ -> 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) parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe NormalTok $ lookup context defaultAttributes)) regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24 = compileRegex "(\\@\\@|\\d).*$" regex_'5c'2a'2b'24 = compileRegex "\\*+$" regex_Only_in_'2e'2a'3a'2e'2a'24 = compileRegex "Only in .*:.*$" regex_diff'2e'2a'24 = compileRegex "diff.*$" regex_'3d'3d'3d'3d'2e'2a'24 = compileRegex "====.*$" regex_'28'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'29'2e'2a'24 = compileRegex "(\\*\\*\\*|\\-\\-\\-).*$" regex_'5c'2d'5c'2d'5c'2d'2e'2a'24 = compileRegex "\\-\\-\\-.*$" regex_'28'5c'2b'5c'2b'5c'2b'7c'5c'2d'5c'2d'5c'2d'29'2e'2a'24 = compileRegex "(\\+\\+\\+|\\-\\-\\-).*$" regex_'28'3d'3d'3d'3d'7c'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'7cdiff'7cOnly_in_'2e'2a'3a'29'2e'2a'24 = compileRegex "(====|\\*\\*\\*|\\-\\-\\-|diff|Only in .*:).*$" regex_Index'3a'2e'2a = compileRegex "Index:.*" regex_'28diff'7cOnly_in_'2e'2a'3a'29'2e'2a'24 = compileRegex "(diff|Only in .*:).*$" regex_'5c'2a'5c'2a'5c'2a_'2e'2a_'5c'2a'5c'2a'5c'2a'5c'2a'24 = compileRegex "\\*\\*\\* .* \\*\\*\\*\\*$" regex_'5c'2d'5c'2d'5c'2d_'2e'2a_'5c'2d'5c'2d'5c'2d'5c'2d'24 = compileRegex "\\-\\-\\- .* \\-\\-\\-\\-$" defaultAttributes = [("Normal",NormalTok),("FindDiff",NormalTok),("File",NormalTok),("Chunk",NormalTok),("ChunkInFile",NormalTok),("RFile",NormalTok),("RChunk",NormalTok),("RChunkInFile",NormalTok),("RChunkNew",NormalTok),("RChunkInFileNew",NormalTok),("File",KeywordTok),("Removed",StringTok),("Added",OtherTok),("ChangedOld",StringTok),("ChangedNew",OtherTok)] parseRules "Normal" = (((pColumn 0 >> pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24 >>= withAttribute DataTypeTok) >>~ pushContext "Chunk") <|> ((pColumn 0 >> pRegExpr regex_'5c'2a'2b'24 >>= withAttribute DataTypeTok) >>~ pushContext "RChunk") <|> ((pColumn 0 >> pRegExpr regex_Only_in_'2e'2a'3a'2e'2a'24 >>= withAttribute KeywordTok)) <|> ((pColumn 0 >> pRegExpr regex_diff'2e'2a'24 >>= withAttribute KeywordTok) >>~ pushContext "RFile") <|> ((pColumn 0 >> pRegExpr regex_'3d'3d'3d'3d'2e'2a'24 >>= withAttribute KeywordTok)) <|> ((pColumn 0 >> pRegExpr regex_'28'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'29'2e'2a'24 >>= withAttribute KeywordTok) >>~ pushContext "File") <|> ((parseRules "FindDiff")) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute NormalTok) >>~ pushContext "ChangedOld")) parseRules "FindDiff" = (((pColumn 0 >> pRegExpr regex_'5c'2d'5c'2d'5c'2d'2e'2a'24 >>= withAttribute KeywordTok)) <|> ((pColumn 0 >> pRegExpr regex_'28'5c'2b'5c'2b'5c'2b'7c'5c'2d'5c'2d'5c'2d'29'2e'2a'24 >>= withAttribute DataTypeTok)) <|> ((pColumn 0 >> pAnyChar "+>" >>= withAttribute OtherTok) >>~ pushContext "Added") <|> ((pColumn 0 >> pAnyChar "-<" >>= withAttribute StringTok) >>~ pushContext "Removed")) parseRules "File" = (((parseRules "FindDiff")) <|> ((pColumn 0 >> pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24 >>= withAttribute DataTypeTok) >>~ pushContext "ChunkInFile") <|> ((pColumn 0 >> pRegExpr regex_'5c'2a'2b'24 >>= withAttribute DataTypeTok) >>~ pushContext "RChunkInFile") <|> ((pColumn 0 >> pRegExpr regex_'28'3d'3d'3d'3d'7c'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'7cdiff'7cOnly_in_'2e'2a'3a'29'2e'2a'24 >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute StringTok) >>~ pushContext "ChangedOld")) parseRules "Chunk" = (((parseRules "FindDiff")) <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute StringTok) >>~ pushContext "ChangedOld")) parseRules "ChunkInFile" = (((parseRules "FindDiff")) <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext)) <|> ((pColumn 0 >> pRegExpr regex_Index'3a'2e'2a >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'28'3d'3d'3d'3d'7c'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'7cdiff'7cOnly_in_'2e'2a'3a'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute StringTok) >>~ pushContext "ChangedOld")) parseRules "RFile" = (((pColumn 0 >> lookAhead (pRegExpr regex_'28diff'7cOnly_in_'2e'2a'3a'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext)) <|> ((pColumn 0 >> pRegExpr regex_'28'3d'3d'3d'3d'7c'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'7cdiff'7cOnly_in_'2e'2a'3a'29'2e'2a'24 >>= withAttribute DataTypeTok)) <|> ((pColumn 0 >> pRegExpr regex_'5c'2a'2b'24 >>= withAttribute DataTypeTok) >>~ pushContext "RChunkInFile") <|> ((parseRules "File"))) parseRules "RChunk" = (((pColumn 0 >> pRegExpr regex_'5c'2a'5c'2a'5c'2a_'2e'2a_'5c'2a'5c'2a'5c'2a'5c'2a'24 >>= withAttribute DataTypeTok)) <|> ((pColumn 0 >> pRegExpr regex_'5c'2d'5c'2d'5c'2d_'2e'2a_'5c'2d'5c'2d'5c'2d'5c'2d'24 >>= withAttribute DataTypeTok) >>~ pushContext "RChunkNew") <|> ((parseRules "Chunk"))) parseRules "RChunkInFile" = (((pColumn 0 >> pRegExpr regex_'5c'2a'5c'2a'5c'2a_'2e'2a_'5c'2a'5c'2a'5c'2a'5c'2a'24 >>= withAttribute DataTypeTok)) <|> ((pColumn 0 >> pRegExpr regex_'5c'2d'5c'2d'5c'2d_'2e'2a_'5c'2d'5c'2d'5c'2d'5c'2d'24 >>= withAttribute DataTypeTok) >>~ pushContext "RChunkInFileNew") <|> ((parseRules "ChunkInFile"))) parseRules "RChunkNew" = (((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext >> popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext "ChangedNew") <|> ((parseRules "FindDiff"))) parseRules "RChunkInFileNew" = (((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext >> popContext)) <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'28'3d'3d'3d'3d'7c'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'7cdiff'7cOnly_in_'2e'2a'3a'29'2e'2a'24) >> return (NormalTok,"") ) >>~ (popContext >> popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext "ChangedNew") <|> ((parseRules "FindDiff"))) parseRules "File" = pzero parseRules "Removed" = pzero parseRules "Added" = pzero parseRules "ChangedOld" = pzero parseRules "ChangedNew" = pzero parseRules "" = parseRules "Normal" parseRules x = fail $ "Unknown context" ++ x