{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module UnliftIO.IO.File.Posix
( withBinaryFileDurable
, withBinaryFileDurableAtomic
, withBinaryFileAtomic
, ensureFileDurable
)
where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Control.Monad (forM_, guard, unless, void, when)
import Control.Monad.IO.Unlift
import Data.Bits (Bits, (.|.))
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe)
import Data.Typeable (cast)
import Foreign (allocaBytes)
import Foreign.C (CInt(..), throwErrnoIfMinus1, throwErrnoIfMinus1Retry,
throwErrnoIfMinus1Retry_)
import GHC.IO.Device (IODeviceType(RegularFile))
import qualified GHC.IO.Device as Device
import GHC.IO.Exception (IOErrorType(UnsupportedOperation))
import qualified GHC.IO.FD as FD
import qualified GHC.IO.Handle.FD as HandleFD
import qualified GHC.IO.Handle.Types as HandleFD (Handle(..), Handle__(..))
import System.Directory (removeFile)
import System.FilePath (takeDirectory, takeFileName)
import System.IO (Handle, IOMode(..), SeekMode(..), hGetBuf, hPutBuf,
openBinaryTempFile)
import System.IO.Error (ioeGetErrorType, isAlreadyExistsError,
isDoesNotExistError)
import qualified System.Posix.Files as Posix
import System.Posix.Internals (CFilePath, c_close, c_safe_open, withFilePath)
import System.Posix.Types (CMode(..), Fd(..), FileMode)
import UnliftIO.Exception
import UnliftIO.IO
import UnliftIO.MVar
newtype CFlag =
CFlag CInt
deriving (Eq, Show, Bits)
foreign import ccall unsafe "HsBase.h __hscore_o_rdonly" o_RDONLY :: CFlag
foreign import ccall unsafe "HsBase.h __hscore_o_wronly" o_WRONLY :: CFlag
foreign import ccall unsafe "HsBase.h __hscore_o_rdwr" o_RDWR :: CFlag
foreign import ccall unsafe "HsBase.h __hscore_o_append" o_APPEND :: CFlag
foreign import ccall unsafe "HsBase.h __hscore_o_creat" o_CREAT :: CFlag
foreign import ccall unsafe "HsBase.h __hscore_o_noctty" o_NOCTTY :: CFlag
foreign import ccall unsafe "file-posix.c unliftio_o_tmpfile" o_TMPFILE :: CFlag
o_TMPFILE_not_supported :: CFlag
o_TMPFILE_not_supported = CFlag 0
newtype CAt = CAt
{ unCAt :: CInt
} deriving (Eq, Show, Bits)
foreign import ccall unsafe "file-posix.c unliftio_at_fdcwd" at_FDCWD :: CAt
foreign import ccall unsafe "file-posix.c unliftio_at_symlink_follow" at_SYMLINK_FOLLOW :: CAt
foreign import ccall unsafe "file-posix.c unliftio_s_irusr" s_IRUSR :: CMode
foreign import ccall unsafe "file-posix.c unliftio_s_iwusr" s_IWUSR :: CMode
c_open :: CFilePath -> CFlag -> CMode -> IO CInt
c_open fp (CFlag flags) = c_safe_open fp flags
foreign import ccall safe "fcntl.h openat"
c_safe_openat :: CInt -> CFilePath -> CInt -> CMode -> IO CInt
c_openat :: DirFd -> CFilePath -> CFlag -> CMode -> IO CInt
c_openat (DirFd (Fd fd)) fp (CFlag flags) = c_safe_openat fd fp flags
foreign import ccall safe "fcntl.h renameat"
c_safe_renameat :: CInt -> CFilePath -> CInt -> CFilePath -> IO CInt
c_renameat :: DirFd -> CFilePath -> DirFd -> CFilePath -> IO CInt
c_renameat (DirFd (Fd fdFrom)) cFpFrom (DirFd (Fd fdTo)) cFpTo =
c_safe_renameat fdFrom cFpFrom fdTo cFpTo
foreign import ccall safe "unistd.h fsync"
c_safe_fsync :: CInt -> IO CInt
c_fsync :: Fd -> IO CInt
c_fsync (Fd fd) = c_safe_fsync fd
foreign import ccall safe "unistd.h linkat"
c_safe_linkat :: CInt -> CFilePath -> CInt -> CFilePath -> CInt -> IO CInt
c_linkat :: CAt -> CFilePath -> Either DirFd CAt -> CFilePath -> CAt -> IO CInt
c_linkat cat oldPath eNewDir newPath (CAt flags) =
c_safe_linkat (unCAt cat) oldPath newDir newPath flags
where
unFd (Fd fd) = fd
newDir = either (unFd . unDirFd) unCAt eNewDir
std_flags, output_flags, read_flags, write_flags, rw_flags,
append_flags :: CFlag
std_flags = o_NOCTTY
output_flags = std_flags .|. o_CREAT
read_flags = std_flags .|. o_RDONLY
write_flags = output_flags .|. o_WRONLY
rw_flags = output_flags .|. o_RDWR
append_flags = write_flags .|. o_APPEND
ioModeToFlags :: IOMode -> CFlag
ioModeToFlags iomode =
case iomode of
ReadMode -> read_flags
WriteMode -> write_flags
ReadWriteMode -> rw_flags
AppendMode -> append_flags
newtype DirFd = DirFd
{ unDirFd :: Fd
}
openDir :: MonadIO m => FilePath -> m Fd
openDir fp
=
liftIO $
withFilePath fp $ \cFp ->
Fd <$>
throwErrnoIfMinus1Retry
"openDir"
(c_open cFp (ioModeToFlags ReadMode) 0o660)
closeDirectory :: MonadIO m => DirFd -> m ()
closeDirectory (DirFd (Fd dirFd)) =
liftIO $
throwErrnoIfMinus1Retry_ "closeDirectory" $ c_close dirFd
fsyncFileDescriptor
:: MonadIO m
=> String
-> Fd
-> m ()
fsyncFileDescriptor name fd =
liftIO $ void $ throwErrnoIfMinus1 ("fsync - " ++ name) $ c_fsync fd
fsyncFileHandle :: String -> Handle -> IO ()
fsyncFileHandle fname hdl = withHandleFd hdl (fsyncFileDescriptor (fname ++ "/File"))
fsyncDirectoryFd :: String -> DirFd -> IO ()
fsyncDirectoryFd fname = fsyncFileDescriptor (fname ++ "/Directory") . unDirFd
openFileFromDir :: MonadIO m => DirFd -> FilePath -> IOMode -> m Handle
openFileFromDir dirFd filePath@(takeFileName -> fileName) iomode =
liftIO $
withFilePath fileName $ \cFileName ->
bracketOnError
(do fileFd <-
throwErrnoIfMinus1Retry "openFileFromDir" $
c_openat dirFd cFileName (ioModeToFlags iomode) 0o666
FD.mkFD
fileFd
iomode
Nothing
False
False
`onException`
c_close fileFd)
(liftIO . Device.close . fst)
(\(fD, fd_type)
-> do
when (iomode == WriteMode && fd_type == RegularFile) $
Device.setSize fD 0
HandleFD.mkHandleFromFD fD fd_type filePath iomode False Nothing)
openAnonymousTempFileFromDir ::
MonadIO m =>
Maybe DirFd
-> FilePath
-> IOMode
-> m Handle
openAnonymousTempFileFromDir mDirFd filePath iomode =
liftIO $
case mDirFd of
Just dirFd -> withFilePath "." (openAnonymousWith . c_openat dirFd)
Nothing ->
withFilePath (takeDirectory filePath) (openAnonymousWith . c_open)
where
fdName = "openAnonymousTempFileFromDir - " ++ filePath
ioModeToTmpFlags :: IOMode -> CFlag
ioModeToTmpFlags =
\case
ReadMode -> o_RDWR
ReadWriteMode -> o_RDWR
_ -> o_WRONLY
openAnonymousWith fopen =
bracketOnError
(do fileFd <-
throwErrnoIfMinus1Retry "openAnonymousTempFileFromDir" $
fopen (o_TMPFILE .|. ioModeToTmpFlags iomode) (s_IRUSR .|. s_IWUSR)
FD.mkFD
fileFd
iomode
Nothing
False
False
`onException`
c_close fileFd)
(liftIO . Device.close . fst)
(\(fD, fd_type) ->
HandleFD.mkHandleFromFD fD fd_type fdName iomode False Nothing)
atomicDurableTempFileRename ::
DirFd -> Maybe FileMode -> Handle -> Maybe FilePath -> FilePath -> IO ()
atomicDurableTempFileRename dirFd mFileMode tmpFileHandle mTmpFilePath filePath = do
fsyncFileHandle "atomicDurableTempFileCreate" tmpFileHandle
let eTmpFile = maybe (Left tmpFileHandle) Right mTmpFilePath
atomicTempFileRename (Just dirFd) mFileMode eTmpFile filePath
hClose tmpFileHandle
fsyncDirectoryFd "atomicDurableTempFileCreate" dirFd
atomicTempFileCreate ::
Maybe DirFd
-> Maybe FileMode
-> Handle
-> FilePath
-> IO ()
atomicTempFileCreate mDirFd mFileMode tmpFileHandle filePath =
withHandleFd tmpFileHandle $ \fd@(Fd cFd) ->
withFilePath ("/proc/self/fd/" ++ show cFd) $ \cFromFilePath ->
withFilePath filePathName $ \cToFilePath -> do
let fileMode = fromMaybe Posix.stdFileMode mFileMode
Posix.setFdMode fd fileMode
let safeLink which to =
throwErrnoIfMinus1Retry_
("atomicFileCreate - c_safe_linkat - " ++ which) $
c_linkat at_FDCWD cFromFilePath cDirFd to at_SYMLINK_FOLLOW
eExc <-
tryJust (guard . isAlreadyExistsError) $
safeLink "anonymous" cToFilePath
case eExc of
Right () -> pure ()
Left () ->
withBinaryTempFileFor filePath $ \visTmpFileName visTmpFileHandle -> do
hClose visTmpFileHandle
removeFile visTmpFileName
case mDirFd of
Nothing -> do
withFilePath visTmpFileName (safeLink "visible")
Posix.rename visTmpFileName filePath
Just dirFd ->
withFilePath (takeFileName visTmpFileName) $ \cVisTmpFile -> do
safeLink "visible" cVisTmpFile
throwErrnoIfMinus1Retry_
"atomicFileCreate - c_safe_renameat" $
c_renameat dirFd cVisTmpFile dirFd cToFilePath
where
(cDirFd, filePathName) =
case mDirFd of
Nothing -> (Right at_FDCWD, filePath)
Just dirFd -> (Left dirFd, takeFileName filePath)
atomicTempFileRename ::
Maybe DirFd
-> Maybe FileMode
-> Either Handle FilePath
-> FilePath
-> IO ()
atomicTempFileRename mDirFd mFileMode eTmpFile filePath =
case eTmpFile of
Left tmpFileHandle ->
atomicTempFileCreate mDirFd mFileMode tmpFileHandle filePath
Right tmpFilePath -> do
forM_ mFileMode $ \fileMode -> Posix.setFileMode tmpFilePath fileMode
case mDirFd of
Nothing -> Posix.rename tmpFilePath filePath
Just dirFd ->
withFilePath (takeFileName filePath) $ \cToFilePath ->
withFilePath (takeFileName tmpFilePath) $ \cTmpFilePath ->
throwErrnoIfMinus1Retry_ "atomicFileCreate - c_safe_renameat" $
c_renameat dirFd cTmpFilePath dirFd cToFilePath
withDirectory :: MonadUnliftIO m => FilePath -> (DirFd -> m a) -> m a
withDirectory dirPath = bracket (DirFd <$> openDir dirPath) closeDirectory
withFileInDirectory ::
MonadUnliftIO m => DirFd -> FilePath -> IOMode -> (Handle -> m a) -> m a
withFileInDirectory dirFd filePath iomode =
bracket (openFileFromDir dirFd filePath iomode) hClose
withBinaryTempFileFor ::
MonadUnliftIO m
=> FilePath
-> (FilePath -> Handle -> m a)
-> m a
withBinaryTempFileFor filePath action =
bracketOnError
(liftIO (openBinaryTempFile dirPath tmpFileName))
(\(tmpFilePath, tmpFileHandle) ->
hClose tmpFileHandle >> liftIO (tryIO (removeFile tmpFilePath)))
(uncurry action)
where
dirPath = takeDirectory filePath
fileName = takeFileName filePath
tmpFileName = "." ++ fileName ++ ".tmp"
withAnonymousBinaryTempFileFor ::
MonadUnliftIO m
=> Maybe DirFd
-> FilePath
-> IOMode
-> (Handle -> m a)
-> m (Maybe a)
withAnonymousBinaryTempFileFor mDirFd filePath iomode action
| o_TMPFILE == o_TMPFILE_not_supported = pure Nothing
| otherwise =
trySupported $
bracket (openAnonymousTempFileFromDir mDirFd filePath iomode) hClose action
where
trySupported m =
tryIO m >>= \case
Right res -> pure $ Just res
Left exc
| ioeGetErrorType exc == UnsupportedOperation -> pure Nothing
Left exc -> throwIO exc
withNonAnonymousBinaryTempFileFor ::
MonadUnliftIO m
=> Maybe DirFd
-> FilePath
-> IOMode
-> (FilePath -> Handle -> m a)
-> m a
withNonAnonymousBinaryTempFileFor mDirFd filePath iomode action =
withBinaryTempFileFor filePath $ \tmpFilePath tmpFileHandle -> do
hClose tmpFileHandle
case mDirFd of
Nothing -> withBinaryFile tmpFilePath iomode (action tmpFilePath)
Just dirFd -> withFileInDirectory dirFd tmpFilePath iomode (action tmpFilePath)
copyFileHandle ::
MonadUnliftIO f => IOMode -> FilePath -> Handle -> f (Maybe FileMode)
copyFileHandle iomode fromFilePath toHandle =
either (const Nothing) Just <$>
tryJust
(guard . isDoesNotExistError)
(do fileStatus <- liftIO $ Posix.getFileStatus fromFilePath
unless (iomode == WriteMode) $ do
withBinaryFile fromFilePath ReadMode (`copyHandleData` toHandle)
unless (iomode == AppendMode) $ hSeek toHandle AbsoluteSeek 0
pure $ Posix.fileMode fileStatus)
copyHandleData :: MonadIO m => Handle -> Handle -> m ()
copyHandleData hFrom hTo = liftIO $ allocaBytes bufferSize go
where
bufferSize = 131072
go buffer = do
count <- hGetBuf hFrom buffer bufferSize
when (count > 0) $ do
hPutBuf hTo buffer count
go buffer
withHandleFd :: Handle -> (Fd -> IO a) -> IO a
withHandleFd h cb =
case h of
HandleFD.FileHandle _ mv ->
withMVar mv $ \HandleFD.Handle__{HandleFD.haDevice = dev} ->
case cast dev of
Just fd -> cb $ Fd $ FD.fdFD fd
Nothing -> error "withHandleFd: not a file handle"
HandleFD.DuplexHandle {} -> error "withHandleFd: not a file handle"
ensureFileDurable :: MonadIO m => FilePath -> m ()
ensureFileDurable filePath =
liftIO $
withDirectory (takeDirectory filePath) $ \dirFd ->
withFileInDirectory dirFd filePath ReadMode $ \fileHandle ->
liftIO $ do
fsyncFileHandle "ensureFileDurablePosix" fileHandle
fsyncDirectoryFd "ensureFileDurablePosix" dirFd
withBinaryFileDurable ::
MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r
withBinaryFileDurable filePath iomode action =
case iomode of
ReadMode
-> withBinaryFile filePath iomode action
_
->
withDirectory (takeDirectory filePath) $ \dirFd ->
withFileInDirectory dirFd filePath iomode $ \tmpFileHandle -> do
res <- action tmpFileHandle
liftIO $ do
fsyncFileHandle "withBinaryFileDurablePosix" tmpFileHandle
fsyncDirectoryFd "withBinaryFileDurablePosix" dirFd
pure res
withBinaryFileDurableAtomic ::
MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r
withBinaryFileDurableAtomic filePath iomode action =
case iomode of
ReadMode
-> withBinaryFile filePath iomode action
_
->
withDirectory (takeDirectory filePath) $ \dirFd -> do
mRes <- withAnonymousBinaryTempFileFor (Just dirFd) filePath iomode $
durableAtomicAction dirFd Nothing
case mRes of
Just res -> pure res
Nothing ->
withNonAnonymousBinaryTempFileFor (Just dirFd) filePath iomode $ \tmpFilePath ->
durableAtomicAction dirFd (Just tmpFilePath)
where
durableAtomicAction dirFd mTmpFilePath tmpFileHandle = do
mFileMode <- copyFileHandle iomode filePath tmpFileHandle
res <- action tmpFileHandle
liftIO $
atomicDurableTempFileRename
dirFd
mFileMode
tmpFileHandle
mTmpFilePath
filePath
pure res
withBinaryFileAtomic ::
MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r
withBinaryFileAtomic filePath iomode action =
case iomode of
ReadMode
-> withBinaryFile filePath iomode action
_
-> do
mRes <-
withAnonymousBinaryTempFileFor Nothing filePath iomode $
atomicAction Nothing
case mRes of
Just res -> pure res
Nothing ->
withNonAnonymousBinaryTempFileFor Nothing filePath iomode $ \tmpFilePath ->
atomicAction (Just tmpFilePath)
where
atomicAction mTmpFilePath tmpFileHandle = do
let eTmpFile = maybe (Left tmpFileHandle) Right mTmpFilePath
mFileMode <- copyFileHandle iomode filePath tmpFileHandle
res <- action tmpFileHandle
liftIO $ atomicTempFileRename Nothing mFileMode eTmpFile filePath
pure res