module CopyFileWithMetadata where import Prelude () import System.Directory.Internal.Prelude import System.Directory.Internal import System.Directory.OsPath import TestUtils () import Util (TestEnv) import qualified Util as T import qualified Data.List as List main :: TestEnv -> IO () main _t = (`finally` cleanup) $ do -- prepare source file writeFile "a" contents writeFile "b" "To be replaced\n" setModificationTime "a" mtime modifyWritable False "a" perm <- getPermissions "a" -- sanity check T.expectEq _t () ["a", "b"] . List.sort =<< listDirectory "." -- copy file copyFileWithMetadata "a" "b" copyFileWithMetadata "a" "c" -- make sure we got the right results T.expectEq _t () ["a", "b", "c"] . List.sort =<< listDirectory "." for_ ["b", "c"] $ \ f -> do T.expectEq _t f perm =<< getPermissions f T.expectEq _t f mtime =<< getModificationTime f T.expectEq _t f contents =<< readFile (so f) where contents = "This is the data\n" mtime = read "2000-01-01 00:00:00Z" cleanup = do -- needed to ensure the test runner can clean up our mess modifyWritable True "a" `catchIOError` \ _ -> return () modifyWritable True "b" `catchIOError` \ _ -> return () modifyWritable True "c" `catchIOError` \ _ -> return () modifyWritable b f = do perm <- getPermissions f setPermissions f (setOwnerWritable b perm)