FileDiff.hs 1.47 KB

module CLI.FileDiff where

import CLI.Types
import Data.List qualified as L
import Data.Text qualified as T
import Data.Text.IO qualified as TIO
import Data.TreeDiff.Class
import Data.TreeDiff.Pretty
import Gargantext.Prelude (HasCallStack, unless, exitFailure)
import Options.Applicative
import Prelude

-- | Renders in a pretty way the content of two golden files. The
-- first file should contain the expected output, the second the
-- actual data generated by the test suite.
fileDiffCLI :: GoldenFileDiffArgs -> IO ()
fileDiffCLI (GoldenFileDiffArgs refPath newPath) = do
  ref <- T.lines <$> TIO.readFile refPath
  new <- T.lines <$> TIO.readFile newPath

  let differences = filter (\(r,n) -> r /= n) $ zip ref new

  unless (L.null differences) $ do
    putStrLn $ show $ ansiWlEditExpr $ ediff' (map fst differences) (map snd differences)
    exitFailure

fileDiffCmd :: HasCallStack => Mod CommandFields CLI
fileDiffCmd = command "golden-file-diff" (info (helper <*> fmap CLISub filediff_p) (progDesc "Compare the output of two golden files."))

filediff_p :: Parser CLICmd
filediff_p = fmap CCMD_golden_file_diff $ GoldenFileDiffArgs
  <$> ( strOption ( long "expected"
                    <> metavar "FILEPATH"
                    <> help "Path to the file containing the expected output."
                    ) )
  <*> ( strOption ( long "actual"
                    <> metavar "FILEPATH"
                    <> help "Path to the file containing the actual output."
                    ) )