{-# LANGUAGE BangPatterns #-}

-- |
-- Module      : Test.Amazonka.Diff
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay <brendan.g.hay+amazonka@gmail.com>
-- Stability   : provisional
-- Portability : non-portable (GHC extensions)
module Test.Amazonka.Diff where

import System.IO
import System.IO.Temp
import System.Process
import Text.Groom

-- | Display the difference between two Haskell values,
-- with control over the diff parameters.
diff :: (Show a, Show b) => a -> b -> IO String
diff :: forall a b. (Show a, Show b) => a -> b -> IO String
diff a
e b
a =
  forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"diff_expect" forall a b. (a -> b) -> a -> b
$ \String
ep Handle
eh ->
    forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"diff_actual" forall a b. (a -> b) -> a -> b
$ \String
ap Handle
ah -> do
      Handle -> String -> IO ()
hPutStrLn Handle
eh (forall a. Show a => a -> String
groom a
e) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hClose Handle
eh
      Handle -> String -> IO ()
hPutStrLn Handle
ah (forall a. Show a => a -> String
groom b
a) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hClose Handle
ah
      (ExitCode
_, !String
out, !String
err) <-
        String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode String
"diff" [String
"-U", String
"3", String
ep, String
ap] []
      forall (m :: * -> *) a. Monad m => a -> m a
return (String
out forall a. [a] -> [a] -> [a]
++ String
"\n" forall a. [a] -> [a] -> [a]
++ String
err)