module Fixme.Diff
  ( newCommentsFromDiff
  ) where
import Protolude
import qualified Data.ByteString as ByteString
import qualified Data.Text as Text
import Text.Diff.Parse (parseDiff)
import Text.Diff.Parse.Types
  ( Annotation(..)
  , Content(..)
  , FileDelta(..)
  , FileStatus(..)
  , Hunk(..)
  , Line(..)
  )
import Fixme.Comment
  ( Comment
  , Language
  , languageForFile
  , parseComments
  , startLine
  , endLine
  )
newCommentsFromDiff :: ByteString -> Either Text [Comment]
newCommentsFromDiff diff
  | ByteString.null diff = Right []
  | otherwise = bimap toS (join . catMaybes . map getNewCommentsForFile) . parseDiff . toS $ diff
  where
    getNewCommentsForFile (FileDelta Deleted _ _ _) = Just []
    getNewCommentsForFile (FileDelta _ _ _ Binary) = Just []
    getNewCommentsForFile (FileDelta _ _ filename (Hunks hunks)) =
      case languageForFile (toS filename) of
        Nothing -> Nothing
        Just language -> Just $ concatMap (getNewCommentsForHunk filename language) hunks
getNewCommentsForHunk :: Text -> Language -> Hunk -> [Comment]
getNewCommentsForHunk filename language hunk =
  let comments = parseComments (Just filename) language (toS afterText)
  in filterInsertions addedLineNumbers comments
  where
    
    
    afterText :: Text
    afterText = Text.unlines $ map lineContent rightSide
    
    
    
    
    
    
    filterInsertions :: [Int] -> [Comment] -> [Comment]
    filterInsertions [] _ = []
    filterInsertions _ [] = []
    filterInsertions lineNums@(i:lineNums') comments@(c:comments') =
      case lineInComment i c of
        LT -> filterInsertions lineNums' comments
        EQ -> c:(filterInsertions lineNums comments')
        GT -> filterInsertions lineNums comments'
    
    
    lineInComment :: Int -> Comment -> Ordering
    lineInComment lineNum comment
      | lineNum > endLine comment = GT
      | lineNum < startLine comment = LT
      | otherwise = EQ
    
    
    addedLineNumbers :: [Int]
    addedLineNumbers =
      [ i | (i, line) <- (zip [0..] rightSide)
          , lineAnnotation line == Added ]
    
    
    rightSide :: [Line]
    rightSide = [ line | line <- hunkLines hunk, lineAnnotation line /= Removed ]