{- 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.Definitions import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) -- | 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 -> Either String [SourceLine] highlight input = case runParser parseSource startingState "source" input of Left err -> Left $ show err Right result -> Right result -- | Parse an expression using appropriate local context. parseExpression :: GenParser Char SyntaxState LabeledSource parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "Diff" } context <- currentContext <|> (pushContext "Normal" >> currentContext) result <- parseRules context updateState $ \st -> st { synStLanguage = oldLang } return result parseSource = do lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents } result <- manyTill parseSourceLine eof return $ map normalizeHighlighting result startingState = SyntaxState {synStContexts = fromList [("Diff",["Normal"])], synStLanguage = "Diff", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "Normal" -> return () >> pHandleEndLine "FindDiff" -> return () >> pHandleEndLine "File" -> return () >> pHandleEndLine "Chunk" -> return () >> pHandleEndLine "ChunkInFile" -> return () >> pHandleEndLine "RFile" -> return () >> pHandleEndLine "RChunk" -> return () >> pHandleEndLine "RChunkInFile" -> return () >> pHandleEndLine "RChunkNew" -> return () >> pHandleEndLine "RChunkInFileNew" -> return () >> pHandleEndLine "File" -> (popContext) >> pEndLine "Removed" -> (popContext) >> pEndLine "Added" -> (popContext) >> pEndLine "ChangedOld" -> (popContext) >> pEndLine "ChangedNew" -> (popContext) >> pEndLine _ -> pHandleEndLine withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" let labs = attr : maybeToList (lookup attr styles) st <- getState let oldCharsParsed = synStCharsParsedInLine st let prevchar = if null txt then '\n' else last txt updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } return (labs, txt) styles = [("File","kw"),("Header","dt"),("Removed line","st"),("Added line","ot"),("Changed line (old)","st"),("Changed line (new)","ot")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ 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","Normal Text"),("FindDiff","Normal Text"),("File","Normal Text"),("Chunk","Normal Text"),("ChunkInFile","Normal Text"),("RFile","Normal Text"),("RChunk","Normal Text"),("RChunkInFile","Normal Text"),("RChunkNew","Normal Text"),("RChunkInFileNew","Normal Text"),("File","File"),("Removed","Removed line"),("Added","Added line"),("ChangedOld","Changed line (old)"),("ChangedNew","Changed line (new)")] parseRules "Normal" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24 >>= withAttribute "Header") >>~ pushContext "Chunk") <|> ((pColumn 0 >> pRegExpr regex_'5c'2a'2b'24 >>= withAttribute "Header") >>~ pushContext "RChunk") <|> ((pColumn 0 >> pRegExpr regex_Only_in_'2e'2a'3a'2e'2a'24 >>= withAttribute "File")) <|> ((pColumn 0 >> pRegExpr regex_diff'2e'2a'24 >>= withAttribute "File") >>~ pushContext "RFile") <|> ((pColumn 0 >> pRegExpr regex_'3d'3d'3d'3d'2e'2a'24 >>= withAttribute "File")) <|> ((pColumn 0 >> pRegExpr regex_'28'5c'2a'5c'2a'5c'2a'7c'5c'2d'5c'2d'5c'2d'29'2e'2a'24 >>= withAttribute "File") >>~ pushContext "File") <|> ((parseRules "FindDiff")) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute "Changed line") >>~ pushContext "ChangedOld")) return (attr, result) parseRules "FindDiff" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'5c'2d'5c'2d'5c'2d'2e'2a'24 >>= withAttribute "File")) <|> ((pColumn 0 >> pRegExpr regex_'28'5c'2b'5c'2b'5c'2b'7c'5c'2d'5c'2d'5c'2d'29'2e'2a'24 >>= withAttribute "Header")) <|> ((pColumn 0 >> pAnyChar "+>" >>= withAttribute "Added line") >>~ pushContext "Added") <|> ((pColumn 0 >> pAnyChar "-<" >>= withAttribute "Removed line") >>~ pushContext "Removed")) return (attr, result) parseRules "File" = do (attr, result) <- (((parseRules "FindDiff")) <|> ((pColumn 0 >> pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24 >>= withAttribute "Header") >>~ pushContext "ChunkInFile") <|> ((pColumn 0 >> pRegExpr regex_'5c'2a'2b'24 >>= withAttribute "Header") >>~ 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 "File") >>~ (popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute "Changed line (old)") >>~ pushContext "ChangedOld")) return (attr, result) parseRules "Chunk" = do (attr, result) <- (((parseRules "FindDiff")) <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return ([],"") ) >>~ (popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute "Changed line (old)") >>~ pushContext "ChangedOld")) return (attr, result) parseRules "ChunkInFile" = do (attr, result) <- (((parseRules "FindDiff")) <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return ([],"") ) >>~ (popContext)) <|> ((pColumn 0 >> pRegExpr regex_Index'3a'2e'2a >>= withAttribute "Normal Text") >>~ (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 ([],"") ) >>~ (popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute "Changed line (old)") >>~ pushContext "ChangedOld")) return (attr, result) parseRules "RFile" = do (attr, result) <- (((pColumn 0 >> lookAhead (pRegExpr regex_'28diff'7cOnly_in_'2e'2a'3a'29'2e'2a'24) >> return ([],"") ) >>~ (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 "Header")) <|> ((pColumn 0 >> pRegExpr regex_'5c'2a'2b'24 >>= withAttribute "Header") >>~ pushContext "RChunkInFile") <|> ((parseRules "File"))) return (attr, result) parseRules "RChunk" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'5c'2a'5c'2a'5c'2a_'2e'2a_'5c'2a'5c'2a'5c'2a'5c'2a'24 >>= withAttribute "Header")) <|> ((pColumn 0 >> pRegExpr regex_'5c'2d'5c'2d'5c'2d_'2e'2a_'5c'2d'5c'2d'5c'2d'5c'2d'24 >>= withAttribute "Header") >>~ pushContext "RChunkNew") <|> ((parseRules "Chunk"))) return (attr, result) parseRules "RChunkInFile" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'5c'2a'5c'2a'5c'2a_'2e'2a_'5c'2a'5c'2a'5c'2a'5c'2a'24 >>= withAttribute "Header")) <|> ((pColumn 0 >> pRegExpr regex_'5c'2d'5c'2d'5c'2d_'2e'2a_'5c'2d'5c'2d'5c'2d'5c'2d'24 >>= withAttribute "Header") >>~ pushContext "RChunkInFileNew") <|> ((parseRules "ChunkInFile"))) return (attr, result) parseRules "RChunkNew" = do (attr, result) <- (((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return ([],"") ) >>~ (popContext >> popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute "Changed line (new)") >>~ pushContext "ChangedNew") <|> ((parseRules "FindDiff"))) return (attr, result) parseRules "RChunkInFileNew" = do (attr, result) <- (((pColumn 0 >> lookAhead (pRegExpr regex_'28'5c'40'5c'40'7c'5cd'29'2e'2a'24) >> return ([],"") ) >>~ (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 ([],"") ) >>~ (popContext >> popContext)) <|> ((pColumn 0 >> pDetectChar False '!' >>= withAttribute "Changed line (new)") >>~ pushContext "ChangedNew") <|> ((parseRules "FindDiff"))) return (attr, result) parseRules "File" = pzero parseRules "Removed" = pzero parseRules "Added" = pzero parseRules "ChangedOld" = pzero parseRules "ChangedNew" = pzero parseRules "" = parseRules "Normal" parseRules x = fail $ "Unknown context" ++ x