module Agda.Utils.IO.Directory
  ( copyDirContent
  )
where
import Control.Monad
import Control.Monad.Writer
import System.Directory
import System.FilePath
import Data.ByteString as BS
copyDirContent :: FilePath -> FilePath -> IO ()
copyDirContent src dest = mapM_ performAction =<< do
  (`appEndo` []) <$> execWriterT (copyDirContentDryRun src dest)
data CopyDirAction
  = MkDir    FilePath
      
  | CopyFile FilePath FilePath
      
performAction :: CopyDirAction -> IO ()
performAction = \case
  MkDir d           -> createDirectoryIfMissing True d
  CopyFile src dest -> copyIfChanged src dest
copyDirContentDryRun :: FilePath -> FilePath -> WriterT (Endo [CopyDirAction]) IO ()
copyDirContentDryRun src dest = do
  tell $ Endo (MkDir dest :)
  chlds <- lift $ getDirectoryContents src
  forM_ chlds $ \ x -> do
    isDir <- lift $ doesDirectoryExist (src </> x)
    case isDir of
      _ | x == "." || x == ".." -> return ()
      True  -> copyDirContentDryRun (src </> x) (dest </> x)
      False -> tell $ Endo (CopyFile (src </> x) (dest </> x) :)
copyIfChanged :: FilePath -> FilePath -> IO ()
copyIfChanged src dst = do
  exist <- doesFileExist dst
  if not exist then copyFile src dst else do
    new <- BS.readFile src
    old <- BS.readFile dst
    unless (old == new) $ copyFile src dst