{-# LANGUAGE ScopedTypeVariables #-}
module System.IO.Extra(
module System.IO,
captureOutput,
withBuffering,
readFileEncoding, readFileUTF8, readFileBinary,
readFile', readFileEncoding', readFileUTF8', readFileBinary',
writeFileEncoding, writeFileUTF8, writeFileBinary,
withTempFile, withTempDir, newTempFile, newTempDir,
newTempFileWithin, newTempDirWithin,
fileEq,
) where
import System.IO
import Control.Concurrent.Extra
import Control.Monad.Extra
import Control.Exception.Extra as E
import GHC.IO.Handle(hDuplicate,hDuplicateTo)
import System.Directory.Extra
import System.IO.Error
import System.IO.Unsafe
import System.FilePath
import Data.Char
import Data.Time.Clock
import Data.Tuple.Extra
import Data.IORef
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.C.Types
import Data.Functor
import Prelude
readFileEncoding :: TextEncoding -> FilePath -> IO String
readFileEncoding enc file = do
h <- openFile file ReadMode
hSetEncoding h enc
hGetContents h
readFileUTF8 :: FilePath -> IO String
readFileUTF8 = readFileEncoding utf8
readFileBinary :: FilePath -> IO String
readFileBinary file = do
h <- openBinaryFile file ReadMode
hGetContents h
hGetContents' :: Handle -> IO String
hGetContents' h = do
s <- hGetContents h
void $ evaluate $ length s
pure s
readFile' :: FilePath -> IO String
readFile' file = withFile file ReadMode hGetContents'
readFileEncoding' :: TextEncoding -> FilePath -> IO String
readFileEncoding' e file = withFile file ReadMode $ \h -> hSetEncoding h e >> hGetContents' h
readFileUTF8' :: FilePath -> IO String
readFileUTF8' = readFileEncoding' utf8
readFileBinary' :: FilePath -> IO String
readFileBinary' file = withBinaryFile file ReadMode hGetContents'
writeFileEncoding :: TextEncoding -> FilePath -> String -> IO ()
writeFileEncoding enc file x = withFile file WriteMode $ \h -> do
hSetEncoding h enc
hPutStr h x
writeFileUTF8 :: FilePath -> String -> IO ()
writeFileUTF8 = writeFileEncoding utf8
writeFileBinary :: FilePath -> String -> IO ()
writeFileBinary file x = withBinaryFile file WriteMode $ \h -> hPutStr h x
captureOutput :: IO a -> IO (String, a)
captureOutput act = withTempFile $ \file ->
withFile file ReadWriteMode $ \h -> do
res <- clone stdout h $ clone stderr h $ do
hClose h
act
out <- readFile' file
pure (out, res)
where
clone out h act = do
buf <- hGetBuffering out
out2 <- hDuplicate out
hDuplicateTo h out
act `finally` do
hDuplicateTo out2 out
hClose out2
hSetBuffering out buf
withBuffering :: Handle -> BufferMode -> IO a -> IO a
withBuffering h m act = bracket (hGetBuffering h) (hSetBuffering h) $ const $ do
hSetBuffering h m
act
{-# NOINLINE tempRef #-}
tempRef :: IORef Int
tempRef = unsafePerformIO $ do
rand :: Integer <- fmap (read . reverse . filter isDigit . show . utctDayTime) getCurrentTime
newIORef $ fromIntegral rand
tempUnique :: IO Int
tempUnique = atomicModifyIORef tempRef $ succ &&& succ
newTempFile :: IO (FilePath, IO ())
newTempFile = newTempFileWithin =<< getTemporaryDirectory
newTempFileWithin :: FilePath -> IO (FilePath, IO ())
newTempFileWithin tmpdir = do
file <- create
del <- once $ ignore $ removeFile file
pure (file, del)
where
create = do
val <- tempUnique
(file, h) <- retryBool (\(_ :: IOError) -> True) 5 $ openTempFile tmpdir $ "extra-file-" ++ show val ++ "-"
hClose h
pure file
withTempFile :: (FilePath -> IO a) -> IO a
withTempFile act = do
(file, del) <- newTempFile
act file `finally` del
newTempDir :: IO (FilePath, IO ())
newTempDir = newTempDirWithin =<< getTemporaryDirectory
newTempDirWithin :: FilePath -> IO (FilePath, IO ())
newTempDirWithin tmpdir = do
dir <- retryBool (\(_ :: IOError) -> True) 5 $ create tmpdir
del <- once $ ignore $ removeDirectoryRecursive dir
pure (dir, del)
where
create tmpdir = do
v <- tempUnique
let dir = tmpdir </> "extra-dir-" ++ show v
catchBool isAlreadyExistsError
(createDirectoryPrivate dir >> pure dir) $
\_ -> create tmpdir
withTempDir :: (FilePath -> IO a) -> IO a
withTempDir act = do
(dir,del) <- newTempDir
act dir `finally` del
sameSize :: Handle -> Handle -> IO Bool
sameSize h1 h2 = liftM2 (==) (hFileSize h1) (hFileSize h2)
foreign import ccall unsafe "string.h memcmp" memcmp
:: Ptr CUChar -> Ptr CUChar -> CSize -> IO CInt
sameContent :: Handle -> Handle -> IO Bool
sameContent h1 h2 = sameSize h1 h2 &&^ withb (\b1 -> withb $ \b2 -> eq b1 b2)
where eq b1 b2 = do
r1 <- hGetBuf h1 b1 bufsz
r2 <- hGetBuf h2 b2 bufsz
if r1 == 0
then pure $ r2 == 0
else pure (r1 == r2) &&^ bufeq b1 b2 r1 &&^ eq b1 b2
bufeq b1 b2 s = (==0) <$> memcmp b1 b2 (fromIntegral s)
withb = allocaBytesAligned bufsz 4096
bufsz = 64*1024
fileEq :: FilePath -> FilePath -> IO Bool
fileEq p1 p2 = withH p1 $ \h1 -> withH p2 $ \h2 -> sameContent h1 h2
where withH p = withBinaryFile p ReadMode