{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
module Path.IO
(
createDir,
createDirIfMissing,
ensureDir,
removeDir,
removeDirRecur,
removePathForcibly,
renameDir,
renamePath,
listDir,
listDirRel,
listDirRecur,
listDirRecurRel,
copyDirRecur,
copyDirRecur',
WalkAction (..),
walkDir,
walkDirRel,
walkDirAccum,
walkDirAccumRel,
getCurrentDir,
setCurrentDir,
withCurrentDir,
getHomeDir,
getAppUserDataDir,
getUserDocsDir,
getTempDir,
D.XdgDirectory (..),
getXdgDir,
D.XdgDirectoryList (..),
getXdgDirList,
AnyPath (..),
resolveFile,
resolveFile',
resolveDir,
resolveDir',
removeFile,
renameFile,
copyFile,
getFileSize,
findExecutable,
findFile,
findFiles,
findFilesWith,
createFileLink,
createDirLink,
removeDirLink,
getSymlinkTarget,
isSymlink,
withTempFile,
withTempDir,
withSystemTempFile,
withSystemTempDir,
openTempFile,
openBinaryTempFile,
createTempDir,
doesPathExist,
doesFileExist,
doesDirExist,
isLocationOccupied,
forgivingAbsence,
ignoringAbsence,
D.Permissions,
D.emptyPermissions,
D.readable,
D.writable,
D.executable,
D.searchable,
D.setOwnerReadable,
D.setOwnerWritable,
D.setOwnerExecutable,
D.setOwnerSearchable,
getPermissions,
setPermissions,
copyPermissions,
getAccessTime,
setAccessTime,
setModificationTime,
getModificationTime,
)
where
import Control.Arrow ((***))
import Control.Monad
import Control.Monad.Catch
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Maybe (MaybeT (..), runMaybeT)
import Control.Monad.Trans.Writer.Strict (WriterT, execWriterT, tell)
import qualified Data.DList as DList
import Data.Either (lefts, rights)
import Data.Kind (Type)
import Data.List ((\\))
import qualified Data.Set as S
import Data.Time (UTCTime)
import Path
import qualified System.Directory as D
import qualified System.FilePath as F
import System.IO (Handle)
import System.IO.Error (isDoesNotExistError)
import qualified System.IO.Temp as T
import qualified System.PosixCompat.Files as P
createDir :: MonadIO m => Path b Dir -> m ()
createDir :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
createDir = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.createDirectory
createDirIfMissing ::
MonadIO m =>
Bool ->
Path b Dir ->
m ()
createDirIfMissing :: forall (m :: * -> *) b. MonadIO m => Bool -> Path b Dir -> m ()
createDirIfMissing Bool
p = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD (Bool -> FilePath -> IO ()
D.createDirectoryIfMissing Bool
p)
ensureDir :: MonadIO m => Path b Dir -> m ()
ensureDir :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir = forall (m :: * -> *) b. MonadIO m => Bool -> Path b Dir -> m ()
createDirIfMissing Bool
True
removeDir :: MonadIO m => Path b Dir -> m ()
removeDir :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
removeDir = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.removeDirectory
removeDirRecur :: MonadIO m => Path b Dir -> m ()
removeDirRecur :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
removeDirRecur = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.removeDirectoryRecursive
removePathForcibly :: MonadIO m => Path b t -> m ()
removePathForcibly :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m ()
removePathForcibly = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.removePathForcibly
renameDir ::
MonadIO m =>
Path b0 Dir ->
Path b1 Dir ->
m ()
renameDir :: forall (m :: * -> *) b0 b1.
MonadIO m =>
Path b0 Dir -> Path b1 Dir -> m ()
renameDir = forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO ()
D.renameDirectory
renamePath :: MonadIO m => Path b0 t -> Path b1 t -> m ()
renamePath :: forall (m :: * -> *) b0 t b1.
MonadIO m =>
Path b0 t -> Path b1 t -> m ()
renamePath = forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO ()
D.renamePath
listDir ::
MonadIO m =>
Path b Dir ->
m ([Path Abs Dir], [Path Abs File])
listDir :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Abs Dir], [Path Abs File])
listDir Path b Dir
path = do
Path Abs Dir
bpath <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
path
([Path Rel Dir]
subdirs, [Path Rel File]
files) <- forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Rel Dir], [Path Rel File])
listDirRel Path Abs Dir
bpath
forall (m :: * -> *) a. Monad m => a -> m a
return
( (Path Abs Dir
bpath forall b t. Path b Dir -> Path Rel t -> Path b t
</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Path Rel Dir]
subdirs,
(Path Abs Dir
bpath forall b t. Path b Dir -> Path Rel t -> Path b t
</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Path Rel File]
files
)
listDirRel ::
MonadIO m =>
Path b Dir ->
m ([Path Rel Dir], [Path Rel File])
listDirRel :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Rel Dir], [Path Rel File])
listDirRel Path b Dir
path = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
[FilePath]
raw <- forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO [FilePath]
D.getDirectoryContents Path b Dir
path
[Either (Path Rel Dir) (Path Rel File)]
items <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM ([FilePath]
raw forall a. Eq a => [a] -> [a] -> [a]
\\ [FilePath
".", FilePath
".."]) forall a b. (a -> b) -> a -> b
$ \FilePath
item -> do
Bool
isDir <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO Bool
D.doesDirectoryExist forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> FilePath
toFilePath Path b Dir
path FilePath -> FilePath -> FilePath
F.</> FilePath
item)
if Bool
isDir
then forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Rel Dir)
parseRelDir FilePath
item
else forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Rel File)
parseRelFile FilePath
item
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. [Either a b] -> [a]
lefts [Either (Path Rel Dir) (Path Rel File)]
items, forall a b. [Either a b] -> [b]
rights [Either (Path Rel Dir) (Path Rel File)]
items)
listDirRecur ::
MonadIO m =>
Path b Dir ->
m ([Path Abs Dir], [Path Abs File])
listDirRecur :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Abs Dir], [Path Abs File])
listDirRecur Path b Dir
dir =
(forall a. DList a -> [a]
DList.toList forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** forall a. DList a -> [a]
DList.toList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) o b.
(MonadIO m, Monoid o) =>
Maybe
(Path Abs Dir
-> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs))
-> (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m o)
-> Path b Dir
-> m o
walkDirAccum (forall a. a -> Maybe a
Just forall {f :: * -> *} {p} {b} {p}.
MonadIO f =>
p -> [Path b Dir] -> p -> f (WalkAction b)
excludeSymlinks) forall {m :: * -> *} {p} {a} {a}.
Monad m =>
p -> [a] -> [a] -> m (DList a, DList a)
writer Path b Dir
dir
where
excludeSymlinks :: p -> [Path b Dir] -> p -> f (WalkAction b)
excludeSymlinks p
_ [Path b Dir]
subdirs p
_ =
forall b. [Path b Dir] -> WalkAction b
WalkExclude forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
isSymlink [Path b Dir]
subdirs
writer :: p -> [a] -> [a] -> m (DList a, DList a)
writer p
_ [a]
ds [a]
fs =
forall (m :: * -> *) a. Monad m => a -> m a
return
( forall a. [a] -> DList a
DList.fromList [a]
ds,
forall a. [a] -> DList a
DList.fromList [a]
fs
)
listDirRecurRel ::
MonadIO m =>
Path b Dir ->
m ([Path Rel Dir], [Path Rel File])
listDirRecurRel :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Rel Dir], [Path Rel File])
listDirRecurRel Path b Dir
dir =
(forall a. DList a -> [a]
DList.toList forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** forall a. DList a -> [a]
DList.toList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) o b.
(MonadIO m, Monoid o) =>
Maybe
(Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel))
-> (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m o)
-> Path b Dir
-> m o
walkDirAccumRel (forall a. a -> Maybe a
Just Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)
excludeSymlinks) forall {m :: * -> *} {b} {t} {t}.
Monad m =>
Path b Dir
-> [Path Rel t]
-> [Path Rel t]
-> m (DList (Path b t), DList (Path b t))
writer Path b Dir
dir
where
excludeSymlinks :: Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)
excludeSymlinks Path Rel Dir
tdir [Path Rel Dir]
subdirs [Path Rel File]
_ =
forall b. [Path b Dir] -> WalkAction b
WalkExclude forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
isSymlink forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Path b Dir
dir forall b t. Path b Dir -> Path Rel t -> Path b t
</>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Path Rel Dir
tdir forall b t. Path b Dir -> Path Rel t -> Path b t
</>)) [Path Rel Dir]
subdirs
writer :: Path b Dir
-> [Path Rel t]
-> [Path Rel t]
-> m (DList (Path b t), DList (Path b t))
writer Path b Dir
tdir [Path Rel t]
ds [Path Rel t]
fs =
forall (m :: * -> *) a. Monad m => a -> m a
return
( forall a. [a] -> DList a
DList.fromList ((Path b Dir
tdir forall b t. Path b Dir -> Path Rel t -> Path b t
</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Path Rel t]
ds),
forall a. [a] -> DList a
DList.fromList ((Path b Dir
tdir forall b t. Path b Dir -> Path Rel t -> Path b t
</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Path Rel t]
fs)
)
copyDirRecur ::
(MonadIO m, MonadCatch m) =>
Path b0 Dir ->
Path b1 Dir ->
m ()
copyDirRecur :: forall (m :: * -> *) b0 b1.
(MonadIO m, MonadCatch m) =>
Path b0 Dir -> Path b1 Dir -> m ()
copyDirRecur = forall (m :: * -> *) b0 b1.
MonadIO m =>
Bool -> Path b0 Dir -> Path b1 Dir -> m ()
copyDirRecurGen Bool
True
copyDirRecur' ::
(MonadIO m, MonadCatch m) =>
Path b0 Dir ->
Path b1 Dir ->
m ()
copyDirRecur' :: forall (m :: * -> *) b0 b1.
(MonadIO m, MonadCatch m) =>
Path b0 Dir -> Path b1 Dir -> m ()
copyDirRecur' = forall (m :: * -> *) b0 b1.
MonadIO m =>
Bool -> Path b0 Dir -> Path b1 Dir -> m ()
copyDirRecurGen Bool
False
copyDirRecurGen ::
MonadIO m =>
Bool ->
Path b0 Dir ->
Path b1 Dir ->
m ()
copyDirRecurGen :: forall (m :: * -> *) b0 b1.
MonadIO m =>
Bool -> Path b0 Dir -> Path b1 Dir -> m ()
copyDirRecurGen Bool
preserveDirPermissions Path b0 Dir
src Path b1 Dir
dest = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Path Abs Dir
bsrc <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b0 Dir
src
Path Abs Dir
bdest <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b1 Dir
dest
([Path Abs Dir]
dirs, [Path Abs File]
files) <- forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Abs Dir], [Path Abs File])
listDirRecur Path Abs Dir
bsrc
let swapParent ::
Path Abs Dir ->
Path Abs Dir ->
Path Abs t ->
IO (Path Abs t)
swapParent :: forall t.
Path Abs Dir -> Path Abs Dir -> Path Abs t -> IO (Path Abs t)
swapParent Path Abs Dir
old Path Abs Dir
new Path Abs t
path =
(Path Abs Dir
new forall b t. Path b Dir -> Path Rel t -> Path b t
</>)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) b t.
MonadThrow m =>
Path b Dir -> Path b t -> m (Path Rel t)
stripProperPrefix Path Abs Dir
old Path Abs t
path
forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir Path Abs Dir
bdest
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Path Abs Dir]
dirs forall a b. (a -> b) -> a -> b
$ \Path Abs Dir
srcDir -> do
Path Abs Dir
destDir <- forall t.
Path Abs Dir -> Path Abs Dir -> Path Abs t -> IO (Path Abs t)
swapParent Path Abs Dir
bsrc Path Abs Dir
bdest Path Abs Dir
srcDir
Bool
dirIsSymlink <- forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
isSymlink Path Abs Dir
srcDir
if Bool
dirIsSymlink
then do
FilePath
target <- forall (m :: * -> *) b t. MonadIO m => Path b t -> m FilePath
getSymlinkTarget Path Abs Dir
srcDir
FilePath -> FilePath -> IO ()
D.createDirectoryLink FilePath
target forall a b. (a -> b) -> a -> b
$
forall b t. Path b t -> FilePath
toFilePath' Path Abs Dir
destDir
else forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir Path Abs Dir
destDir
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
preserveDirPermissions forall a b. (a -> b) -> a -> b
$
IO () -> IO ()
ignoringIOErrors (forall (m :: * -> *) b0 t0 b1 t1.
MonadIO m =>
Path b0 t0 -> Path b1 t1 -> m ()
copyPermissions Path Abs Dir
srcDir Path Abs Dir
destDir)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Path Abs File]
files forall a b. (a -> b) -> a -> b
$ \Path Abs File
srcFile -> do
Path Abs File
destFile <- forall t.
Path Abs Dir -> Path Abs Dir -> Path Abs t -> IO (Path Abs t)
swapParent Path Abs Dir
bsrc Path Abs Dir
bdest Path Abs File
srcFile
Bool
fileIsSymlink <- forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
isSymlink Path Abs File
srcFile
if Bool
fileIsSymlink
then do
FilePath
target <- forall (m :: * -> *) b t. MonadIO m => Path b t -> m FilePath
getSymlinkTarget Path Abs File
srcFile
FilePath -> FilePath -> IO ()
D.createFileLink FilePath
target (forall b t. Path b t -> FilePath
toFilePath Path Abs File
destFile)
else forall (m :: * -> *) b0 b1.
MonadIO m =>
Path b0 File -> Path b1 File -> m ()
copyFile Path Abs File
srcFile Path Abs File
destFile
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
preserveDirPermissions forall a b. (a -> b) -> a -> b
$
IO () -> IO ()
ignoringIOErrors (forall (m :: * -> *) b0 t0 b1 t1.
MonadIO m =>
Path b0 t0 -> Path b1 t1 -> m ()
copyPermissions Path Abs Dir
bsrc Path Abs Dir
bdest)
data WalkAction b
=
WalkFinish
|
WalkExclude [Path b Dir]
deriving (WalkAction b -> WalkAction b -> Bool
forall b. WalkAction b -> WalkAction b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalkAction b -> WalkAction b -> Bool
$c/= :: forall b. WalkAction b -> WalkAction b -> Bool
== :: WalkAction b -> WalkAction b -> Bool
$c== :: forall b. WalkAction b -> WalkAction b -> Bool
Eq, Int -> WalkAction b -> FilePath -> FilePath
forall b. Int -> WalkAction b -> FilePath -> FilePath
forall b. [WalkAction b] -> FilePath -> FilePath
forall b. WalkAction b -> FilePath
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [WalkAction b] -> FilePath -> FilePath
$cshowList :: forall b. [WalkAction b] -> FilePath -> FilePath
show :: WalkAction b -> FilePath
$cshow :: forall b. WalkAction b -> FilePath
showsPrec :: Int -> WalkAction b -> FilePath -> FilePath
$cshowsPrec :: forall b. Int -> WalkAction b -> FilePath -> FilePath
Show)
walkDir ::
MonadIO m =>
(Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) ->
Path b Dir ->
m ()
walkDir :: forall (m :: * -> *) b.
MonadIO m =>
(Path Abs Dir
-> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs))
-> Path b Dir -> m ()
walkDir Path Abs Dir
-> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)
handler Path b Dir
topdir =
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$
forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
topdir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Set (DeviceID, FileID) -> Path Abs Dir -> m (Maybe ())
walkAvoidLoop forall a. Set a
S.empty
where
walkAvoidLoop :: Set (DeviceID, FileID) -> Path Abs Dir -> m (Maybe ())
walkAvoidLoop Set (DeviceID, FileID)
traversed Path Abs Dir
curdir = do
Maybe (Set (DeviceID, FileID))
mRes <- forall {m :: * -> *}.
MonadIO m =>
Set (DeviceID, FileID)
-> Path Abs Dir -> m (Maybe (Set (DeviceID, FileID)))
checkLoop Set (DeviceID, FileID)
traversed Path Abs Dir
curdir
case Maybe (Set (DeviceID, FileID))
mRes of
Maybe (Set (DeviceID, FileID))
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ()
Just Set (DeviceID, FileID)
traversed' -> Set (DeviceID, FileID) -> Path Abs Dir -> m (Maybe ())
walktree Set (DeviceID, FileID)
traversed' Path Abs Dir
curdir
walktree :: Set (DeviceID, FileID) -> Path Abs Dir -> m (Maybe ())
walktree Set (DeviceID, FileID)
traversed Path Abs Dir
curdir = do
([Path Abs Dir]
subdirs, [Path Abs File]
files) <- forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Abs Dir], [Path Abs File])
listDir Path Abs Dir
curdir
WalkAction Abs
action <- Path Abs Dir
-> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)
handler Path Abs Dir
curdir [Path Abs Dir]
subdirs [Path Abs File]
files
case WalkAction Abs
action of
WalkAction Abs
WalkFinish -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
WalkExclude [Path Abs Dir]
xdirs ->
case [Path Abs Dir]
subdirs forall a. Eq a => [a] -> [a] -> [a]
\\ [Path Abs Dir]
xdirs of
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ()
[Path Abs Dir]
ds ->
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (DeviceID, FileID) -> Path Abs Dir -> m (Maybe ())
walkAvoidLoop Set (DeviceID, FileID)
traversed)
[Path Abs Dir]
ds
checkLoop :: Set (DeviceID, FileID)
-> Path Abs Dir -> m (Maybe (Set (DeviceID, FileID)))
checkLoop Set (DeviceID, FileID)
traversed Path Abs Dir
dir = do
FileStatus
st <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FileStatus
P.getFileStatus (Path Abs Dir -> FilePath
fromAbsDir Path Abs Dir
dir)
let ufid :: (DeviceID, FileID)
ufid = (FileStatus -> DeviceID
P.deviceID FileStatus
st, FileStatus -> FileID
P.fileID FileStatus
st)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if forall a. Ord a => a -> Set a -> Bool
S.member (DeviceID, FileID)
ufid Set (DeviceID, FileID)
traversed
then forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just (forall a. Ord a => a -> Set a -> Set a
S.insert (DeviceID, FileID)
ufid Set (DeviceID, FileID)
traversed)
walkDirRel ::
MonadIO m =>
( Path Rel Dir ->
[Path Rel Dir] ->
[Path Rel File] ->
m (WalkAction Rel)
) ->
Path b Dir ->
m ()
walkDirRel :: forall (m :: * -> *) b.
MonadIO m =>
(Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel))
-> Path b Dir -> m ()
walkDirRel Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)
handler Path b Dir
topdir' = do
Path Abs Dir
topdir <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
topdir'
let walkAvoidLoop :: Set (DeviceID, FileID) -> Path Rel Dir -> m (Maybe ())
walkAvoidLoop Set (DeviceID, FileID)
traversed Path Rel Dir
curdir = do
Maybe (Set (DeviceID, FileID))
mRes <- forall {m :: * -> *}.
MonadIO m =>
Set (DeviceID, FileID)
-> Path Abs Dir -> m (Maybe (Set (DeviceID, FileID)))
checkLoop Set (DeviceID, FileID)
traversed (Path Abs Dir
topdir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
curdir)
case Maybe (Set (DeviceID, FileID))
mRes of
Maybe (Set (DeviceID, FileID))
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ()
Just Set (DeviceID, FileID)
traversed' -> Set (DeviceID, FileID) -> Path Rel Dir -> m (Maybe ())
walktree Set (DeviceID, FileID)
traversed' Path Rel Dir
curdir
walktree :: Set (DeviceID, FileID) -> Path Rel Dir -> m (Maybe ())
walktree Set (DeviceID, FileID)
traversed Path Rel Dir
curdir = do
([Path Rel Dir]
subdirs, [Path Rel File]
files) <- forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Rel Dir], [Path Rel File])
listDirRel (Path Abs Dir
topdir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
curdir)
WalkAction Rel
action <- Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)
handler Path Rel Dir
curdir [Path Rel Dir]
subdirs [Path Rel File]
files
case WalkAction Rel
action of
WalkAction Rel
WalkFinish -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
WalkExclude [Path Rel Dir]
xdirs ->
case [Path Rel Dir]
subdirs forall a. Eq a => [a] -> [a] -> [a]
\\ [Path Rel Dir]
xdirs of
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ()
[Path Rel Dir]
ds ->
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (DeviceID, FileID) -> Path Rel Dir -> m (Maybe ())
walkAvoidLoop Set (DeviceID, FileID)
traversed)
((Path Rel Dir
curdir forall b t. Path b Dir -> Path Rel t -> Path b t
</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Path Rel Dir]
ds)
checkLoop :: Set (DeviceID, FileID)
-> Path Abs Dir -> m (Maybe (Set (DeviceID, FileID)))
checkLoop Set (DeviceID, FileID)
traversed Path Abs Dir
dir = do
FileStatus
st <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FileStatus
P.getFileStatus (Path Abs Dir -> FilePath
fromAbsDir Path Abs Dir
dir)
let ufid :: (DeviceID, FileID)
ufid = (FileStatus -> DeviceID
P.deviceID FileStatus
st, FileStatus -> FileID
P.fileID FileStatus
st)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if forall a. Ord a => a -> Set a -> Bool
S.member (DeviceID, FileID)
ufid Set (DeviceID, FileID)
traversed
then forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just (forall a. Ord a => a -> Set a -> Set a
S.insert (DeviceID, FileID)
ufid Set (DeviceID, FileID)
traversed)
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Set (DeviceID, FileID) -> Path Rel Dir -> m (Maybe ())
walkAvoidLoop forall a. Set a
S.empty $(mkRelDir "."))
walkDirAccum ::
(MonadIO m, Monoid o) =>
Maybe
(Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) ->
(Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m o) ->
Path b Dir ->
m o
walkDirAccum :: forall (m :: * -> *) o b.
(MonadIO m, Monoid o) =>
Maybe
(Path Abs Dir
-> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs))
-> (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m o)
-> Path b Dir
-> m o
walkDirAccum = forall (m :: * -> *) o a b.
(MonadIO m, Monoid o) =>
((Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a))
-> Path b Dir -> WriterT o m ())
-> Maybe
(Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a))
-> (Path a Dir -> [Path a Dir] -> [Path a File] -> m o)
-> Path b Dir
-> m o
walkDirAccumWith forall (m :: * -> *) b.
MonadIO m =>
(Path Abs Dir
-> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs))
-> Path b Dir -> m ()
walkDir
walkDirAccumRel ::
(MonadIO m, Monoid o) =>
Maybe
(Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)) ->
(Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m o) ->
Path b Dir ->
m o
walkDirAccumRel :: forall (m :: * -> *) o b.
(MonadIO m, Monoid o) =>
Maybe
(Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel))
-> (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m o)
-> Path b Dir
-> m o
walkDirAccumRel = forall (m :: * -> *) o a b.
(MonadIO m, Monoid o) =>
((Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a))
-> Path b Dir -> WriterT o m ())
-> Maybe
(Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a))
-> (Path a Dir -> [Path a Dir] -> [Path a File] -> m o)
-> Path b Dir
-> m o
walkDirAccumWith forall (m :: * -> *) b.
MonadIO m =>
(Path Rel Dir
-> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel))
-> Path b Dir -> m ()
walkDirRel
walkDirAccumWith ::
(MonadIO m, Monoid o) =>
( ( Path a Dir ->
[Path a Dir] ->
[Path a File] ->
WriterT o m (WalkAction a)
) ->
Path b Dir ->
WriterT o m ()
) ->
Maybe (Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a)) ->
(Path a Dir -> [Path a Dir] -> [Path a File] -> m o) ->
Path b Dir ->
m o
walkDirAccumWith :: forall (m :: * -> *) o a b.
(MonadIO m, Monoid o) =>
((Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a))
-> Path b Dir -> WriterT o m ())
-> Maybe
(Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a))
-> (Path a Dir -> [Path a Dir] -> [Path a File] -> m o)
-> Path b Dir
-> m o
walkDirAccumWith (Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a))
-> Path b Dir -> WriterT o m ()
walkF Maybe
(Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a))
dHandler Path a Dir -> [Path a Dir] -> [Path a File] -> m o
writer Path b Dir
topdir =
forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
execWriterT ((Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a))
-> Path b Dir -> WriterT o m ()
walkF Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a)
handler Path b Dir
topdir)
where
handler :: Path a Dir
-> [Path a Dir] -> [Path a File] -> WriterT o m (WalkAction a)
handler Path a Dir
dir [Path a Dir]
subdirs [Path a File]
files = do
o
res <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ Path a Dir -> [Path a Dir] -> [Path a File] -> m o
writer Path a Dir
dir [Path a Dir]
subdirs [Path a File]
files
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell o
res
case Maybe
(Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a))
dHandler of
Just Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a)
h -> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a)
h Path a Dir
dir [Path a Dir]
subdirs [Path a File]
files
Maybe
(Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a))
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall b. [Path b Dir] -> WalkAction b
WalkExclude [])
getCurrentDir :: MonadIO m => m (Path Abs Dir)
getCurrentDir :: forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ IO FilePath
D.getCurrentDirectory forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
setCurrentDir :: MonadIO m => Path b Dir -> m ()
setCurrentDir :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
setCurrentDir = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.setCurrentDirectory
withCurrentDir ::
(MonadIO m, MonadMask m) =>
Path b Dir ->
m a ->
m a
withCurrentDir :: forall (m :: * -> *) b a.
(MonadIO m, MonadMask m) =>
Path b Dir -> m a -> m a
withCurrentDir Path b Dir
dir m a
action =
forall (m :: * -> *) a c b.
MonadMask m =>
m a -> (a -> m c) -> (a -> m b) -> m b
bracket forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
setCurrentDir forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const (forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
setCurrentDir Path b Dir
dir forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m a
action)
getHomeDir :: MonadIO m => m (Path Abs Dir)
getHomeDir :: forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getHomeDir = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO FilePath
D.getHomeDirectory forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadIO m => FilePath -> m (Path Abs Dir)
resolveDir'
getAppUserDataDir ::
MonadIO m =>
String ->
m (Path Abs Dir)
getAppUserDataDir :: forall (m :: * -> *). MonadIO m => FilePath -> m (Path Abs Dir)
getAppUserDataDir = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.getAppUserDataDirectory
getUserDocsDir :: MonadIO m => m (Path Abs Dir)
getUserDocsDir :: forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getUserDocsDir = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ IO FilePath
D.getUserDocumentsDirectory forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
getTempDir :: MonadIO m => m (Path Abs Dir)
getTempDir :: forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getTempDir = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO FilePath
D.getTemporaryDirectory forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadIO m => FilePath -> m (Path Abs Dir)
resolveDir'
getXdgDir ::
MonadIO m =>
D.XdgDirectory ->
Maybe (Path Rel Dir) ->
m (Path Abs Dir)
getXdgDir :: forall (m :: * -> *).
MonadIO m =>
XdgDirectory -> Maybe (Path Rel Dir) -> m (Path Abs Dir)
getXdgDir XdgDirectory
xdgDir Maybe (Path Rel Dir)
suffix =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ (XdgDirectory -> FilePath -> IO FilePath
D.getXdgDirectory XdgDirectory
xdgDir forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"" forall b t. Path b t -> FilePath
toFilePath Maybe (Path Rel Dir)
suffix) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
getXdgDirList ::
MonadIO m =>
D.XdgDirectoryList ->
m [Path Abs Dir]
getXdgDirList :: forall (m :: * -> *).
MonadIO m =>
XdgDirectoryList -> m [Path Abs Dir]
getXdgDirList XdgDirectoryList
xdgDirList =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (XdgDirectoryList -> IO [FilePath]
D.getXdgDirectoryList XdgDirectoryList
xdgDirList forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir)
class AnyPath path where
type AbsPath path :: Type
type RelPath path :: Type
canonicalizePath ::
MonadIO m =>
path ->
m (AbsPath path)
makeAbsolute ::
MonadIO m =>
path ->
m (AbsPath path)
makeRelative ::
MonadThrow m =>
Path Abs Dir ->
path ->
m (RelPath path)
makeRelativeToCurrentDir ::
MonadIO m =>
path ->
m (RelPath path)
instance AnyPath (Path b File) where
type AbsPath (Path b File) = Path Abs File
type RelPath (Path b File) = Path Rel File
canonicalizePath :: forall (m :: * -> *).
MonadIO m =>
Path b File -> m (AbsPath (Path b File))
canonicalizePath = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
D.canonicalizePath forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile
makeAbsolute :: forall (m :: * -> *).
MonadIO m =>
Path b File -> m (AbsPath (Path b File))
makeAbsolute = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
D.makeAbsolute forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile
makeRelative :: forall (m :: * -> *).
MonadThrow m =>
Path Abs Dir -> Path b File -> m (RelPath (Path b File))
makeRelative Path Abs Dir
b Path b File
p = forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Rel File)
parseRelFile (FilePath -> FilePath -> FilePath
F.makeRelative (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
b) (forall b t. Path b t -> FilePath
toFilePath Path b File
p))
makeRelativeToCurrentDir :: forall (m :: * -> *).
MonadIO m =>
Path b File -> m (RelPath (Path b File))
makeRelativeToCurrentDir Path b File
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a b c. (a -> b -> c) -> b -> a -> c
flip forall path (m :: * -> *).
(AnyPath path, MonadThrow m) =>
Path Abs Dir -> path -> m (RelPath path)
makeRelative Path b File
p
instance AnyPath (Path b Dir) where
type AbsPath (Path b Dir) = Path Abs Dir
type RelPath (Path b Dir) = Path Rel Dir
canonicalizePath :: forall (m :: * -> *).
MonadIO m =>
Path b Dir -> m (AbsPath (Path b Dir))
canonicalizePath = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO FilePath
D.canonicalizePath forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
makeAbsolute :: forall (m :: * -> *).
MonadIO m =>
Path b Dir -> m (AbsPath (Path b Dir))
makeAbsolute = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO FilePath
D.makeAbsolute forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
makeRelative :: forall (m :: * -> *).
MonadThrow m =>
Path Abs Dir -> Path b Dir -> m (RelPath (Path b Dir))
makeRelative Path Abs Dir
b Path b Dir
p = forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Rel Dir)
parseRelDir (FilePath -> FilePath -> FilePath
F.makeRelative (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
b) (forall b t. Path b t -> FilePath
toFilePath Path b Dir
p))
makeRelativeToCurrentDir :: forall (m :: * -> *).
MonadIO m =>
Path b Dir -> m (RelPath (Path b Dir))
makeRelativeToCurrentDir Path b Dir
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a b c. (a -> b -> c) -> b -> a -> c
flip forall path (m :: * -> *).
(AnyPath path, MonadThrow m) =>
Path Abs Dir -> path -> m (RelPath path)
makeRelative Path b Dir
p
instance AnyPath (SomeBase File) where
type AbsPath (SomeBase File) = Path Abs File
type RelPath (SomeBase File) = Path Rel File
canonicalizePath :: forall (m :: * -> *).
MonadIO m =>
SomeBase File -> m (AbsPath (SomeBase File))
canonicalizePath SomeBase File
s = case SomeBase File
s of
Abs Path Abs File
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
canonicalizePath Path Abs File
a
Rel Path Rel File
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
canonicalizePath Path Rel File
a
makeAbsolute :: forall (m :: * -> *).
MonadIO m =>
SomeBase File -> m (AbsPath (SomeBase File))
makeAbsolute SomeBase File
s = case SomeBase File
s of
Abs Path Abs File
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path Abs File
a
Rel Path Rel File
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path Rel File
a
makeRelative :: forall (m :: * -> *).
MonadThrow m =>
Path Abs Dir -> SomeBase File -> m (RelPath (SomeBase File))
makeRelative Path Abs Dir
r SomeBase File
s = case SomeBase File
s of
Abs Path Abs File
a -> forall path (m :: * -> *).
(AnyPath path, MonadThrow m) =>
Path Abs Dir -> path -> m (RelPath path)
makeRelative Path Abs Dir
r Path Abs File
a
Rel Path Rel File
a -> forall path (m :: * -> *).
(AnyPath path, MonadThrow m) =>
Path Abs Dir -> path -> m (RelPath path)
makeRelative Path Abs Dir
r Path Rel File
a
makeRelativeToCurrentDir :: forall (m :: * -> *).
MonadIO m =>
SomeBase File -> m (RelPath (SomeBase File))
makeRelativeToCurrentDir SomeBase File
s = case SomeBase File
s of
Abs Path Abs File
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (RelPath path)
makeRelativeToCurrentDir Path Abs File
a
Rel Path Rel File
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (RelPath path)
makeRelativeToCurrentDir Path Rel File
a
instance AnyPath (SomeBase Dir) where
type AbsPath (SomeBase Dir) = Path Abs Dir
type RelPath (SomeBase Dir) = Path Rel Dir
canonicalizePath :: forall (m :: * -> *).
MonadIO m =>
SomeBase Dir -> m (AbsPath (SomeBase Dir))
canonicalizePath SomeBase Dir
s = case SomeBase Dir
s of
Abs Path Abs Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
canonicalizePath Path Abs Dir
a
Rel Path Rel Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
canonicalizePath Path Rel Dir
a
makeAbsolute :: forall (m :: * -> *).
MonadIO m =>
SomeBase Dir -> m (AbsPath (SomeBase Dir))
makeAbsolute SomeBase Dir
s = case SomeBase Dir
s of
Abs Path Abs Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path Abs Dir
a
Rel Path Rel Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path Rel Dir
a
makeRelative :: forall (m :: * -> *).
MonadThrow m =>
Path Abs Dir -> SomeBase Dir -> m (RelPath (SomeBase Dir))
makeRelative Path Abs Dir
r SomeBase Dir
s = case SomeBase Dir
s of
Abs Path Abs Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadThrow m) =>
Path Abs Dir -> path -> m (RelPath path)
makeRelative Path Abs Dir
r Path Abs Dir
a
Rel Path Rel Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadThrow m) =>
Path Abs Dir -> path -> m (RelPath path)
makeRelative Path Abs Dir
r Path Rel Dir
a
makeRelativeToCurrentDir :: forall (m :: * -> *).
MonadIO m =>
SomeBase Dir -> m (RelPath (SomeBase Dir))
makeRelativeToCurrentDir SomeBase Dir
s = case SomeBase Dir
s of
Abs Path Abs Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (RelPath path)
makeRelativeToCurrentDir Path Abs Dir
a
Rel Path Rel Dir
a -> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (RelPath path)
makeRelativeToCurrentDir Path Rel Dir
a
resolveFile ::
MonadIO m =>
Path Abs Dir ->
FilePath ->
m (Path Abs File)
resolveFile :: forall (m :: * -> *).
MonadIO m =>
Path Abs Dir -> FilePath -> m (Path Abs File)
resolveFile Path Abs Dir
b FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
D.canonicalizePath (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
b FilePath -> FilePath -> FilePath
F.</> FilePath
p) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile
resolveFile' ::
MonadIO m =>
FilePath ->
m (Path Abs File)
resolveFile' :: forall (m :: * -> *). MonadIO m => FilePath -> m (Path Abs File)
resolveFile' FilePath
p = forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *).
MonadIO m =>
Path Abs Dir -> FilePath -> m (Path Abs File)
resolveFile FilePath
p
resolveDir ::
MonadIO m =>
Path Abs Dir ->
FilePath ->
m (Path Abs Dir)
resolveDir :: forall (m :: * -> *).
MonadIO m =>
Path Abs Dir -> FilePath -> m (Path Abs Dir)
resolveDir Path Abs Dir
b FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
D.canonicalizePath (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
b FilePath -> FilePath -> FilePath
F.</> FilePath
p) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
resolveDir' ::
MonadIO m =>
FilePath ->
m (Path Abs Dir)
resolveDir' :: forall (m :: * -> *). MonadIO m => FilePath -> m (Path Abs Dir)
resolveDir' FilePath
p = forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *).
MonadIO m =>
Path Abs Dir -> FilePath -> m (Path Abs Dir)
resolveDir FilePath
p
removeFile :: MonadIO m => Path b File -> m ()
removeFile :: forall (m :: * -> *) b. MonadIO m => Path b File -> m ()
removeFile = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.removeFile
renameFile ::
MonadIO m =>
Path b0 File ->
Path b1 File ->
m ()
renameFile :: forall (m :: * -> *) b0 b1.
MonadIO m =>
Path b0 File -> Path b1 File -> m ()
renameFile = forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO ()
D.renameFile
copyFile ::
MonadIO m =>
Path b0 File ->
Path b1 File ->
m ()
copyFile :: forall (m :: * -> *) b0 b1.
MonadIO m =>
Path b0 File -> Path b1 File -> m ()
copyFile = forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO ()
D.copyFile
getFileSize :: MonadIO m => Path b File -> m Integer
getFileSize :: forall (m :: * -> *) b. MonadIO m => Path b File -> m Integer
getFileSize = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO Integer
D.getFileSize
findExecutable ::
MonadIO m =>
Path Rel File ->
m (Maybe (Path Abs File))
findExecutable :: forall (m :: * -> *).
MonadIO m =>
Path Rel File -> m (Maybe (Path Abs File))
findExecutable = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO (Maybe FilePath)
D.findExecutable
findFile ::
MonadIO m =>
[Path b Dir] ->
Path Rel File ->
m (Maybe (Path Abs File))
findFile :: forall (m :: * -> *) b.
MonadIO m =>
[Path b Dir] -> Path Rel File -> m (Maybe (Path Abs File))
findFile [] Path Rel File
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
findFile (Path b Dir
d : [Path b Dir]
ds) Path Rel File
file = do
Path Abs File
bfile <- (forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
file) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
d
Bool
exist <- forall (m :: * -> *) b. MonadIO m => Path b File -> m Bool
doesFileExist Path Abs File
bfile
if Bool
exist
then forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Path Abs File
bfile)
else forall (m :: * -> *) b.
MonadIO m =>
[Path b Dir] -> Path Rel File -> m (Maybe (Path Abs File))
findFile [Path b Dir]
ds Path Rel File
file
findFiles ::
MonadIO m =>
[Path b Dir] ->
Path Rel File ->
m [Path Abs File]
findFiles :: forall (m :: * -> *) b.
MonadIO m =>
[Path b Dir] -> Path Rel File -> m [Path Abs File]
findFiles = forall (m :: * -> *) b.
MonadIO m =>
(Path Abs File -> m Bool)
-> [Path b Dir] -> Path Rel File -> m [Path Abs File]
findFilesWith (forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
findFilesWith ::
MonadIO m =>
(Path Abs File -> m Bool) ->
[Path b Dir] ->
Path Rel File ->
m [Path Abs File]
findFilesWith :: forall (m :: * -> *) b.
MonadIO m =>
(Path Abs File -> m Bool)
-> [Path b Dir] -> Path Rel File -> m [Path Abs File]
findFilesWith Path Abs File -> m Bool
_ [] Path Rel File
_ = forall (m :: * -> *) a. Monad m => a -> m a
return []
findFilesWith Path Abs File -> m Bool
f (Path b Dir
d : [Path b Dir]
ds) Path Rel File
file = do
Path Abs File
bfile <- (forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
file) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
d
Bool
exist <- forall (m :: * -> *) b. MonadIO m => Path b File -> m Bool
doesFileExist Path Abs File
bfile
Bool
b <- if Bool
exist then Path Abs File -> m Bool
f Path Abs File
bfile else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
if Bool
b
then (Path Abs File
bfile forall a. a -> [a] -> [a]
:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) b.
MonadIO m =>
(Path Abs File -> m Bool)
-> [Path b Dir] -> Path Rel File -> m [Path Abs File]
findFilesWith Path Abs File -> m Bool
f [Path b Dir]
ds Path Rel File
file
else forall (m :: * -> *) b.
MonadIO m =>
(Path Abs File -> m Bool)
-> [Path b Dir] -> Path Rel File -> m [Path Abs File]
findFilesWith Path Abs File -> m Bool
f [Path b Dir]
ds Path Rel File
file
createFileLink ::
MonadIO m =>
Path b0 File ->
Path b1 File ->
m ()
createFileLink :: forall (m :: * -> *) b0 b1.
MonadIO m =>
Path b0 File -> Path b1 File -> m ()
createFileLink = forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO ()
D.createFileLink
createDirLink ::
MonadIO m =>
Path b0 Dir ->
Path b1 Dir ->
m ()
createDirLink :: forall (m :: * -> *) b0 b1.
MonadIO m =>
Path b0 Dir -> Path b1 Dir -> m ()
createDirLink Path b0 Dir
target' Path b1 Dir
dest' = do
let target :: FilePath
target = forall b t. Path b t -> FilePath
toFilePath Path b0 Dir
target'
dest :: FilePath
dest = forall b t. Path b t -> FilePath
toFilePath' Path b1 Dir
dest'
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
D.createDirectoryLink FilePath
target FilePath
dest
removeDirLink ::
MonadIO m =>
Path b Dir ->
m ()
removeDirLink :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
removeDirLink = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO ()
D.removeDirectoryLink
getSymlinkTarget ::
MonadIO m =>
Path b t ->
m FilePath
getSymlinkTarget :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m FilePath
getSymlinkTarget = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO FilePath
D.getSymbolicLinkTarget
isSymlink :: MonadIO m => Path b t -> m Bool
isSymlink :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
isSymlink = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO Bool
D.pathIsSymbolicLink
withTempFile ::
(MonadIO m, MonadMask m) =>
Path b Dir ->
String ->
(Path Abs File -> Handle -> m a) ->
m a
withTempFile :: forall (m :: * -> *) b a.
(MonadIO m, MonadMask m) =>
Path b Dir -> FilePath -> (Path Abs File -> Handle -> m a) -> m a
withTempFile Path b Dir
path FilePath
t Path Abs File -> Handle -> m a
action = do
Path Abs Dir
apath <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
path
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
FilePath -> FilePath -> (FilePath -> Handle -> m a) -> m a
T.withTempFile (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
apath) FilePath
t forall a b. (a -> b) -> a -> b
$ \FilePath
file Handle
h ->
forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile FilePath
file forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a b c. (a -> b -> c) -> b -> a -> c
flip Path Abs File -> Handle -> m a
action Handle
h
withTempDir ::
(MonadIO m, MonadMask m) =>
Path b Dir ->
String ->
(Path Abs Dir -> m a) ->
m a
withTempDir :: forall (m :: * -> *) b a.
(MonadIO m, MonadMask m) =>
Path b Dir -> FilePath -> (Path Abs Dir -> m a) -> m a
withTempDir Path b Dir
path FilePath
t Path Abs Dir -> m a
action = do
Path Abs Dir
apath <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
path
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
FilePath -> FilePath -> (FilePath -> m a) -> m a
T.withTempDirectory (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
apath) FilePath
t (forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Path Abs Dir -> m a
action)
withSystemTempFile ::
(MonadIO m, MonadMask m) =>
String ->
(Path Abs File -> Handle -> m a) ->
m a
withSystemTempFile :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
FilePath -> (Path Abs File -> Handle -> m a) -> m a
withSystemTempFile FilePath
t Path Abs File -> Handle -> m a
action =
forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getTempDir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Path Abs Dir
path ->
forall (m :: * -> *) b a.
(MonadIO m, MonadMask m) =>
Path b Dir -> FilePath -> (Path Abs File -> Handle -> m a) -> m a
withTempFile Path Abs Dir
path FilePath
t Path Abs File -> Handle -> m a
action
withSystemTempDir ::
(MonadIO m, MonadMask m) =>
String ->
(Path Abs Dir -> m a) ->
m a
withSystemTempDir :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
FilePath -> (Path Abs Dir -> m a) -> m a
withSystemTempDir FilePath
t Path Abs Dir -> m a
action =
forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getTempDir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Path Abs Dir
path ->
forall (m :: * -> *) b a.
(MonadIO m, MonadMask m) =>
Path b Dir -> FilePath -> (Path Abs Dir -> m a) -> m a
withTempDir Path Abs Dir
path FilePath
t Path Abs Dir -> m a
action
openTempFile ::
MonadIO m =>
Path b Dir ->
String ->
m (Path Abs File, Handle)
openTempFile :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> FilePath -> m (Path Abs File, Handle)
openTempFile Path b Dir
path FilePath
t = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Path Abs Dir
apath <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
path
(FilePath
tfile, Handle
h) <- forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> FilePath -> IO (FilePath, Handle)
T.openTempFile Path Abs Dir
apath FilePath
t
(,Handle
h) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile FilePath
tfile
openBinaryTempFile ::
MonadIO m =>
Path b Dir ->
String ->
m (Path Abs File, Handle)
openBinaryTempFile :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> FilePath -> m (Path Abs File, Handle)
openBinaryTempFile Path b Dir
path FilePath
t = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Path Abs Dir
apath <- forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
path
(FilePath
tfile, Handle
h) <- forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> FilePath -> IO (FilePath, Handle)
T.openBinaryTempFile Path Abs Dir
apath FilePath
t
(,Handle
h) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile FilePath
tfile
createTempDir ::
MonadIO m =>
Path b Dir ->
String ->
m (Path Abs Dir)
createTempDir :: forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> FilePath -> m (Path Abs Dir)
createTempDir Path b Dir
path FilePath
t =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall path (m :: * -> *).
(AnyPath path, MonadIO m) =>
path -> m (AbsPath path)
makeAbsolute Path b Dir
path forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Path Abs Dir
apath ->
forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> FilePath -> IO FilePath
T.createTempDirectory Path Abs Dir
apath FilePath
t forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir
doesPathExist :: MonadIO m => Path b t -> m Bool
doesPathExist :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
doesPathExist = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO Bool
D.doesPathExist
doesFileExist :: MonadIO m => Path b File -> m Bool
doesFileExist :: forall (m :: * -> *) b. MonadIO m => Path b File -> m Bool
doesFileExist = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO Bool
D.doesFileExist
doesDirExist :: MonadIO m => Path b Dir -> m Bool
doesDirExist :: forall (m :: * -> *) b. MonadIO m => Path b Dir -> m Bool
doesDirExist = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO Bool
D.doesDirectoryExist
isLocationOccupied :: MonadIO m => Path b t -> m Bool
isLocationOccupied :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m Bool
isLocationOccupied Path b t
path = do
let fp :: FilePath
fp = forall b t. Path b t -> FilePath
toFilePath Path b t
path
Bool
file <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO Bool
D.doesFileExist FilePath
fp)
Bool
dir <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO Bool
D.doesDirectoryExist FilePath
fp)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
file Bool -> Bool -> Bool
|| Bool
dir)
forgivingAbsence :: (MonadIO m, MonadCatch m) => m a -> m (Maybe a)
forgivingAbsence :: forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence m a
f =
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> Bool) -> m a -> (e -> m a) -> m a
catchIf
IOError -> Bool
isDoesNotExistError
(forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m a
f)
(forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing)
ignoringAbsence :: (MonadIO m, MonadCatch m) => m a -> m ()
ignoringAbsence :: forall (m :: * -> *) a. (MonadIO m, MonadCatch m) => m a -> m ()
ignoringAbsence = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence
getPermissions :: MonadIO m => Path b t -> m D.Permissions
getPermissions :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m Permissions
getPermissions = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO Permissions
D.getPermissions
setPermissions :: MonadIO m => Path b t -> D.Permissions -> m ()
setPermissions :: forall (m :: * -> *) b t.
MonadIO m =>
Path b t -> Permissions -> m ()
setPermissions = forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> Permissions -> IO ()
D.setPermissions
copyPermissions ::
MonadIO m =>
Path b0 t0 ->
Path b1 t1 ->
m ()
copyPermissions :: forall (m :: * -> *) b0 t0 b1 t1.
MonadIO m =>
Path b0 t0 -> Path b1 t1 -> m ()
copyPermissions = forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO ()
D.copyPermissions
getAccessTime :: MonadIO m => Path b t -> m UTCTime
getAccessTime :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m UTCTime
getAccessTime = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO UTCTime
D.getAccessTime
setAccessTime :: MonadIO m => Path b t -> UTCTime -> m ()
setAccessTime :: forall (m :: * -> *) b t. MonadIO m => Path b t -> UTCTime -> m ()
setAccessTime = forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> UTCTime -> IO ()
D.setAccessTime
setModificationTime :: MonadIO m => Path b t -> UTCTime -> m ()
setModificationTime :: forall (m :: * -> *) b t. MonadIO m => Path b t -> UTCTime -> m ()
setModificationTime = forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> UTCTime -> IO ()
D.setModificationTime
getModificationTime :: MonadIO m => Path b t -> m UTCTime
getModificationTime :: forall (m :: * -> *) b t. MonadIO m => Path b t -> m UTCTime
getModificationTime = forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO UTCTime
D.getModificationTime
liftD ::
MonadIO m =>
(FilePath -> IO a) ->
Path b t ->
m a
liftD :: forall (m :: * -> *) a b t.
MonadIO m =>
(FilePath -> IO a) -> Path b t -> m a
liftD FilePath -> IO a
m = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO a
m forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> FilePath
toFilePath'
{-# INLINE liftD #-}
liftD2 ::
MonadIO m =>
(FilePath -> FilePath -> IO a) ->
Path b0 t0 ->
Path b1 t1 ->
m a
liftD2 :: forall (m :: * -> *) a b0 t0 b1 t1.
MonadIO m =>
(FilePath -> FilePath -> IO a) -> Path b0 t0 -> Path b1 t1 -> m a
liftD2 FilePath -> FilePath -> IO a
m Path b0 t0
a Path b1 t1
b = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO a
m (forall b t. Path b t -> FilePath
toFilePath' Path b0 t0
a) (forall b t. Path b t -> FilePath
toFilePath' Path b1 t1
b)
{-# INLINE liftD2 #-}
liftD2' ::
MonadIO m =>
(FilePath -> v -> IO a) ->
Path b t ->
v ->
m a
liftD2' :: forall (m :: * -> *) v a b t.
MonadIO m =>
(FilePath -> v -> IO a) -> Path b t -> v -> m a
liftD2' FilePath -> v -> IO a
m Path b t
a v
v = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> v -> IO a
m (forall b t. Path b t -> FilePath
toFilePath' Path b t
a) v
v
{-# INLINE liftD2' #-}
toFilePath' :: Path b t -> FilePath
toFilePath' :: forall b t. Path b t -> FilePath
toFilePath' = FilePath -> FilePath
F.dropTrailingPathSeparator forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> FilePath
toFilePath
ignoringIOErrors :: IO () -> IO ()
ignoringIOErrors :: IO () -> IO ()
ignoringIOErrors IO ()
ioe = IO ()
ioe forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` forall (m :: * -> *). Monad m => IOError -> m ()
handler
where
handler :: Monad m => IOError -> m ()
handler :: forall (m :: * -> *). Monad m => IOError -> m ()
handler = forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())