{-# LANGUAGE ForeignFunctionInterface, CPP #-}
module ProjectM36.Persist (writeFileSync,
writeBSFileSync,
renameSync,
printFdCount,
DiskSync(..)) where
import qualified Data.Text as T
#if defined(linux_HOST_OS)
# define FDCOUNTSUPPORTED 1
# define FDDIR "/proc/self/fd"
#elif defined(darwin_HOST_OS)
# define FDCOUNTSUPPORTED 1
# define FDDIR "/dev/fd"
#else
# define FDCOUNTSUPPORTED 0
#endif
#if FDCOUNTSUPPORTED
import System.Directory
#endif
#if defined(mingw32_HOST_OS)
import qualified System.Win32 as Win32
#else
import qualified System.Posix as Posix
#if defined(linux_HOST_OS)
import System.Posix.Unistd (fileSynchroniseDataOnly)
#else
import System.Posix.Unistd (fileSynchronise)
#endif
import System.Posix.IO (handleToFd, closeFd)
import Foreign.C
#endif
import System.IO (withFile, IOMode(WriteMode), Handle)
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString as BS'
import qualified Data.Text.Encoding as TE
#if defined(mingw32_HOST_OS)
import ProjectM36.Win32Handle
#else
foreign import ccall unsafe "cDirectoryFsync" cHSDirectoryFsync :: CString -> IO CInt
#endif
data DiskSync = NoDiskSync | FsyncDiskSync
writeFileSync :: DiskSync -> FilePath -> T.Text -> IO()
writeFileSync sync path strOut = withFile path WriteMode handler
where
handler handle = do
BS'.hPut handle (TE.encodeUtf8 strOut)
syncHandle sync handle
renameSync :: DiskSync -> FilePath -> FilePath -> IO ()
renameSync sync srcPath dstPath = do
atomicRename srcPath dstPath
syncDirectory sync dstPath
{-# ANN atomicRename ("HLint: ignore Eta reduce" :: String) #-}
atomicRename :: FilePath -> FilePath -> IO ()
atomicRename srcPath dstPath =
#if defined(mingw32_HOST_OS)
Win32.moveFileEx srcPath dstPath Win32.mOVEFILE_REPLACE_EXISTING
#else
Posix.rename srcPath dstPath
#endif
syncHandle :: DiskSync -> Handle -> IO ()
syncHandle FsyncDiskSync handle =
#if defined(mingw32_HOST_OS)
withHandleToHANDLE handle (\h -> Win32.flushFileBuffers h)
#elif defined(linux_HOST_OS)
do
fd <- handleToFd handle
fileSynchroniseDataOnly fd
closeFd fd
#else
do
fd <- handleToFd handle
fileSynchronise fd
closeFd fd
#endif
syncHandle NoDiskSync _ = pure ()
syncDirectory :: DiskSync -> FilePath -> IO ()
syncDirectory FsyncDiskSync path = directoryFsync path
syncDirectory NoDiskSync _ = pure ()
writeBSFileSync :: DiskSync -> FilePath -> BS.ByteString -> IO ()
writeBSFileSync sync path bstring =
withFile path WriteMode $ \handle -> do
BS.hPut handle bstring
syncHandle sync handle
directoryFsync :: FilePath -> IO ()
#if defined(mingw32_HOST_OS)
directoryFsync _ = pure ()
#else
directoryFsync path = throwErrnoIfMinus1Retry_ "directoryFsync" (withCString path $ \cpath -> cHSDirectoryFsync cpath)
#endif
printFdCount :: IO ()
printFdCount =
#if FDCOUNTSUPPORTED
do
fdc <- fdCount
putStrLn ("Fd count: " ++ show fdc)
#else
putStrLn "Fd count not supported on this OS."
#endif
fdCount :: IO Int
#if FDCOUNTSUPPORTED
fdCount = do
fds <- getDirectoryContents FDDIR
pure ((length fds) - 2)
#else
fdCount = pure 0
#endif