{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
module System.Path.IO
(
withFile
, openTempFile'
, readLazyByteString
, readStrictByteString
, writeLazyByteString
, writeStrictByteString
, appendLazyByteString
, appendStrictByteString
, readLazyText
, readStrictText
, writeLazyText
, writeStrictText
, appendLazyText
, appendStrictText
, readLazyTextUtf8
, readStrictTextUtf8
, writeLazyTextUtf8
, writeStrictTextUtf8
, appendLazyTextUtf8
, appendStrictTextUtf8
, copyFile
, createDirectory
, createDirectoryIfMissing
, removeDirectory
, doesFileExist
, doesDirectoryExist
, getModificationTime
, removeFile
, getTemporaryDirectory
, getDirectoryContents
, getRecursiveContents
, renameFile
, getCurrentDirectory
, module System.Path
, IOMode(..)
, BufferMode(..)
, Handle
, SeekMode(..)
, IO.hSetBuffering
, IO.hClose
, IO.hFileSize
, IO.hSeek
) where
import System.Path
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Control.Exception (evaluate)
import Control.Monad
import Data.Time (UTCTime)
import System.IO (BufferMode (..), Handle, IOMode (..),
SeekMode (..))
import qualified System.IO as IO
import System.IO.Unsafe (unsafeInterleaveIO)
#if !MIN_VERSION_directory(1,2,0)
import Data.Time.Clock (picosecondsToDiffTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import System.Time (ClockTime (TOD))
#endif
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BS.L
import qualified Data.Text as T
import qualified Data.Text.Encoding as T.E
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as T.L
import qualified Data.Text.Lazy.Encoding as T.L.E
import qualified Data.Text.Lazy.IO as T.L
import qualified System.Directory as Dir
#if defined(__HADDOCK_VERSION__)
import Data.Text.Encoding.Error (UnicodeException)
#endif
withFile :: FsRoot root => Path root -> IOMode -> (Handle -> IO r) -> IO r
withFile path mode callback = do
filePath <- toAbsoluteFilePath path
IO.withFile filePath mode callback
openTempFile' :: FsRoot root => Path root -> String -> IO (Path Absolute, Handle)
openTempFile' path template = do
filePath <- toAbsoluteFilePath path
(tempFilePath, h) <- IO.openBinaryTempFileWithDefaultPermissions filePath template
return (fromAbsoluteFilePath tempFilePath, h)
readLazyByteString :: FsRoot root => Path root -> IO BS.L.ByteString
readLazyByteString path = do
filePath <- toAbsoluteFilePath path
BS.L.readFile filePath
readStrictByteString :: FsRoot root => Path root -> IO BS.ByteString
readStrictByteString path = do
filePath <- toAbsoluteFilePath path
BS.readFile filePath
writeLazyByteString :: FsRoot root => Path root -> BS.L.ByteString -> IO ()
writeLazyByteString path bs = do
filePath <- toAbsoluteFilePath path
BS.L.writeFile filePath bs
writeStrictByteString :: FsRoot root => Path root -> BS.ByteString -> IO ()
writeStrictByteString path bs = do
filePath <- toAbsoluteFilePath path
BS.writeFile filePath bs
appendLazyByteString :: FsRoot root => Path root -> BS.L.ByteString -> IO ()
appendLazyByteString path bs = do
filePath <- toAbsoluteFilePath path
BS.L.appendFile filePath bs
appendStrictByteString :: FsRoot root => Path root -> BS.ByteString -> IO ()
appendStrictByteString path bs = do
filePath <- toAbsoluteFilePath path
BS.appendFile filePath bs
readLazyText :: FsRoot root => Path root -> IO T.L.Text
readLazyText path = do
filePath <- toAbsoluteFilePath path
T.L.readFile filePath
readStrictText :: FsRoot root => Path root -> IO T.Text
readStrictText path = do
filePath <- toAbsoluteFilePath path
T.readFile filePath
writeLazyText :: FsRoot root => Path root -> T.L.Text -> IO ()
writeLazyText path bs = do
filePath <- toAbsoluteFilePath path
T.L.writeFile filePath bs
writeStrictText :: FsRoot root => Path root -> T.Text -> IO ()
writeStrictText path bs = do
filePath <- toAbsoluteFilePath path
T.writeFile filePath bs
appendLazyText :: FsRoot root => Path root -> T.L.Text -> IO ()
appendLazyText path bs = do
filePath <- toAbsoluteFilePath path
T.L.appendFile filePath bs
appendStrictText :: FsRoot root => Path root -> T.Text -> IO ()
appendStrictText path bs = do
filePath <- toAbsoluteFilePath path
T.appendFile filePath bs
readLazyTextUtf8 :: FsRoot root => Path root -> IO T.L.Text
readLazyTextUtf8 path = T.L.E.decodeUtf8 <$> readLazyByteString path
readStrictTextUtf8 :: FsRoot root => Path root -> IO T.Text
readStrictTextUtf8 path = do
bs <- readStrictByteString path
evaluate (T.E.decodeUtf8 bs)
writeLazyTextUtf8 :: FsRoot root => Path root -> T.L.Text -> IO ()
writeLazyTextUtf8 path bs = do
filePath <- toAbsoluteFilePath path
T.L.writeFile filePath bs
writeStrictTextUtf8 :: FsRoot root => Path root -> T.Text -> IO ()
writeStrictTextUtf8 path bs = do
filePath <- toAbsoluteFilePath path
T.writeFile filePath bs
appendLazyTextUtf8 :: FsRoot root => Path root -> T.L.Text -> IO ()
appendLazyTextUtf8 path bs = do
filePath <- toAbsoluteFilePath path
T.L.appendFile filePath bs
appendStrictTextUtf8 :: FsRoot root => Path root -> T.Text -> IO ()
appendStrictTextUtf8 path bs = do
filePath <- toAbsoluteFilePath path
T.appendFile filePath bs
copyFile :: (FsRoot root, FsRoot root') => Path root -> Path root' -> IO ()
copyFile src dst = do
src' <- toAbsoluteFilePath src
dst' <- toAbsoluteFilePath dst
Dir.copyFile src' dst'
createDirectory :: FsRoot root => Path root -> IO ()
createDirectory path = Dir.createDirectory =<< toAbsoluteFilePath path
createDirectoryIfMissing :: FsRoot root => Bool -> Path root -> IO ()
createDirectoryIfMissing createParents path = do
filePath <- toAbsoluteFilePath path
Dir.createDirectoryIfMissing createParents filePath
removeDirectory :: FsRoot root => Path root -> IO ()
removeDirectory path = Dir.removeDirectory =<< toAbsoluteFilePath path
doesFileExist :: FsRoot root => Path root -> IO Bool
doesFileExist path = do
filePath <- toAbsoluteFilePath path
Dir.doesFileExist filePath
doesDirectoryExist :: FsRoot root => Path root -> IO Bool
doesDirectoryExist path = do
filePath <- toAbsoluteFilePath path
Dir.doesDirectoryExist filePath
getModificationTime :: FsRoot root => Path root -> IO UTCTime
getModificationTime path = do
filePath <- toAbsoluteFilePath path
toUTC <$> Dir.getModificationTime filePath
where
#if MIN_VERSION_directory(1,2,0)
toUTC :: UTCTime -> UTCTime
toUTC = id
#else
toUTC :: ClockTime -> UTCTime
toUTC (TOD secs psecs) = posixSecondsToUTCTime $ realToFrac $ picosecondsToDiffTime (psecs + secs*1000000000000)
#endif
removeFile :: FsRoot root => Path root -> IO ()
removeFile path = do
filePath <- toAbsoluteFilePath path
Dir.removeFile filePath
getTemporaryDirectory :: IO (Path Absolute)
getTemporaryDirectory = fromAbsoluteFilePath <$> Dir.getTemporaryDirectory
getDirectoryContents :: FsRoot root => Path root -> IO [Path Unrooted]
getDirectoryContents path = do
filePath <- toAbsoluteFilePath path
fragments' <$> Dir.getDirectoryContents filePath
where
fragments' :: [String] -> [Path Unrooted]
fragments' = map fragment . filter (not . skip)
skip :: String -> Bool
skip "." = True
skip ".." = True
skip _ = False
getRecursiveContents :: FsRoot root => Path root -> IO [Path Unrooted]
getRecursiveContents root = go emptyPath
where
go :: Path Unrooted -> IO [Path Unrooted]
go subdir = unsafeInterleaveIO $ do
entries <- getDirectoryContents (root </> subdir)
liftM concat $ forM entries $ \entry -> do
let path = subdir </> entry
isDirectory <- doesDirectoryExist (root </> path)
if isDirectory then go path
else return [path]
emptyPath :: Path Unrooted
emptyPath = joinFragments []
renameFile :: (FsRoot root, FsRoot root')
=> Path root
-> Path root'
-> IO ()
renameFile old new = do
old' <- toAbsoluteFilePath old
new' <- toAbsoluteFilePath new
Dir.renameFile old' new'
getCurrentDirectory :: IO (Path Absolute)
getCurrentDirectory = do
cwd <- Dir.getCurrentDirectory
makeAbsolute $ fromFilePath cwd