{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}

-- |
-- Module: Filesystem
-- Copyright: 2011-2012 John Millikin <jmillikin@gmail.com>
-- License: MIT
--
-- Maintainer: John Millikin <jmillikin@gmail.com>
-- Portability: portable
--
-- Simple 'FilePath'&#8208;aware wrappers around standard "System.IO"
-- computations. These wrappers are designed to work as similarly as
-- possible across various versions of GHC.
--
-- In particular, they do not require POSIX file paths to be valid strings,
-- and can therefore open paths regardless of the current locale encoding.
module Filesystem
	(
	-- * Exports from System.IO
	  IO.Handle
	, IO.IOMode(..)
	
	-- * Files
	, isFile
	, getModified
	, getSize
	, copyFile
	, copyFileContent
	, copyPermissions
	, removeFile
	
	-- ** Binary files
	, openFile
	, withFile
	, readFile
	, writeFile
	, appendFile
	
	-- ** Text files
	, openTextFile
	, withTextFile
	, readTextFile
	, writeTextFile
	, appendTextFile
	
	-- * Directories
	, isDirectory
	, canonicalizePath
	, listDirectory
	
	-- ** Creating directories
	, createDirectory
	, createTree
	
	-- ** Removing directories
	, removeDirectory
	, removeTree
	
	-- ** Current working directory
	, getWorkingDirectory
	, setWorkingDirectory
	
	-- ** Commonly used paths
	, getHomeDirectory
	, getDesktopDirectory
	, getDocumentsDirectory
	, getAppDataDirectory
	, getAppCacheDirectory
	, getAppConfigDirectory
	
	-- * Other
	, rename
	) where

import           Prelude hiding (FilePath, readFile, writeFile, appendFile)

import qualified Control.Exception as Exc
import           Control.Monad (forM_, unless, when)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.IO as T
import           Foreign.Ptr (Ptr, nullPtr)
import           Foreign.C (CInt(..), CString, withCAString)
import qualified Foreign.C.Error as CError
import qualified System.Environment as SE

import           Filesystem.Path (FilePath, append)
import qualified Filesystem.Path as Path
import           Filesystem.Path.CurrentOS (currentOS, encodeString, decodeString)
import qualified Filesystem.Path.Rules as R

import qualified System.IO as IO
import           System.IO.Error (IOError)

#ifdef CABAL_OS_WINDOWS

import           Data.Bits ((.|.))
import           Data.Time ( UTCTime(..)
                           , fromGregorian
                           , secondsToDiffTime
                           , picosecondsToDiffTime)
import           Foreign.C (CWString, withCWString)
import qualified System.Win32 as Win32
import           System.IO.Error (isDoesNotExistError)
import qualified System.Directory as SD

#else

import           Data.Time (UTCTime)
import           Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import qualified System.Posix as Posix
import qualified System.Posix.Error as Posix
#if MIN_VERSION_unix(2,5,1)
import qualified System.Posix.Files.ByteString
#endif

#endif

#ifdef SYSTEMFILEIO_LOCAL_OPEN_FILE
import           Data.Bits ((.|.))
import           GHC.IO.Handle.FD (mkHandleFromFD)
import           GHC.IO.FD (mkFD)
import qualified GHC.IO.Device
import qualified System.Posix.Internals
#endif

-- | Check if a file exists at the given path.
--
-- Any non&#8208;directory object, including devices and pipes, are
-- considered to be files. Symbolic links are resolved to their targets
-- before checking their type.
--
-- This computation does not throw exceptions.
isFile :: FilePath -> IO Bool
#ifdef CABAL_OS_WINDOWS
isFile path = SD.doesFileExist (encodeString path)
#else
isFile :: FilePath -> IO Bool
isFile FilePath
path = IO Bool -> (IOError -> IO Bool) -> IO Bool
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Exc.catch
	(do
		FileStatus
stat <- String -> FilePath -> IO FileStatus
posixStat String
"isFile" FilePath
path
		Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Bool
not (FileStatus -> Bool
Posix.isDirectory FileStatus
stat)))
	((\IOError
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) :: IOError -> IO Bool)
#endif

-- | Check if a directory exists at the given path.
--
-- Symbolic links are resolved to their targets before checking their type.
--
-- This computation does not throw exceptions.
isDirectory :: FilePath -> IO Bool
#ifdef CABAL_OS_WINDOWS
isDirectory path = SD.doesDirectoryExist (encodeString path)
#else
isDirectory :: FilePath -> IO Bool
isDirectory FilePath
path = IO Bool -> (IOError -> IO Bool) -> IO Bool
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Exc.catch
	(do
		FileStatus
stat <- String -> FilePath -> IO FileStatus
posixStat String
"isDirectory" FilePath
path
		Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileStatus -> Bool
Posix.isDirectory FileStatus
stat))
	((\IOError
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) :: IOError -> IO Bool)
#endif

-- | Rename a filesystem object.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
rename :: FilePath -> FilePath -> IO ()
rename :: FilePath -> FilePath -> IO ()
rename FilePath
old FilePath
new =
#ifdef CABAL_OS_WINDOWS
	let old' = encodeString old in
	let new' = encodeString new in
#if MIN_VERSION_Win32(2,6,0)
	Win32.moveFileEx old' (Just new') Win32.mOVEFILE_REPLACE_EXISTING
#else
	Win32.moveFileEx old' new' Win32.mOVEFILE_REPLACE_EXISTING
#endif
#else
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
old ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
old' ->
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
new ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
new' ->
	String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1_ String
"rename" FilePath
old (CString -> CString -> IO CInt
c_rename CString
old' CString
new')

foreign import ccall unsafe "rename"
	c_rename :: CString -> CString -> IO CInt

#endif

-- | Resolve symlinks and \"..\" path elements to return a canonical path.
-- It is intended that two paths referring to the same object will always
-- resolve to the same canonical path.
--
-- Note that on many operating systems, it is impossible to guarantee that
-- two paths to the same file will resolve to the same canonical path.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
--
-- Since: 0.1.1
canonicalizePath :: FilePath -> IO FilePath
canonicalizePath :: FilePath -> IO FilePath
canonicalizePath FilePath
path =
	(FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath -> FilePath
preserveFinalSlash FilePath
path) (IO FilePath -> IO FilePath) -> IO FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$
	let path' :: String
path' = FilePath -> String
encodeString FilePath
path in
#ifdef CABAL_OS_WINDOWS
	fmap decodeString $
#if MIN_VERSION_Win32(2,2,1)
	Win32.getFullPathName path'
#else
	Win32.withTString path' $ \c_name -> do
		Win32.try "getFullPathName" (\buf len ->
			c_GetFullPathNameW c_name len buf nullPtr) 512
#endif
#else
	FilePath -> (CString -> IO FilePath) -> IO FilePath
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO FilePath) -> IO FilePath)
-> (CString -> IO FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ \CString
cPath -> do
		CString
cOut <- String -> String -> IO CString -> IO CString
forall a. String -> String -> IO (Ptr a) -> IO (Ptr a)
Posix.throwErrnoPathIfNull String
"canonicalizePath" String
path' (CString -> CString -> IO CString
c_realpath CString
cPath CString
forall a. Ptr a
nullPtr)
		ByteString
bytes <- CString -> IO ByteString
B.packCString CString
cOut
		CString -> IO ()
forall a. Ptr a -> IO ()
c_free CString
cOut
		FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rules ByteString -> ByteString -> FilePath
forall platformFormat.
Rules platformFormat -> platformFormat -> FilePath
R.decode Rules ByteString
R.posix ByteString
bytes)
#endif

preserveFinalSlash :: FilePath -> FilePath -> FilePath
preserveFinalSlash :: FilePath -> FilePath -> FilePath
preserveFinalSlash FilePath
orig FilePath
out = if FilePath -> Bool
Path.null (FilePath -> FilePath
Path.filename FilePath
orig)
	then FilePath -> FilePath -> FilePath
Path.append FilePath
out FilePath
Path.empty
	else FilePath
out

#ifdef CABAL_OS_WINDOWS
#if MIN_VERSION_Win32(2,2,1)
#else
foreign import stdcall unsafe "GetFullPathNameW"
	c_GetFullPathNameW :: Win32.LPCTSTR -> Win32.DWORD -> Win32.LPTSTR -> Ptr Win32.LPTSTR -> IO Win32.DWORD
#endif
#endif

#ifndef CABAL_OS_WINDOWS
foreign import ccall unsafe "realpath"
	c_realpath :: CString -> CString -> IO CString
#endif

-- | Create a directory at a given path. The user may choose whether it is
-- an error for a directory to already exist at that path.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
createDirectory :: Bool -- ^ Succeed if the directory already exists
                -> FilePath -> IO ()
createDirectory :: Bool -> FilePath -> IO ()
createDirectory Bool
succeedIfExists FilePath
path =
#ifdef CABAL_OS_WINDOWS
	let path' = encodeString path in
	if succeedIfExists
		then SD.createDirectoryIfMissing False path'
		else Win32.createDirectory path' Nothing
#else
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPath ->
	String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1Retry_ String
"createDirectory" FilePath
path (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ if Bool
succeedIfExists
		then FilePath -> CString -> CInt -> IO CInt
mkdirIfMissing FilePath
path CString
cPath CInt
0o777
		else CString -> CInt -> IO CInt
c_mkdir CString
cPath CInt
0o777

mkdirIfMissing :: FilePath -> CString -> CInt -> IO CInt
mkdirIfMissing :: FilePath -> CString -> CInt -> IO CInt
mkdirIfMissing FilePath
path CString
cPath CInt
mode = do
	CInt
rc <- CString -> CInt -> IO CInt
c_mkdir CString
cPath CInt
mode
	if CInt
rc CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1
		then do
			Errno
errno <- IO Errno
CError.getErrno
			if Errno
errno Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
CError.eEXIST
				then do
					Bool
dirExists <- FilePath -> IO Bool
isDirectory FilePath
path
					if Bool
dirExists
						then CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
0
						else CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
rc
				else CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
rc
		else CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
rc

foreign import ccall unsafe "mkdir"
	c_mkdir :: CString -> CInt -> IO CInt
#endif

-- | Create a directory at a given path, including any parents which might
-- be missing.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
createTree :: FilePath -> IO ()
#ifdef CABAL_OS_WINDOWS
createTree path = SD.createDirectoryIfMissing True (encodeString path)
#else
createTree :: FilePath -> IO ()
createTree FilePath
path = do
	let parent :: FilePath
parent = FilePath -> FilePath
Path.parent FilePath
path
	Bool
parentExists <- FilePath -> IO Bool
isDirectory FilePath
parent
	Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
parentExists (FilePath -> IO ()
createTree FilePath
parent)
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPath ->
		String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1Retry_ String
"createTree" FilePath
path (FilePath -> CString -> CInt -> IO CInt
mkdirIfMissing FilePath
path CString
cPath CInt
0o777)
#endif

-- | List objects in a directory, excluding @\".\"@ and @\"..\"@. Each
-- returned 'FilePath' includes the path of the directory. Entries are not
-- sorted.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
listDirectory :: FilePath -> IO [FilePath]
#ifdef CABAL_OS_WINDOWS
listDirectory root = fmap cleanup contents where
	contents = SD.getDirectoryContents (encodeString root)
	cleanup = map (append root) . map decodeString . filter (`notElem` [".", ".."])
#else
listDirectory :: FilePath -> IO [FilePath]
listDirectory FilePath
root = IO (Ptr (), Dir)
-> ((Ptr (), Dir) -> IO ())
-> ((Ptr (), Dir) -> IO [FilePath])
-> IO [FilePath]
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exc.bracket IO (Ptr (), Dir)
alloc (Ptr (), Dir) -> IO ()
free (Ptr (), Dir) -> IO [FilePath]
list where
	alloc :: IO (Ptr (), Dir)
alloc = do
		Dir
dir <- FilePath -> IO Dir
openDir FilePath
root
		let Dir FilePath
_ Ptr ()
dirp = Dir
dir
		Ptr ()
dirent <- Ptr () -> IO (Ptr ())
c_alloc_dirent Ptr ()
dirp
		(Ptr (), Dir) -> IO (Ptr (), Dir)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr ()
dirent, Dir
dir)
	free :: (Ptr (), Dir) -> IO ()
free (Ptr ()
dirent, Dir
dir) = do
		Ptr () -> IO ()
c_free_dirent Ptr ()
dirent
		Dir -> IO ()
closeDir Dir
dir
	list :: (Ptr (), Dir) -> IO [FilePath]
list (Ptr ()
dirent, Dir
dir) = IO [FilePath]
loop where
		loop :: IO [FilePath]
loop = do
			Maybe ByteString
next <- Dir -> Ptr () -> IO (Maybe ByteString)
readDir Dir
dir Ptr ()
dirent
			case Maybe ByteString
next of
				Maybe ByteString
Nothing -> [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
				Just ByteString
bytes | ByteString -> Bool
ignore ByteString
bytes -> IO [FilePath]
loop
				Just ByteString
bytes -> do
					let name :: FilePath
name = FilePath -> FilePath -> FilePath
append FilePath
root (Rules ByteString -> ByteString -> FilePath
forall platformFormat.
Rules platformFormat -> platformFormat -> FilePath
R.decode Rules ByteString
R.posix ByteString
bytes)
					[FilePath]
names <- IO [FilePath]
loop
					[FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
nameFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
names)

ignore :: B.ByteString -> Bool
ignore :: ByteString -> Bool
ignore = ByteString -> Bool
ignore' where
	dot :: ByteString
dot = [Word8] -> ByteString
B.pack [Word8
46]
	dotdot :: ByteString
dotdot = [Word8] -> ByteString
B.pack [Word8
46, Word8
46]
	ignore' :: ByteString -> Bool
ignore' ByteString
b = ByteString
b ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
dot Bool -> Bool -> Bool
|| ByteString
b ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
dotdot

data Dir = Dir FilePath (Ptr ())

openDir :: FilePath -> IO Dir
openDir :: FilePath -> IO Dir
openDir FilePath
root = FilePath -> (CString -> IO Dir) -> IO Dir
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
root ((CString -> IO Dir) -> IO Dir) -> (CString -> IO Dir) -> IO Dir
forall a b. (a -> b) -> a -> b
$ \CString
cRoot -> do
	Ptr ()
p <- String -> FilePath -> IO (Ptr ()) -> IO (Ptr ())
forall a. String -> FilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry String
"listDirectory" FilePath
root (CString -> IO (Ptr ())
c_opendir CString
cRoot)
	Dir -> IO Dir
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Ptr () -> Dir
Dir FilePath
root Ptr ()
p)

closeDir :: Dir -> IO ()
closeDir :: Dir -> IO ()
closeDir (Dir FilePath
_ Ptr ()
p) = String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
CError.throwErrnoIfMinus1Retry_ String
"listDirectory" (Ptr () -> IO CInt
c_closedir Ptr ()
p)

readDir :: Dir -> Ptr () -> IO (Maybe B.ByteString)
readDir :: Dir -> Ptr () -> IO (Maybe ByteString)
readDir (Dir FilePath
_ Ptr ()
p) Ptr ()
dirent = do
	CInt
rc <- String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
CError.throwErrnoIfMinus1Retry String
"listDirectory" (Ptr () -> Ptr () -> IO CInt
c_readdir Ptr ()
p Ptr ()
dirent)
	if CInt
rc CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
		then do
			ByteString
bytes <- Ptr () -> IO CString
c_dirent_name Ptr ()
dirent IO CString -> (CString -> IO ByteString) -> IO ByteString
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO ByteString
B.packCString
			Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bytes)
		else Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing

foreign import ccall unsafe "opendir"
	c_opendir :: CString -> IO (Ptr ())

foreign import ccall unsafe "closedir"
	c_closedir :: Ptr () -> IO CInt

foreign import ccall unsafe "hssystemfileio_alloc_dirent"
	c_alloc_dirent :: Ptr () -> IO (Ptr ())

foreign import ccall unsafe "hssystemfileio_free_dirent"
	c_free_dirent :: Ptr () -> IO ()

foreign import ccall unsafe "hssystemfileio_readdir"
	c_readdir :: Ptr () -> Ptr () -> IO CInt

foreign import ccall unsafe "hssystemfileio_dirent_name"
	c_dirent_name :: Ptr () -> IO CString

#endif

-- | Remove a file. This will fail if the file does not exist.
--
-- This computation cannot remove directories. For that, use 'removeDirectory'
-- or 'removeTree'.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
removeFile :: FilePath -> IO ()
removeFile :: FilePath -> IO ()
removeFile FilePath
path =
#ifdef CABAL_OS_WINDOWS
	Win32.deleteFile (encodeString path)
#else
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPath ->
	String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1_ String
"removeFile" FilePath
path (CString -> IO CInt
c_unlink CString
cPath)

foreign import ccall unsafe "unlink"
	c_unlink :: CString -> IO CInt
#endif

-- | Remove an empty directory.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
removeDirectory :: FilePath -> IO ()
removeDirectory :: FilePath -> IO ()
removeDirectory FilePath
path =
#ifdef CABAL_OS_WINDOWS
	Win32.removeDirectory (encodeString path)
#else
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPath ->
	String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1Retry_ String
"removeDirectory" FilePath
path (CString -> IO CInt
c_rmdir CString
cPath)

foreign import ccall unsafe "rmdir"
	c_rmdir :: CString -> IO CInt
#endif

-- | Recursively remove a directory tree rooted at the given path.
--
-- This computation does not follow symlinks. If the tree contains symlinks,
-- the links themselves will be removed, but not the objects they point to.
--
-- If the root path is a symlink, then it will be treated as if it were a
-- regular directory.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
removeTree :: FilePath -> IO ()
#ifdef CABAL_OS_WINDOWS
removeTree root = SD.removeDirectoryRecursive (encodeString root)
#else
removeTree :: FilePath -> IO ()
removeTree FilePath
root = do
	[FilePath]
items <- FilePath -> IO [FilePath]
listDirectory FilePath
root
	[FilePath] -> (FilePath -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [FilePath]
items ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
item -> IO () -> (IOError -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Exc.catch
		(FilePath -> IO ()
removeFile FilePath
item)
		(\IOError
exc -> do
			Bool
isDir <- FilePath -> IO Bool
isRealDir FilePath
item
			if Bool
isDir
				then FilePath -> IO ()
removeTree FilePath
item
				else IOError -> IO ()
forall e a. Exception e => e -> IO a
Exc.throwIO (IOError
exc :: IOError))
	FilePath -> IO ()
removeDirectory FilePath
root

-- Check whether a path is a directory, and not just a symlink to a directory.
--
-- This is used in 'removeTree' to prevent recursing into symlinks if the link
-- itself cannot be deleted.
isRealDir :: FilePath -> IO Bool
isRealDir :: FilePath -> IO Bool
isRealDir FilePath
path = FilePath -> (CString -> IO Bool) -> IO Bool
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
cPath -> do
	CInt
rc <- String -> FilePath -> IO CInt -> IO CInt
throwErrnoPathIfMinus1Retry String
"removeTree" FilePath
path (CString -> IO CInt
c_isrealdir CString
cPath)
	Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt
rc CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
1)

foreign import ccall unsafe "hssystemfileio_isrealdir"
	c_isrealdir :: CString -> IO CInt

#endif

-- | Get the current working directory.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getWorkingDirectory :: IO FilePath
getWorkingDirectory :: IO FilePath
getWorkingDirectory = do
#ifdef CABAL_OS_WINDOWS
#if MIN_VERSION_Win32(2,2,1)
	fmap decodeString Win32.getCurrentDirectory
#else
	fmap decodeString (Win32.try "getWorkingDirectory" (flip c_GetCurrentDirectoryW) 512)
#endif
#else
	CString
buf <- String -> IO CString -> IO CString
forall a. String -> IO (Ptr a) -> IO (Ptr a)
CError.throwErrnoIfNull String
"getWorkingDirectory" IO CString
c_getcwd
	ByteString
bytes <- CString -> IO ByteString
B.packCString CString
buf
	CString -> IO ()
forall a. Ptr a -> IO ()
c_free CString
buf
	FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rules ByteString -> ByteString -> FilePath
forall platformFormat.
Rules platformFormat -> platformFormat -> FilePath
R.decode Rules ByteString
R.posix ByteString
bytes)

foreign import ccall unsafe "hssystemfileio_getcwd"
	c_getcwd :: IO CString

#endif

#ifdef CABAL_OS_WINDOWS
#if MIN_VERSION_Win32(2,2,1)
#else
foreign import stdcall unsafe "GetCurrentDirectoryW"
	c_GetCurrentDirectoryW :: Win32.DWORD -> Win32.LPTSTR -> IO Win32.UINT
#endif
#endif

-- | Set the current working directory.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
setWorkingDirectory :: FilePath -> IO ()
setWorkingDirectory :: FilePath -> IO ()
setWorkingDirectory FilePath
path =
#ifdef CABAL_OS_WINDOWS
	Win32.setCurrentDirectory (encodeString path)
#else
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPath ->
	String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1Retry_ String
"setWorkingDirectory" FilePath
path (CString -> IO CInt
c_chdir CString
cPath)

foreign import ccall unsafe "chdir"
	c_chdir :: CString -> IO CInt

#endif

-- TODO: expose all known exceptions as specific types, for users to catch
-- if need be

-- | Get the user&#x2019;s home directory. This is useful for building paths
-- to more specific directories.
--
-- For directing the user to open or safe a document, use
-- 'getDocumentsDirectory'.
--
-- For data files the user does not explicitly create, such as automatic
-- saves, use 'getAppDataDirectory'.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getHomeDirectory :: IO FilePath
#ifdef CABAL_OS_WINDOWS
getHomeDirectory = fmap decodeString SD.getHomeDirectory
#else
getHomeDirectory :: IO FilePath
getHomeDirectory = do
	Maybe FilePath
path <- String -> IO (Maybe FilePath)
getenv String
"HOME"
	case Maybe FilePath
path of
		Just FilePath
p -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
p
		Maybe FilePath
Nothing -> do
			-- use getEnv to throw the right exception type
			(String -> FilePath) -> IO String -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> FilePath
decodeString (String -> IO String
SE.getEnv String
"HOME")
#endif

-- | Get the user&#x2019;s desktop directory. This is a good starting point for
-- file dialogs and other user queries. For data files the user does not
-- explicitly create, such as automatic saves, use 'getAppDataDirectory'.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getDesktopDirectory :: IO FilePath
getDesktopDirectory :: IO FilePath
getDesktopDirectory = String -> Maybe Text -> IO FilePath -> IO FilePath
xdg String
"XDG_DESKTOP_DIR" Maybe Text
forall a. Maybe a
Nothing
	(String -> IO FilePath
homeSlash String
"Desktop")

-- | Get the user&#x2019;s documents directory. This is a good place to save
-- user&#8208;created files. For data files the user does not explicitly
-- create, such as automatic saves, use 'getAppDataDirectory'.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getDocumentsDirectory :: IO FilePath
getDocumentsDirectory :: IO FilePath
getDocumentsDirectory = String -> Maybe Text -> IO FilePath -> IO FilePath
xdg String
"XDG_DOCUMENTS_DIR" Maybe Text
forall a. Maybe a
Nothing
#ifdef CABAL_OS_WINDOWS
	(fmap decodeString SD.getUserDocumentsDirectory)
#else
	(String -> IO FilePath
homeSlash String
"Documents")
#endif

-- | Get the user&#x2019;s application data directory, given an application
-- label. This directory is where applications should store data the user did
-- not explicitly create, such as databases and automatic saves.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getAppDataDirectory :: T.Text -> IO FilePath
getAppDataDirectory :: Text -> IO FilePath
getAppDataDirectory Text
label = String -> Maybe Text -> IO FilePath -> IO FilePath
xdg String
"XDG_DATA_HOME" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
label)
#ifdef CABAL_OS_WINDOWS
	(fmap decodeString (SD.getAppUserDataDirectory ""))
#else
	(String -> IO FilePath
homeSlash String
".local/share")
#endif

-- | Get the user&#x2019;s application cache directory, given an application
-- label. This directory is where applications should store caches, which
-- might be large and can be safely deleted.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getAppCacheDirectory :: T.Text -> IO FilePath
getAppCacheDirectory :: Text -> IO FilePath
getAppCacheDirectory Text
label = String -> Maybe Text -> IO FilePath -> IO FilePath
xdg String
"XDG_CACHE_HOME" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
label)
#ifdef CABAL_OS_WINDOWS
	(homeSlash "Local Settings\\Cache")
#else
	(String -> IO FilePath
homeSlash String
".cache")
#endif

-- | Get the user&#x2019;s application configuration directory, given an
-- application label. This directory is where applications should store their
-- configurations and settings.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
getAppConfigDirectory :: T.Text -> IO FilePath
getAppConfigDirectory :: Text -> IO FilePath
getAppConfigDirectory Text
label = String -> Maybe Text -> IO FilePath -> IO FilePath
xdg String
"XDG_CONFIG_HOME" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
label)
#ifdef CABAL_OS_WINDOWS
	(homeSlash "Local Settings")
#else
	(String -> IO FilePath
homeSlash String
".config")
#endif

homeSlash :: String -> IO FilePath
homeSlash :: String -> IO FilePath
homeSlash String
path = do
	FilePath
home <- IO FilePath
getHomeDirectory
	FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> FilePath -> FilePath
append FilePath
home (String -> FilePath
decodeString String
path))

getenv :: String -> IO (Maybe FilePath)
#ifdef CABAL_OS_WINDOWS
getenv key = Exc.catch
	(fmap (Just . decodeString) (SE.getEnv key))
	(\e -> if isDoesNotExistError e
		then return Nothing
		else Exc.throwIO e)
#else
getenv :: String -> IO (Maybe FilePath)
getenv String
key = String -> (CString -> IO (Maybe FilePath)) -> IO (Maybe FilePath)
forall a. String -> (CString -> IO a) -> IO a
withCAString String
key ((CString -> IO (Maybe FilePath)) -> IO (Maybe FilePath))
-> (CString -> IO (Maybe FilePath)) -> IO (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ \CString
cKey -> do
	CString
ret <- CString -> IO CString
c_getenv CString
cKey
	if CString
ret CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
		then Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
		else do
			ByteString
bytes <- CString -> IO ByteString
B.packCString CString
ret
			Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (Rules ByteString -> ByteString -> FilePath
forall platformFormat.
Rules platformFormat -> platformFormat -> FilePath
R.decode Rules ByteString
R.posix ByteString
bytes))

foreign import ccall unsafe "getenv"
	c_getenv :: CString -> IO CString

#endif

xdg :: String -> Maybe T.Text -> IO FilePath -> IO FilePath
xdg :: String -> Maybe Text -> IO FilePath -> IO FilePath
xdg String
envkey Maybe Text
label IO FilePath
fallback = do
	Maybe FilePath
env <- String -> IO (Maybe FilePath)
getenv String
envkey
	FilePath
dir <- case Maybe FilePath
env of
		Just FilePath
var -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
var
		Maybe FilePath
Nothing -> IO FilePath
fallback
	FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ case Maybe Text
label of
		Just Text
text -> FilePath -> FilePath -> FilePath
append FilePath
dir (Rules ByteString -> Text -> FilePath
forall platformFormat. Rules platformFormat -> Text -> FilePath
R.fromText Rules ByteString
currentOS Text
text)
		Maybe Text
Nothing -> FilePath
dir

-- | Copy the content of a file to a new entry in the filesystem. If a
-- file already exists at the new location, it will be replaced. Copying
-- a file is not atomic.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
--
-- Since: 0.2.4 / 0.3.4
copyFileContent :: FilePath -- ^ Old location
                -> FilePath -- ^ New location
                -> IO ()
copyFileContent :: FilePath -> FilePath -> IO ()
copyFileContent FilePath
oldPath FilePath
newPath =
	FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile FilePath
oldPath IOMode
IO.ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
old ->
	FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile FilePath
newPath IOMode
IO.WriteMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
new ->
	Handle -> IO ByteString
BL.hGetContents Handle
old IO ByteString -> (ByteString -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Handle -> ByteString -> IO ()
BL.hPut Handle
new

-- | Copy the permissions from one path to another. Both paths must already
-- exist.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
--
-- Since: 0.2.4 / 0.3.4
copyPermissions :: FilePath -- ^ Old location
                -> FilePath -- ^ New location
                -> IO ()
copyPermissions :: FilePath -> FilePath -> IO ()
copyPermissions FilePath
oldPath FilePath
newPath =
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
oldPath ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cOldPath ->
	FilePath -> (CString -> IO ()) -> IO ()
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
newPath ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cNewPath ->
	String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
CError.throwErrnoIfMinus1Retry_ String
"copyPermissions" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
	CString -> CString -> IO CInt
c_copy_permissions CString
cOldPath CString
cNewPath

#ifdef CABAL_OS_WINDOWS

foreign import ccall unsafe "hssystemfileio_copy_permissions"
	c_copy_permissions :: CWString -> CWString -> IO CInt

#else

foreign import ccall unsafe "hssystemfileio_copy_permissions"
	c_copy_permissions :: CString -> CString -> IO CInt

#endif

-- | Copy the content and permissions of a file to a new entry in the
-- filesystem. If a file already exists at the new location, it will be
-- replaced. Copying a file is not atomic.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
--
-- Since: 0.1.1
copyFile :: FilePath -- ^ Old location
         -> FilePath -- ^ New location
         -> IO ()
copyFile :: FilePath -> FilePath -> IO ()
copyFile FilePath
oldPath FilePath
newPath = do
	FilePath -> FilePath -> IO ()
copyFileContent FilePath
oldPath FilePath
newPath
	IO () -> (IOError -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Exc.catch
		(FilePath -> FilePath -> IO ()
copyPermissions FilePath
oldPath FilePath
newPath)
		((\IOError
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) :: IOError -> IO ())

-- | Get when the object at a given path was last modified.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
--
-- Since: 0.2
getModified :: FilePath -> IO UTCTime
getModified :: FilePath -> IO UTCTime
getModified FilePath
path = do
#ifdef CABAL_OS_WINDOWS
	info <- withHANDLE path Win32.getFileInformationByHandle
	let ftime = Win32.bhfiLastWriteTime info
	stime <- Win32.fileTimeToSystemTime ftime
	
	let date = fromGregorian
		(fromIntegral (Win32.wYear stime))
		(fromIntegral (Win32.wMonth stime))
		(fromIntegral (Win32.wDay stime))
	
	let seconds = secondsToDiffTime $
		(toInteger (Win32.wHour stime) * 3600) +
		(toInteger (Win32.wMinute stime) * 60) +
		(toInteger (Win32.wSecond stime))
	
	let msecs = picosecondsToDiffTime $
		(toInteger (Win32.wMilliseconds stime) * 1000000000)
	
	return (UTCTime date (seconds + msecs))
#else
	FileStatus
stat <- String -> FilePath -> IO FileStatus
posixStat String
"getModified" FilePath
path
	let mtime :: EpochTime
mtime = FileStatus -> EpochTime
Posix.modificationTime FileStatus
stat
	UTCTime -> IO UTCTime
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (POSIXTime -> UTCTime
posixSecondsToUTCTime (EpochTime -> POSIXTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac EpochTime
mtime))
#endif

-- | Get the size of an object at a given path. For special objects like
-- links or directories, the size is filesystem&#8208; and
-- platform&#8208;dependent.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
--
-- Since: 0.2
getSize :: FilePath -> IO Integer
getSize :: FilePath -> IO Integer
getSize FilePath
path = do
#ifdef CABAL_OS_WINDOWS
	info <- withHANDLE path Win32.getFileInformationByHandle
	return (toInteger (Win32.bhfiSize info))
#else
	FileStatus
stat <- String -> FilePath -> IO FileStatus
posixStat String
"getSize" FilePath
path
	Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileOffset -> Integer
forall a. Integral a => a -> Integer
toInteger (FileStatus -> FileOffset
Posix.fileSize FileStatus
stat))
#endif

-- | Open a file in binary mode, and return an open 'Handle'. The 'Handle'
-- should be closed with 'IO.hClose' when it is no longer needed.
--
-- 'withFile' is easier to use, because it will handle the 'Handle'&#x2019;s
-- lifetime automatically.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
openFile :: FilePath -> IO.IOMode -> IO IO.Handle
#ifdef SYSTEMFILEIO_LOCAL_OPEN_FILE
openFile path mode = openFile' "openFile" path mode Nothing
#else
openFile :: FilePath -> IOMode -> IO Handle
openFile FilePath
path = String -> IOMode -> IO Handle
IO.openBinaryFile (FilePath -> String
encodeString FilePath
path)
#endif

-- | Open a file in binary mode, and pass its 'Handle' to a provided
-- computation. The 'Handle' will be automatically closed when the
-- computation returns.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
withFile :: FilePath -> IO.IOMode -> (IO.Handle -> IO a) -> IO a
withFile :: forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile FilePath
path IOMode
mode = IO Handle -> (Handle -> IO ()) -> (Handle -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exc.bracket (FilePath -> IOMode -> IO Handle
openFile FilePath
path IOMode
mode) Handle -> IO ()
IO.hClose

-- | Read in the entire content of a binary file.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
readFile :: FilePath -> IO B.ByteString
readFile :: FilePath -> IO ByteString
readFile FilePath
path = FilePath -> IOMode -> (Handle -> IO ByteString) -> IO ByteString
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile FilePath
path IOMode
IO.ReadMode
	(\Handle
h -> Handle -> IO Integer
IO.hFileSize Handle
h IO Integer -> (Integer -> IO ByteString) -> IO ByteString
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Handle -> Int -> IO ByteString
B.hGet Handle
h (Int -> IO ByteString)
-> (Integer -> Int) -> Integer -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral)

-- | Replace the entire content of a binary file with the provided
-- 'B.ByteString'.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
writeFile :: FilePath -> B.ByteString -> IO ()
writeFile :: FilePath -> ByteString -> IO ()
writeFile FilePath
path ByteString
bytes = FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile FilePath
path IOMode
IO.WriteMode
	(\Handle
h -> Handle -> ByteString -> IO ()
B.hPut Handle
h ByteString
bytes)

-- | Append a 'B.ByteString' to a file. If the file does not exist, it will
-- be created.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
appendFile :: FilePath -> B.ByteString -> IO ()
appendFile :: FilePath -> ByteString -> IO ()
appendFile FilePath
path ByteString
bytes = FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile FilePath
path IOMode
IO.AppendMode
	(\Handle
h -> Handle -> ByteString -> IO ()
B.hPut Handle
h ByteString
bytes)

-- | Open a file in text mode, and return an open 'Handle'. The 'Handle'
-- should be closed with 'IO.hClose' when it is no longer needed.
--
-- 'withTextFile' is easier to use, because it will handle the
-- 'Handle'&#x2019;s lifetime automatically.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
openTextFile :: FilePath -> IO.IOMode -> IO IO.Handle
#ifdef SYSTEMFILEIO_LOCAL_OPEN_FILE
openTextFile path mode = openFile' "openTextFile" path mode (Just IO.localeEncoding)
#else
openTextFile :: FilePath -> IOMode -> IO Handle
openTextFile FilePath
path = String -> IOMode -> IO Handle
IO.openFile (FilePath -> String
encodeString FilePath
path)
#endif

-- | Open a file in text mode, and pass its 'Handle' to a provided
-- computation. The 'Handle' will be automatically closed when the
-- computation returns.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
withTextFile :: FilePath -> IO.IOMode -> (IO.Handle -> IO a) -> IO a
withTextFile :: forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withTextFile FilePath
path IOMode
mode = IO Handle -> (Handle -> IO ()) -> (Handle -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exc.bracket (FilePath -> IOMode -> IO Handle
openTextFile FilePath
path IOMode
mode) Handle -> IO ()
IO.hClose

-- | Read in the entire content of a text file.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
readTextFile :: FilePath -> IO T.Text
readTextFile :: FilePath -> IO Text
readTextFile FilePath
path = FilePath -> IOMode -> IO Handle
openTextFile FilePath
path IOMode
IO.ReadMode IO Handle -> (Handle -> IO Text) -> IO Text
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Handle -> IO Text
T.hGetContents

-- | Replace the entire content of a text file with the provided
-- 'T.Text'.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
writeTextFile :: FilePath -> T.Text -> IO ()
writeTextFile :: FilePath -> Text -> IO ()
writeTextFile FilePath
path Text
text = FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withTextFile FilePath
path IOMode
IO.WriteMode
	(\Handle
h -> Handle -> Text -> IO ()
T.hPutStr Handle
h Text
text)

-- | Append 'T.Text' to a file. If the file does not exist, it will
-- be created.
--
-- This computation throws 'IOError' on failure. See &#8220;Classifying
-- I/O errors&#8221; in the "System.IO.Error" documentation for information on
-- why the failure occured.
appendTextFile :: FilePath -> T.Text -> IO ()
appendTextFile :: FilePath -> Text -> IO ()
appendTextFile FilePath
path Text
text = FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall a. FilePath -> IOMode -> (Handle -> IO a) -> IO a
withTextFile FilePath
path IOMode
IO.AppendMode
	(\Handle
h -> Handle -> Text -> IO ()
T.hPutStr Handle
h Text
text)

#ifdef SYSTEMFILEIO_LOCAL_OPEN_FILE
-- | Copied from GHC.IO.FD.openFile
openFile' :: String -> FilePath -> IO.IOMode -> (Maybe IO.TextEncoding) -> IO IO.Handle
openFile' loc path mode codec = open where
	sys_c_open = System.Posix.Internals.c_open
	sys_c_close = System.Posix.Internals.c_close
	flags = iomodeFlags mode
	open = withFilePath path $ \cPath -> do
		c_fd <- throwErrnoPathIfMinus1Retry loc path (sys_c_open cPath flags 0o666)
		(fd, fd_type) <- Exc.onException
			(mkFD c_fd mode Nothing False True)
			(sys_c_close c_fd)
		when (mode == IO.WriteMode && fd_type == GHC.IO.Device.RegularFile) $ do
			GHC.IO.Device.setSize fd 0
		Exc.onException
			(mkHandleFromFD fd fd_type (encodeString path) mode False codec)
			(GHC.IO.Device.close fd)

iomodeFlags :: IO.IOMode -> CInt
iomodeFlags mode = cased .|. commonFlags where
	cased = case mode of
		IO.ReadMode -> flagsR
#ifdef mingw32_HOST_OS
		IO.WriteMode -> flagsW .|. System.Posix.Internals.o_TRUNC
#else
		IO.WriteMode -> flagsW
#endif
		IO.ReadWriteMode -> flagsRW
		IO.AppendMode -> flagsA
	
	flagsR  = System.Posix.Internals.o_RDONLY
	flagsW  = outputFlags .|. System.Posix.Internals.o_WRONLY
	flagsRW = outputFlags .|. System.Posix.Internals.o_RDWR
	flagsA  = flagsW      .|. System.Posix.Internals.o_APPEND
	
	commonFlags = System.Posix.Internals.o_NOCTTY .|.
	              System.Posix.Internals.o_NONBLOCK
	outputFlags = System.Posix.Internals.o_CREAT

#endif

#ifdef CABAL_OS_WINDOWS

-- Only for accessing file or directory metadata.
-- See issue #8.
withHANDLE :: FilePath -> (Win32.HANDLE -> IO a) -> IO a
withHANDLE path = Exc.bracket open close where
	open = Win32.createFile
		(encodeString path)
		0
		(Win32.fILE_SHARE_READ .|. Win32.fILE_SHARE_WRITE)
		Nothing
		Win32.oPEN_EXISTING
		Win32.fILE_FLAG_BACKUP_SEMANTICS
		Nothing
	close = Win32.closeHandle

withFilePath :: FilePath -> (CWString -> IO a) -> IO a
withFilePath path = withCWString (encodeString path)

#else

withFilePath :: FilePath -> (CString -> IO a) -> IO a
withFilePath :: forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path = ByteString -> (CString -> IO a) -> IO a
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString (Rules ByteString -> FilePath -> ByteString
forall platformFormat.
Rules platformFormat -> FilePath -> platformFormat
R.encode Rules ByteString
R.posix FilePath
path)

throwErrnoPathIfMinus1 :: String -> FilePath -> IO CInt -> IO CInt
throwErrnoPathIfMinus1 :: String -> FilePath -> IO CInt -> IO CInt
throwErrnoPathIfMinus1 String
loc FilePath
path = String -> String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> String -> IO a -> IO a
CError.throwErrnoPathIfMinus1 String
loc (FilePath -> String
encodeString FilePath
path)

throwErrnoPathIfMinus1_ :: String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1_ :: String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1_ String
loc FilePath
path = String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
CError.throwErrnoPathIfMinus1_ String
loc (FilePath -> String
encodeString FilePath
path)

throwErrnoPathIfNullRetry :: String -> FilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry :: forall a. String -> FilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry = (Ptr a -> Bool) -> String -> FilePath -> IO (Ptr a) -> IO (Ptr a)
forall a. (a -> Bool) -> String -> FilePath -> IO a -> IO a
throwErrnoPathIfRetry (Ptr a -> Ptr a -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr a
forall a. Ptr a
nullPtr)

throwErrnoPathIfMinus1Retry :: String -> FilePath -> IO CInt -> IO CInt
throwErrnoPathIfMinus1Retry :: String -> FilePath -> IO CInt -> IO CInt
throwErrnoPathIfMinus1Retry = (CInt -> Bool) -> String -> FilePath -> IO CInt -> IO CInt
forall a. (a -> Bool) -> String -> FilePath -> IO a -> IO a
throwErrnoPathIfRetry (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1)

throwErrnoPathIfMinus1Retry_ :: String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1Retry_ :: String -> FilePath -> IO CInt -> IO ()
throwErrnoPathIfMinus1Retry_ = (CInt -> Bool) -> String -> FilePath -> IO CInt -> IO ()
forall a. (a -> Bool) -> String -> FilePath -> IO a -> IO ()
throwErrnoPathIfRetry_ (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1)

throwErrnoPathIfRetry :: (a -> Bool) -> String -> FilePath -> IO a -> IO a
throwErrnoPathIfRetry :: forall a. (a -> Bool) -> String -> FilePath -> IO a -> IO a
throwErrnoPathIfRetry a -> Bool
failed String
loc FilePath
path IO a
io = IO a
loop where
	loop :: IO a
loop = do
		a
a <- IO a
io
		if a -> Bool
failed a
a
			then do
				Errno
errno <- IO Errno
CError.getErrno
				if Errno
errno Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
CError.eINTR
					then IO a
loop
					else String -> String -> IO a
forall a. String -> String -> IO a
CError.throwErrnoPath String
loc (FilePath -> String
encodeString FilePath
path)
			else a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a

throwErrnoPathIfRetry_ :: (a -> Bool) -> String -> FilePath -> IO a -> IO ()
throwErrnoPathIfRetry_ :: forall a. (a -> Bool) -> String -> FilePath -> IO a -> IO ()
throwErrnoPathIfRetry_ a -> Bool
failed String
loc FilePath
path IO a
io = do
	a
_ <- (a -> Bool) -> String -> FilePath -> IO a -> IO a
forall a. (a -> Bool) -> String -> FilePath -> IO a -> IO a
throwErrnoPathIfRetry a -> Bool
failed String
loc FilePath
path IO a
io
	() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

posixStat :: String -> FilePath -> IO Posix.FileStatus
#if MIN_VERSION_unix(2,5,1)
posixStat :: String -> FilePath -> IO FileStatus
posixStat String
_ FilePath
path = ByteString -> IO FileStatus
System.Posix.Files.ByteString.getFileStatus (Rules ByteString -> FilePath -> ByteString
forall platformFormat.
Rules platformFormat -> FilePath -> platformFormat
R.encode Rules ByteString
R.posix FilePath
path)
#else
posixStat loc path = withFd loc path Posix.getFdStatus

withFd :: String -> FilePath -> (Posix.Fd -> IO a) -> IO a
withFd fnName path = Exc.bracket open close where
	open = withFilePath path $ \cpath -> do
		fd <- throwErrnoPathIfMinus1 fnName path (c_open_nonblocking cpath 0)
		return (Posix.Fd fd)
	close = Posix.closeFd

foreign import ccall unsafe "hssystemfileio_open_nonblocking"
	c_open_nonblocking :: CString -> CInt -> IO CInt

#endif

foreign import ccall unsafe "free"
	c_free :: Ptr a -> IO ()

#endif