aboutsummaryrefslogtreecommitdiffstats
path: root/app/Patch.hs
blob: 9e6ed884a9a76fce350c164ca003e705c5d20655 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
{-# LANGUAGE DerivingStrategies #-}

module Patch
  ( Patch,
    parse,
  )
where

import Control.Exception (throw)
import Data.Binary (Binary (..))
import Data.Text qualified as T
import Exception qualified as E
import GHC.Generics (Generic)
import Render ((<<<))
import Render qualified as P
import Text.Diff.Extra ()
import Text.Diff.Parse qualified as D
import Text.Diff.Parse.Types qualified as D

newtype Patch = Patch
  { fileDeltas :: D.FileDeltas
  }
  deriving (Show, Generic)
  deriving newtype (Binary)

parse :: T.Text -> Patch
parse = either (throw . E.InvalidDiff) Patch . D.parseDiff

instance P.Render Patch where
  render = P.render . P.Detailed

instance P.Render (P.Detailed Patch) where
  render (P.Detailed (Patch {..})) =
    P.vsep $ map prettyFileDelta fileDeltas
    where
      prettyFileDelta (D.FileDelta {..}) = prettyContent fileDeltaContent
      prettyContent D.Binary = P.emptyDoc
      prettyContent (D.Hunks hunks) = P.vsep (map prettyHunk hunks)
      prettyHunk (D.Hunk {..}) = P.vsep $ map prettyLine hunkLines
      prettyLine (D.Line {..}) =
        case lineAnnotation of
          D.Added -> P.styled [P.color P.Green] $ P.plus @P.AnsiStyle <<< lineContent
          D.Removed -> P.styled [P.color P.Red] $ P.minus @P.AnsiStyle <<< lineContent
          D.Context -> P.styled [P.color P.White] $ P.space @P.AnsiStyle <<< lineContent