{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK hide #-}
module Distribution.Compat.CopyFile
( copyFile
, copyFileChanged
, filesEqual
, copyOrdinaryFile
, copyExecutableFile
, setFileOrdinary
, setFileExecutable
, setDirOrdinary
) where
import Distribution.Compat.Prelude
import Prelude ()
#ifndef mingw32_HOST_OS
import Distribution.Compat.Internal.TempFile
import Control.Exception
( bracketOnError )
import qualified Data.ByteString.Lazy as BSL
import Data.Bits
( (.|.) )
import System.IO.Error
( ioeSetLocation )
import System.Directory
( doesFileExist, renameFile, removeFile )
import System.FilePath
( takeDirectory )
import System.IO
( IOMode(ReadMode), hClose, hGetBuf, hPutBuf, hFileSize
, withBinaryFile )
import Foreign
( allocaBytes )
import System.Posix.Types
( FileMode )
import System.Posix.Files
( getFileStatus, fileMode, setFileMode )
#else /* else mingw32_HOST_OS */
import qualified Data.ByteString.Lazy as BSL
import System.IO.Error
( ioeSetLocation )
import System.Directory
( doesFileExist )
import System.FilePath
( addTrailingPathSeparator
, hasTrailingPathSeparator
, isPathSeparator
, isRelative
, joinDrive
, joinPath
, pathSeparator
, pathSeparators
, splitDirectories
, splitDrive
)
import System.IO
( IOMode(ReadMode), hFileSize
, withBinaryFile )
import qualified System.Win32.File as Win32 ( copyFile )
#endif /* mingw32_HOST_OS */
copyOrdinaryFile, copyExecutableFile :: FilePath -> FilePath -> IO ()
copyOrdinaryFile :: FilePath -> FilePath -> IO ()
copyOrdinaryFile FilePath
src FilePath
dest = FilePath -> FilePath -> IO ()
copyFile FilePath
src FilePath
dest IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FilePath -> IO ()
setFileOrdinary FilePath
dest
copyExecutableFile :: FilePath -> FilePath -> IO ()
copyExecutableFile FilePath
src FilePath
dest = FilePath -> FilePath -> IO ()
copyFile FilePath
src FilePath
dest IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FilePath -> IO ()
setFileExecutable FilePath
dest
setFileOrdinary, setFileExecutable, setDirOrdinary :: FilePath -> IO ()
#ifndef mingw32_HOST_OS
setFileOrdinary path = addFileMode path 0o644
setFileExecutable path = addFileMode path 0o755
addFileMode :: FilePath -> FileMode -> IO ()
addFileMode name m = do
o <- fileMode <$> getFileStatus name
setFileMode name (m .|. o)
#else
setFileOrdinary :: FilePath -> IO ()
setFileOrdinary FilePath
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
setFileExecutable :: FilePath -> IO ()
setFileExecutable FilePath
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#endif
setDirOrdinary :: FilePath -> IO ()
setDirOrdinary = FilePath -> IO ()
setFileExecutable
copyFile :: FilePath -> FilePath -> IO ()
copyFile :: FilePath -> FilePath -> IO ()
copyFile FilePath
fromFPath FilePath
toFPath =
IO ()
copy
IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIO` (\IOError
ioe -> IOError -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOError -> FilePath -> IOError
ioeSetLocation IOError
ioe FilePath
"copyFile"))
where
#ifndef mingw32_HOST_OS
copy = withBinaryFile fromFPath ReadMode $ \hFrom ->
bracketOnError openTmp cleanTmp $ \(tmpFPath, hTmp) ->
do allocaBytes bufferSize $ copyContents hFrom hTmp
hClose hTmp
renameFile tmpFPath toFPath
openTmp = openBinaryTempFile (takeDirectory toFPath) ".copyFile.tmp"
cleanTmp (tmpFPath, hTmp) = do
hClose hTmp `catchIO` \_ -> return ()
removeFile tmpFPath `catchIO` \_ -> return ()
bufferSize = 4096
copyContents hFrom hTo buffer = do
count <- hGetBuf hFrom buffer bufferSize
when (count > 0) $ do
hPutBuf hTo buffer count
copyContents hFrom hTo buffer
#else
copy :: IO ()
copy = FilePath -> FilePath -> Bool -> IO ()
Win32.copyFile (FilePath -> FilePath
toExtendedLengthPath FilePath
fromFPath)
(FilePath -> FilePath
toExtendedLengthPath FilePath
toFPath)
Bool
False
toExtendedLengthPath :: FilePath -> FilePath
toExtendedLengthPath :: FilePath -> FilePath
toExtendedLengthPath FilePath
path
| FilePath -> Bool
isRelative FilePath
path = FilePath
path
| Bool
otherwise =
case FilePath
normalisedPath of
Char
'\\' : Char
'?' : Char
'?' : Char
'\\' : FilePath
_ -> FilePath
normalisedPath
Char
'\\' : Char
'\\' : Char
'?' : Char
'\\' : FilePath
_ -> FilePath
normalisedPath
Char
'\\' : Char
'\\' : Char
'.' : Char
'\\' : FilePath
_ -> FilePath
normalisedPath
Char
'\\' : subpath :: FilePath
subpath@(Char
'\\' : FilePath
_) -> FilePath
"\\\\?\\UNC" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
subpath
FilePath
_ -> FilePath
"\\\\?\\" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
normalisedPath
where normalisedPath :: FilePath
normalisedPath = FilePath -> FilePath
simplifyWindows FilePath
path
simplifyWindows :: FilePath -> FilePath
simplifyWindows :: FilePath -> FilePath
simplifyWindows FilePath
"" = FilePath
""
simplifyWindows FilePath
path =
case FilePath
drive' of
FilePath
"\\\\?\\" -> FilePath
drive' FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
subpath
FilePath
_ -> FilePath
simplifiedPath
where
simplifiedPath :: FilePath
simplifiedPath = FilePath -> FilePath -> FilePath
joinDrive FilePath
drive' FilePath
subpath'
(FilePath
drive, FilePath
subpath) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
path
drive' :: FilePath
drive' = FilePath -> FilePath
upperDrive (FilePath -> FilePath
normaliseTrailingSep (FilePath -> FilePath
normalisePathSeps FilePath
drive))
subpath' :: FilePath
subpath' = FilePath -> FilePath
appendSep (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
avoidEmpty (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
prependSep (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
joinPath ([FilePath] -> FilePath)
-> (FilePath -> [FilePath]) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[FilePath] -> [FilePath]
stripPardirs ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath]
expandDots ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath]
skipSeps ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
FilePath -> [FilePath]
splitDirectories (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
subpath
upperDrive :: FilePath -> FilePath
upperDrive FilePath
d = case FilePath
d of
Char
c : Char
':' : FilePath
s | Char -> Bool
isAlpha Char
c Bool -> Bool -> Bool
&& (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator FilePath
s -> Char -> Char
toUpper Char
c Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: Char
':' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
s
FilePath
_ -> FilePath
d
skipSeps :: [FilePath] -> [FilePath]
skipSeps = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Char -> FilePath
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Char -> FilePath) -> FilePath -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath
pathSeparators)))
stripPardirs :: [FilePath] -> [FilePath]
stripPardirs | Bool
pathIsAbsolute Bool -> Bool -> Bool
|| Bool
subpathIsAbsolute = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"..")
| Bool
otherwise = [FilePath] -> [FilePath]
forall a. a -> a
id
prependSep :: FilePath -> FilePath
prependSep | Bool
subpathIsAbsolute = (Char
pathSeparator Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:)
| Bool
otherwise = FilePath -> FilePath
forall a. a -> a
id
avoidEmpty :: FilePath -> FilePath
avoidEmpty | Bool -> Bool
not Bool
pathIsAbsolute
Bool -> Bool -> Bool
&& (FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
drive Bool -> Bool -> Bool
|| Bool
hasTrailingPathSep)
= FilePath -> FilePath
emptyToCurDir
| Bool
otherwise = FilePath -> FilePath
forall a. a -> a
id
appendSep :: FilePath -> FilePath
appendSep FilePath
p | Bool
hasTrailingPathSep
Bool -> Bool -> Bool
&& Bool -> Bool
not (Bool
pathIsAbsolute Bool -> Bool -> Bool
&& FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
p)
= FilePath -> FilePath
addTrailingPathSeparator FilePath
p
| Bool
otherwise = FilePath
p
pathIsAbsolute :: Bool
pathIsAbsolute = Bool -> Bool
not (FilePath -> Bool
isRelative FilePath
path)
subpathIsAbsolute :: Bool
subpathIsAbsolute = (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isPathSeparator (Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
take Int
1 FilePath
subpath)
hasTrailingPathSep :: Bool
hasTrailingPathSep = FilePath -> Bool
hasTrailingPathSeparator FilePath
subpath
expandDots :: [FilePath] -> [FilePath]
expandDots :: [FilePath] -> [FilePath]
expandDots = [FilePath] -> [FilePath]
forall a. [a] -> [a]
reverse ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath] -> [FilePath]
go []
where
go :: [FilePath] -> [FilePath] -> [FilePath]
go [FilePath]
ys' [FilePath]
xs' =
case [FilePath]
xs' of
[] -> [FilePath]
ys'
FilePath
x : [FilePath]
xs ->
case FilePath
x of
FilePath
"." -> [FilePath] -> [FilePath] -> [FilePath]
go [FilePath]
ys' [FilePath]
xs
FilePath
".." ->
case [FilePath]
ys' of
[] -> [FilePath] -> [FilePath] -> [FilePath]
go (FilePath
x FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
ys') [FilePath]
xs
FilePath
".." : [FilePath]
_ -> [FilePath] -> [FilePath] -> [FilePath]
go (FilePath
x FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
ys') [FilePath]
xs
FilePath
_ : [FilePath]
ys -> [FilePath] -> [FilePath] -> [FilePath]
go [FilePath]
ys [FilePath]
xs
FilePath
_ -> [FilePath] -> [FilePath] -> [FilePath]
go (FilePath
x FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
ys') [FilePath]
xs
normalisePathSeps :: FilePath -> FilePath
normalisePathSeps :: FilePath -> FilePath
normalisePathSeps FilePath
p = (\ Char
c -> if Char -> Bool
isPathSeparator Char
c then Char
pathSeparator else Char
c) (Char -> Char) -> FilePath -> FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath
p
normaliseTrailingSep :: FilePath -> FilePath
normaliseTrailingSep :: FilePath -> FilePath
normaliseTrailingSep FilePath
path = do
let path' :: FilePath
path' = FilePath -> FilePath
forall a. [a] -> [a]
reverse FilePath
path
let (FilePath
sep, FilePath
path'') = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isPathSeparator FilePath
path'
let addSep :: FilePath -> FilePath
addSep = if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
sep then FilePath -> FilePath
forall a. a -> a
id else (Char
pathSeparator Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:)
FilePath -> FilePath
forall a. [a] -> [a]
reverse (FilePath -> FilePath
addSep FilePath
path'')
emptyToCurDir :: FilePath -> FilePath
emptyToCurDir :: FilePath -> FilePath
emptyToCurDir FilePath
"" = FilePath
"."
emptyToCurDir FilePath
path = FilePath
path
#endif /* mingw32_HOST_OS */
copyFileChanged :: FilePath -> FilePath -> IO ()
copyFileChanged :: FilePath -> FilePath -> IO ()
copyFileChanged FilePath
src FilePath
dest = do
Bool
equal <- FilePath -> FilePath -> IO Bool
filesEqual FilePath
src FilePath
dest
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
equal (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
copyFile FilePath
src FilePath
dest
filesEqual :: FilePath -> FilePath -> IO Bool
filesEqual :: FilePath -> FilePath -> IO Bool
filesEqual FilePath
f1 FilePath
f2 = do
Bool
ex1 <- FilePath -> IO Bool
doesFileExist FilePath
f1
Bool
ex2 <- FilePath -> IO Bool
doesFileExist FilePath
f2
if Bool -> Bool
not (Bool
ex1 Bool -> Bool -> Bool
&& Bool
ex2)
then Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else FilePath -> IOMode -> (Handle -> IO Bool) -> IO Bool
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile FilePath
f1 IOMode
ReadMode ((Handle -> IO Bool) -> IO Bool) -> (Handle -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Handle
h1 ->
FilePath -> IOMode -> (Handle -> IO Bool) -> IO Bool
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile FilePath
f2 IOMode
ReadMode ((Handle -> IO Bool) -> IO Bool) -> (Handle -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Handle
h2 -> do
Integer
s1 <- Handle -> IO Integer
hFileSize Handle
h1
Integer
s2 <- Handle -> IO Integer
hFileSize Handle
h2
if Integer
s1 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
/= Integer
s2
then Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else do
ByteString
c1 <- Handle -> IO ByteString
BSL.hGetContents Handle
h1
ByteString
c2 <- Handle -> IO ByteString
BSL.hGetContents Handle
h2
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! ByteString
c1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
c2