1{-# LANGUAGE FlexibleInstances #-}
2{-# LANGUAGE TemplateHaskell #-}
3{-# LANGUAGE TupleSections #-}
4{-# LANGUAGE TypeFamilies #-}
5
6-- |
7-- Module      :  Path.IO
8-- Copyright   :  © 2016–present Mark Karpov
9-- License     :  BSD 3 clause
10--
11-- Maintainer  :  Mark Karpov <markkarpov92@gmail.com>
12-- Stability   :  experimental
13-- Portability :  portable
14--
15-- This module provides an interface to "System.Directory" for users of the
16-- "Path" module. It also implements commonly used primitives like recursive
17-- scanning and copying of directories, working with temporary
18-- files\/directories, etc.
19module Path.IO
20  ( -- * Actions on directories
21    createDir,
22    createDirIfMissing,
23    ensureDir,
24    removeDir,
25    removeDirRecur,
26    renameDir,
27    listDir,
28    listDirRel,
29    listDirRecur,
30    listDirRecurRel,
31    copyDirRecur,
32    copyDirRecur',
33
34    -- ** Walking directory trees
35    WalkAction (..),
36    walkDir,
37    walkDirRel,
38    walkDirAccum,
39    walkDirAccumRel,
40
41    -- ** Current working directory
42    getCurrentDir,
43    setCurrentDir,
44    withCurrentDir,
45
46    -- * Pre-defined directories
47    getHomeDir,
48    getAppUserDataDir,
49    getUserDocsDir,
50    getTempDir,
51    D.XdgDirectory (..),
52    getXdgDir,
53    D.XdgDirectoryList (..),
54    getXdgDirList,
55
56    -- * Path transformation
57    AnyPath (..),
58    resolveFile,
59    resolveFile',
60    resolveDir,
61    resolveDir',
62
63    -- * Actions on files
64    removeFile,
65    renameFile,
66    copyFile,
67    findExecutable,
68    findFile,
69    findFiles,
70    findFilesWith,
71
72    -- * Symbolic links
73    createFileLink,
74    createDirLink,
75    removeDirLink,
76    getSymlinkTarget,
77    isSymlink,
78
79    -- * Temporary files and directories
80    withTempFile,
81    withTempDir,
82    withSystemTempFile,
83    withSystemTempDir,
84    openTempFile,
85    openBinaryTempFile,
86    createTempDir,
87
88    -- * Existence tests
89    doesFileExist,
90    doesDirExist,
91    isLocationOccupied,
92    forgivingAbsence,
93    ignoringAbsence,
94
95    -- * Permissions
96    D.Permissions,
97    D.emptyPermissions,
98    D.readable,
99    D.writable,
100    D.executable,
101    D.searchable,
102    D.setOwnerReadable,
103    D.setOwnerWritable,
104    D.setOwnerExecutable,
105    D.setOwnerSearchable,
106    getPermissions,
107    setPermissions,
108    copyPermissions,
109
110    -- * Timestamps
111    getAccessTime,
112    setAccessTime,
113    setModificationTime,
114    getModificationTime,
115  )
116where
117
118import Control.Arrow ((***))
119import Control.Monad
120import Control.Monad.Catch
121import Control.Monad.IO.Class (MonadIO (..))
122import Control.Monad.Trans.Class (lift)
123import Control.Monad.Trans.Maybe (MaybeT (..), runMaybeT)
124import Control.Monad.Trans.Writer.Strict (WriterT, execWriterT, tell)
125import qualified Data.DList as DList
126import Data.Either (lefts, rights)
127import Data.Kind (Type)
128import Data.List ((\\))
129import qualified Data.Set as S
130import Data.Time (UTCTime)
131import Path
132import qualified System.Directory as D
133import qualified System.FilePath as F
134import System.IO (Handle)
135import System.IO.Error (isDoesNotExistError)
136import qualified System.IO.Temp as T
137import qualified System.PosixCompat.Files as P
138
139----------------------------------------------------------------------------
140-- Actions on directories
141
142-- | @'createDir' dir@ creates a new directory @dir@ which is initially
143-- empty, or as near to empty as the operating system allows.
144--
145-- The operation may fail with:
146--
147-- * 'isPermissionError' \/ 'PermissionDenied'
148-- The process has insufficient privileges to perform the operation.
149-- @[EROFS, EACCES]@
150--
151-- * 'isAlreadyExistsError' \/ 'AlreadyExists'
152-- The operand refers to a directory that already exists.
153-- @ [EEXIST]@
154--
155-- * 'HardwareFault'
156-- A physical I\/O error has occurred.
157-- @[EIO]@
158--
159-- * 'InvalidArgument'
160-- The operand is not a valid directory name.
161-- @[ENAMETOOLONG, ELOOP]@
162--
163-- * 'NoSuchThing'
164-- There is no path to the directory.
165-- @[ENOENT, ENOTDIR]@
166--
167-- * 'ResourceExhausted' Insufficient resources (virtual memory, process
168-- file descriptors, physical disk space, etc.) are available to perform the
169-- operation. @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
170--
171-- * 'InappropriateType'
172-- The path refers to an existing non-directory object.
173-- @[EEXIST]@
174createDir :: MonadIO m => Path b Dir -> m ()
175createDir = liftD D.createDirectory
176
177-- | @'createDirIfMissing' parents dir@ creates a new directory @dir@ if it
178-- doesn't exist. If the first argument is 'True' the function will also
179-- create all parent directories if they are missing.
180createDirIfMissing ::
181  MonadIO m =>
182  -- | Create its parents too?
183  Bool ->
184  -- | The path to the directory you want to make
185  Path b Dir ->
186  m ()
187createDirIfMissing p = liftD (D.createDirectoryIfMissing p)
188
189-- | Ensure that a directory exists creating it and its parent directories
190-- if necessary. This is just a handy shortcut:
191--
192-- > ensureDir = createDirIfMissing True
193--
194-- @since 0.3.1
195ensureDir :: MonadIO m => Path b Dir -> m ()
196ensureDir = createDirIfMissing True
197
198-- | @'removeDir' dir@ removes an existing directory @dir@. The
199-- implementation may specify additional constraints which must be satisfied
200-- before a directory can be removed (e.g. the directory has to be empty, or
201-- may not be in use by other processes). It is not legal for an
202-- implementation to partially remove a directory unless the entire
203-- directory is removed. A conformant implementation need not support
204-- directory removal in all situations (e.g. removal of the root directory).
205--
206-- The operation may fail with:
207--
208-- * 'HardwareFault'
209-- A physical I\/O error has occurred.
210-- @[EIO]@
211--
212-- * 'InvalidArgument'
213-- The operand is not a valid directory name.
214-- @[ENAMETOOLONG, ELOOP]@
215--
216-- * 'isDoesNotExistError' \/ 'NoSuchThing'
217-- The directory does not exist.
218-- @[ENOENT, ENOTDIR]@
219--
220-- * 'isPermissionError' \/ 'PermissionDenied'
221-- The process has insufficient privileges to perform the operation.
222-- @[EROFS, EACCES, EPERM]@
223--
224-- * 'UnsatisfiedConstraints'
225-- Implementation-dependent constraints are not satisfied.
226-- @[EBUSY, ENOTEMPTY, EEXIST]@
227--
228-- * 'UnsupportedOperation'
229-- The implementation does not support removal in this situation.
230-- @[EINVAL]@
231--
232-- * 'InappropriateType'
233-- The operand refers to an existing non-directory object.
234-- @[ENOTDIR]@
235removeDir :: MonadIO m => Path b Dir -> m ()
236removeDir = liftD D.removeDirectory
237
238-- | @'removeDirRecur' dir@ removes an existing directory @dir@ together
239-- with its contents and sub-directories. Within this directory, symbolic
240-- links are removed without affecting their targets.
241removeDirRecur :: MonadIO m => Path b Dir -> m ()
242removeDirRecur = liftD D.removeDirectoryRecursive
243
244-- | @'renameDir' old new@ changes the name of an existing directory from
245--  @old@ to @new@. If the @new@ directory already exists, it is atomically
246--  replaced by the @old@ directory. If the @new@ directory is neither the
247--  @old@ directory nor an alias of the @old@ directory, it is removed as if
248--  by 'removeDir'. A conformant implementation need not support renaming
249--  directories in all situations (e.g. renaming to an existing directory, or
250--  across different physical devices), but the constraints must be
251--  documented.
252--
253--  On Win32 platforms, @renameDir@ fails if the @new@ directory already
254--  exists.
255--
256--  The operation may fail with:
257--
258--  * 'HardwareFault'
259--  A physical I\/O error has occurred.
260--  @[EIO]@
261--
262--  * 'InvalidArgument'
263--  Either operand is not a valid directory name.
264--  @[ENAMETOOLONG, ELOOP]@
265--
266--  * 'isDoesNotExistError' \/ 'NoSuchThing'
267--  The original directory does not exist, or there is no path to the target.
268--  @[ENOENT, ENOTDIR]@
269--
270--  * 'isPermissionError' \/ 'PermissionDenied'
271--  The process has insufficient privileges to perform the operation.
272--  @[EROFS, EACCES, EPERM]@
273--
274--  * 'ResourceExhausted'
275--  Insufficient resources are available to perform the operation.
276--  @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
277--
278--  * 'UnsatisfiedConstraints'
279--  Implementation-dependent constraints are not satisfied.
280--  @[EBUSY, ENOTEMPTY, EEXIST]@
281--
282--  * 'UnsupportedOperation'
283--  The implementation does not support renaming in this situation.
284--  @[EINVAL, EXDEV]@
285--
286--  * 'InappropriateType'
287--  Either path refers to an existing non-directory object.
288--  @[ENOTDIR, EISDIR]@
289renameDir ::
290  MonadIO m =>
291  -- | Old name
292  Path b0 Dir ->
293  -- | New name
294  Path b1 Dir ->
295  m ()
296renameDir = liftD2 D.renameDirectory
297
298-- | @'listDir' dir@ returns a list of /all/ entries in @dir@ without the
299-- special entries (@.@ and @..@). Entries are not sorted.
300--
301-- The operation may fail with:
302--
303-- * 'HardwareFault'
304--   A physical I\/O error has occurred.
305--   @[EIO]@
306--
307-- * 'InvalidArgument'
308--   The operand is not a valid directory name.
309--   @[ENAMETOOLONG, ELOOP]@
310--
311-- * 'isDoesNotExistError' \/ 'NoSuchThing'
312--   The directory does not exist.
313--   @[ENOENT, ENOTDIR]@
314--
315-- * 'isPermissionError' \/ 'PermissionDenied'
316--   The process has insufficient privileges to perform the operation.
317--   @[EACCES]@
318--
319-- * 'ResourceExhausted'
320--   Insufficient resources are available to perform the operation.
321--   @[EMFILE, ENFILE]@
322--
323-- * 'InappropriateType'
324--   The path refers to an existing non-directory object.
325--   @[ENOTDIR]@
326listDir ::
327  MonadIO m =>
328  -- | Directory to list
329  Path b Dir ->
330  -- | Sub-directories and files
331  m ([Path Abs Dir], [Path Abs File])
332listDir path = do
333  bpath <- makeAbsolute path
334  (subdirs, files) <- listDirRel bpath
335  return
336    ( (bpath </>) <$> subdirs,
337      (bpath </>) <$> files
338    )
339
340-- | The same as 'listDir' but returns relative paths.
341--
342-- @since 1.4.0
343listDirRel ::
344  MonadIO m =>
345  -- | Directory to list
346  Path b Dir ->
347  -- | Sub-directories and files
348  m ([Path Rel Dir], [Path Rel File])
349listDirRel path = liftIO $ do
350  raw <- liftD D.getDirectoryContents path
351  items <- forM (raw \\ [".", ".."]) $ \item -> do
352    isDir <- liftIO (D.doesDirectoryExist $ toFilePath path F.</> item)
353    if isDir
354      then Left <$> parseRelDir item
355      else Right <$> parseRelFile item
356  return (lefts items, rights items)
357
358-- | Similar to 'listDir', but recursively traverses every sub-directory
359-- /excluding symbolic links/, and returns all files and directories found.
360-- This can fail with the same exceptions as 'listDir'.
361--
362-- __Note__: before version /1.3.0/, this function followed symlinks.
363listDirRecur ::
364  MonadIO m =>
365  -- | Directory to list
366  Path b Dir ->
367  -- | Sub-directories and files
368  m ([Path Abs Dir], [Path Abs File])
369listDirRecur dir =
370  (DList.toList *** DList.toList)
371    <$> walkDirAccum (Just excludeSymlinks) writer dir
372  where
373    excludeSymlinks _ subdirs _ =
374      WalkExclude <$> filterM isSymlink subdirs
375    writer _ ds fs =
376      return
377        ( DList.fromList ds,
378          DList.fromList fs
379        )
380
381-- | The same as 'listDirRecur' but returns paths that are relative to the
382-- given directory.
383--
384-- @since 1.4.2
385listDirRecurRel ::
386  MonadIO m =>
387  -- | Directory to list
388  Path b Dir ->
389  -- | Sub-directories and files
390  m ([Path Rel Dir], [Path Rel File])
391listDirRecurRel dir =
392  (DList.toList *** DList.toList)
393    <$> walkDirAccumRel (Just excludeSymlinks) writer dir
394  where
395    excludeSymlinks tdir subdirs _ =
396      WalkExclude <$> filterM (isSymlink . (dir </>) . (tdir </>)) subdirs
397    writer tdir ds fs =
398      return
399        ( DList.fromList ((tdir </>) <$> ds),
400          DList.fromList ((tdir </>) <$> fs)
401        )
402
403-- | Copies a directory recursively. It /does not/ follow symbolic links and
404-- preserves permissions when possible. If the destination directory already
405-- exists, new files and sub-directories complement its structure, possibly
406-- overwriting old files if they happen to have the same name as the new
407-- ones.
408--
409-- __Note__: before version /1.3.0/, this function followed symlinks.
410--
411-- __Note__: before version /1.6.0/, the function created empty directories
412-- in the destination directory when the source directory contained
413-- directory symlinks. The symlinked directories were not recursively
414-- traversed. It also copied symlinked files creating normal regular files
415-- in the target directory as the result. This was fixed in the version
416-- /1.6.0/ so that the function now behaves much like the @cp@ utility, not
417-- traversing symlinked directories, but recreating symlinks in the target
418-- directory according to their targets in the source directory.
419copyDirRecur ::
420  (MonadIO m, MonadCatch m) =>
421  -- | Source
422  Path b0 Dir ->
423  -- | Destination
424  Path b1 Dir ->
425  m ()
426copyDirRecur = copyDirRecurGen True
427
428-- | The same as 'copyDirRecur', but it /does not/ preserve directory
429-- permissions. This may be useful, for example, if the directory you want
430-- to copy is “read-only”, but you want your copy to be editable.
431--
432-- @since 1.1.0
433--
434-- __Note__: before version /1.3.0/, this function followed symlinks.
435--
436-- __Note__: before version /1.6.0/, the function created empty directories
437-- in the destination directory when the source directory contained
438-- directory symlinks. The symlinked directories were not recursively
439-- traversed. It also copied symlinked files creating normal regular files
440-- in the target directory as the result. This was fixed in the version
441-- /1.6.0/ so that the function now behaves much like the @cp@ utility, not
442-- traversing symlinked directories, but recreating symlinks in the target
443-- directory according to their targets in the source directory.
444copyDirRecur' ::
445  (MonadIO m, MonadCatch m) =>
446  -- | Source
447  Path b0 Dir ->
448  -- | Destination
449  Path b1 Dir ->
450  m ()
451copyDirRecur' = copyDirRecurGen False
452
453-- | Generic version of 'copyDirRecur'. The first argument controls whether
454-- to preserve directory permissions or not. /Does not/ follow symbolic
455-- links. Internal function.
456copyDirRecurGen ::
457  MonadIO m =>
458  -- | Should we preserve directory permissions?
459  Bool ->
460  -- | Source
461  Path b0 Dir ->
462  -- | Destination
463  Path b1 Dir ->
464  m ()
465copyDirRecurGen preserveDirPermissions src dest = liftIO $ do
466  bsrc <- makeAbsolute src
467  bdest <- makeAbsolute dest
468  (dirs, files) <- listDirRecur bsrc
469  let swapParent ::
470        Path Abs Dir ->
471        Path Abs Dir ->
472        Path Abs t ->
473        IO (Path Abs t)
474      swapParent old new path =
475        (new </>)
476          <$> stripProperPrefix old path
477  ensureDir bdest
478  forM_ dirs $ \srcDir -> do
479    destDir <- swapParent bsrc bdest srcDir
480    dirIsSymlink <- isSymlink srcDir
481    if dirIsSymlink
482      then do
483        target <- getSymlinkTarget srcDir
484        D.createDirectoryLink target $
485          F.dropTrailingPathSeparator (toFilePath destDir)
486      else ensureDir destDir
487    when preserveDirPermissions $
488      ignoringIOErrors (copyPermissions srcDir destDir)
489  forM_ files $ \srcFile -> do
490    destFile <- swapParent bsrc bdest srcFile
491    fileIsSymlink <- isSymlink srcFile
492    if fileIsSymlink
493      then do
494        target <- getSymlinkTarget srcFile
495        D.createFileLink target (toFilePath destFile)
496      else copyFile srcFile destFile
497  when preserveDirPermissions $
498    ignoringIOErrors (copyPermissions bsrc bdest)
499
500----------------------------------------------------------------------------
501-- Walking directory trees
502
503-- Recursive directory walk functionality, with a flexible API and avoidance
504-- of loops. Following are some notes on the design.
505--
506-- Callback handler API:
507--
508-- The callback handler interface is designed to be highly flexible. There are
509-- two possible alternative ways to control the traversal:
510--
511-- - In the context of the parent dir, decide which subdirs to descend into.
512-- - In the context of the subdir, decide whether to traverse the subdir or not.
513--
514-- We choose the first approach here since it is more flexible and can
515-- achieve everything that the second one can. The additional benefit with
516-- this is that we can use the parent dir context efficiently instead of
517-- each child looking at the parent context independently.
518--
519-- To control which subdirs to descend we use a 'WalkExclude' API instead of
520-- a “WalkInclude” type of API so that the handlers cannot accidentally ask
521-- us to descend a dir which is not a subdir of the directory being walked.
522--
523-- Avoiding Traversal Loops:
524--
525-- There can be loops in the path being traversed due to subdirectory
526-- symlinks or filesystem corruptions can cause loops by creating directory
527-- hardlinks. Also, if the filesystem is changing while we are traversing
528-- then we might be going in loops due to the changes.
529--
530-- We record the path we are coming from to detect the loops. If we end up
531-- traversing the same directory again we are in a loop.
532
533-- | Action returned by the traversal handler function. The action controls
534-- how the traversal will proceed.
535--
536-- __Note__: in version /1.4.0/ the type was adjusted to have the @b@ type
537-- parameter.
538--
539-- @since 1.2.0
540data WalkAction b
541  = -- | Finish the entire walk altogether
542    WalkFinish
543  | -- | List of sub-directories to exclude from
544    -- descending
545    WalkExclude [Path b Dir]
546  deriving (Eq, Show)
547
548-- | Traverse a directory tree using depth first pre-order traversal,
549-- calling a handler function at each directory node traversed. The absolute
550-- paths of the parent directory, sub-directories and the files in the
551-- directory are provided as arguments to the handler.
552--
553-- The function is capable of detecting and avoiding traversal loops in the
554-- directory tree. Note that the traversal follows symlinks by default, an
555-- appropriate traversal handler can be used to avoid that when necessary.
556--
557-- @since 1.2.0
558walkDir ::
559  MonadIO m =>
560  -- | Handler (@dir -> subdirs -> files -> 'WalkAction'@)
561  (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) ->
562  -- | Directory where traversal begins
563  Path b Dir ->
564  m ()
565walkDir handler topdir =
566  void $
567    makeAbsolute topdir >>= walkAvoidLoop S.empty
568  where
569    walkAvoidLoop traversed curdir = do
570      mRes <- checkLoop traversed curdir
571      case mRes of
572        Nothing -> return $ Just ()
573        Just traversed' -> walktree traversed' curdir
574    walktree traversed curdir = do
575      (subdirs, files) <- listDir curdir
576      action <- handler curdir subdirs files
577      case action of
578        WalkFinish -> return Nothing
579        WalkExclude xdirs ->
580          case subdirs \\ xdirs of
581            [] -> return $ Just ()
582            ds ->
583              runMaybeT $
584                mapM_
585                  (MaybeT . walkAvoidLoop traversed)
586                  ds
587    checkLoop traversed dir = do
588      st <- liftIO $ P.getFileStatus (fromAbsDir dir)
589      let ufid = (P.deviceID st, P.fileID st)
590      return $
591        if S.member ufid traversed
592          then Nothing
593          else Just (S.insert ufid traversed)
594
595-- | The same as 'walkDir' but uses relative paths. The handler is given
596-- @dir@, directory relative to the directory where traversal begins.
597-- Sub-directories and files are relative to @dir@.
598--
599-- @since 1.4.2
600walkDirRel ::
601  MonadIO m =>
602  -- | Handler (@dir -> subdirs -> files -> 'WalkAction'@)
603  ( Path Rel Dir ->
604    [Path Rel Dir] ->
605    [Path Rel File] ->
606    m (WalkAction Rel)
607  ) ->
608  -- | Directory where traversal begins
609  Path b Dir ->
610  m ()
611walkDirRel handler topdir' = do
612  topdir <- makeAbsolute topdir'
613  let walkAvoidLoop traversed curdir = do
614        mRes <- checkLoop traversed (topdir </> curdir)
615        case mRes of
616          Nothing -> return $ Just ()
617          Just traversed' -> walktree traversed' curdir
618      walktree traversed curdir = do
619        (subdirs, files) <- listDirRel (topdir </> curdir)
620        action <- handler curdir subdirs files
621        case action of
622          WalkFinish -> return Nothing
623          WalkExclude xdirs ->
624            case subdirs \\ xdirs of
625              [] -> return $ Just ()
626              ds ->
627                runMaybeT $
628                  mapM_
629                    (MaybeT . walkAvoidLoop traversed)
630                    ((curdir </>) <$> ds)
631      checkLoop traversed dir = do
632        st <- liftIO $ P.getFileStatus (fromAbsDir dir)
633        let ufid = (P.deviceID st, P.fileID st)
634        return $
635          if S.member ufid traversed
636            then Nothing
637            else Just (S.insert ufid traversed)
638  void (walkAvoidLoop S.empty $(mkRelDir "."))
639
640-- | Similar to 'walkDir' but accepts a 'Monoid'-returning output writer as
641-- well. Values returned by the output writer invocations are accumulated
642-- and returned.
643--
644-- Both, the descend handler as well as the output writer can be used for
645-- side effects but keep in mind that the output writer runs before the
646-- descend handler.
647--
648-- @since 1.2.0
649walkDirAccum ::
650  (MonadIO m, Monoid o) =>
651  -- | Descend handler (@dir -> subdirs -> files -> 'WalkAction'@),
652  -- descend the whole tree if omitted
653  Maybe
654    (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) ->
655  -- | Output writer (@dir -> subdirs -> files -> o@)
656  (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m o) ->
657  -- | Directory where traversal begins
658  Path b Dir ->
659  -- | Accumulation of outputs generated by the output writer invocations
660  m o
661walkDirAccum = walkDirAccumWith walkDir
662
663-- | The same as 'walkDirAccum' but uses relative paths. The handler and
664-- writer are given @dir@, directory relative to the directory where
665-- traversal begins. Sub-directories and files are relative to @dir@.
666--
667-- @since 1.4.2
668walkDirAccumRel ::
669  (MonadIO m, Monoid o) =>
670  -- | Descend handler (@dir -> subdirs -> files -> 'WalkAction'@),
671  -- descend the whole tree if omitted
672  Maybe
673    (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)) ->
674  -- | Output writer (@dir -> subdirs -> files -> o@)
675  (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m o) ->
676  -- | Directory where traversal begins
677  Path b Dir ->
678  -- | Accumulation of outputs generated by the output writer invocations
679  m o
680walkDirAccumRel = walkDirAccumWith walkDirRel
681
682-- | Non-public helper function for defining accumulating walking actions.
683walkDirAccumWith ::
684  (MonadIO m, Monoid o) =>
685  -- | The walk function we use
686  ( ( Path a Dir ->
687      [Path a Dir] ->
688      [Path a File] ->
689      WriterT o m (WalkAction a)
690    ) ->
691    Path b Dir ->
692    WriterT o m ()
693  ) ->
694  -- | Descend handler (@dir -> subdirs -> files -> 'WalkAction'@),
695  -- descend the whole tree if omitted
696  Maybe (Path a Dir -> [Path a Dir] -> [Path a File] -> m (WalkAction a)) ->
697  -- | Output writer (@dir -> subdirs -> files -> o@)
698  (Path a Dir -> [Path a Dir] -> [Path a File] -> m o) ->
699  -- | Directory where traversal begins
700  Path b Dir ->
701  -- | Accumulation of outputs generated by the output writer invocations
702  m o
703walkDirAccumWith walkF dHandler writer topdir =
704  execWriterT (walkF handler topdir)
705  where
706    handler dir subdirs files = do
707      res <- lift $ writer dir subdirs files
708      tell res
709      case dHandler of
710        Just h -> lift $ h dir subdirs files
711        Nothing -> return (WalkExclude [])
712
713----------------------------------------------------------------------------
714-- Current working directory
715
716-- | Obtain the current working directory as an absolute path.
717--
718-- In a multithreaded program, the current working directory is a global
719-- state shared among all threads of the process. Therefore, when performing
720-- filesystem operations from multiple threads, it is highly recommended to
721-- use absolute rather than relative paths (see: 'makeAbsolute').
722--
723-- The operation may fail with:
724--
725-- * 'HardwareFault'
726-- A physical I\/O error has occurred.
727-- @[EIO]@
728--
729-- * 'isDoesNotExistError' or 'NoSuchThing'
730-- There is no path referring to the working directory.
731-- @[EPERM, ENOENT, ESTALE...]@
732--
733-- * 'isPermissionError' or 'PermissionDenied'
734-- The process has insufficient privileges to perform the operation.
735-- @[EACCES]@
736--
737-- * 'ResourceExhausted'
738-- Insufficient resources are available to perform the operation.
739--
740-- * 'UnsupportedOperation'
741-- The operating system has no notion of current working directory.
742getCurrentDir :: MonadIO m => m (Path Abs Dir)
743getCurrentDir = liftIO $ D.getCurrentDirectory >>= parseAbsDir
744
745-- | Change the working directory to the given path.
746--
747-- In a multithreaded program, the current working directory is a global
748-- state shared among all threads of the process. Therefore, when performing
749-- filesystem operations from multiple threads, it is highly recommended to
750-- use absolute rather than relative paths (see: 'makeAbsolute').
751--
752-- The operation may fail with:
753--
754-- * 'HardwareFault'
755-- A physical I\/O error has occurred.
756-- @[EIO]@
757--
758-- * 'InvalidArgument'
759-- The operand is not a valid directory name.
760-- @[ENAMETOOLONG, ELOOP]@
761--
762-- * 'isDoesNotExistError' or 'NoSuchThing'
763-- The directory does not exist.
764-- @[ENOENT, ENOTDIR]@
765--
766-- * 'isPermissionError' or 'PermissionDenied'
767-- The process has insufficient privileges to perform the operation.
768-- @[EACCES]@
769--
770-- * 'UnsupportedOperation'
771-- The operating system has no notion of current working directory, or the
772-- working directory cannot be dynamically changed.
773--
774-- * 'InappropriateType'
775-- The path refers to an existing non-directory object.
776-- @[ENOTDIR]@
777setCurrentDir :: MonadIO m => Path b Dir -> m ()
778setCurrentDir = liftD D.setCurrentDirectory
779
780-- | Run an 'IO' action with the given working directory and restore the
781-- original working directory afterwards, even if the given action fails due
782-- to an exception.
783--
784-- The operation may fail with the same exceptions as 'getCurrentDir' and
785-- 'setCurrentDir'.
786withCurrentDir ::
787  (MonadIO m, MonadMask m) =>
788  -- | Directory to execute in
789  Path b Dir ->
790  -- | Action to be executed
791  m a ->
792  m a
793withCurrentDir dir action =
794  bracket getCurrentDir setCurrentDir $ const (setCurrentDir dir >> action)
795
796----------------------------------------------------------------------------
797-- Pre-defined directories
798
799-- | Return the current user's home directory.
800--
801-- The directory returned is expected to be writable by the current user,
802-- but note that it isn't generally considered good practice to store
803-- application-specific data here; use 'getAppUserDataDir' instead.
804--
805-- On Unix, 'getHomeDir' returns the value of the @HOME@ environment
806-- variable. On Windows, the system is queried for a suitable path; a
807-- typical path might be @C:\/Users\//\<user\>/@.
808--
809-- The operation may fail with:
810--
811-- * 'UnsupportedOperation'
812-- The operating system has no notion of home directory.
813--
814-- * 'isDoesNotExistError'
815-- The home directory for the current user does not exist, or
816-- cannot be found.
817getHomeDir :: MonadIO m => m (Path Abs Dir)
818getHomeDir = liftIO D.getHomeDirectory >>= resolveDir'
819
820-- | Obtain the path to a special directory for storing user-specific
821-- application data (traditional Unix location).
822--
823-- The argument is usually the name of the application. Since it will be
824-- integrated into the path, it must consist of valid path characters.
825--
826-- * On Unix-like systems, the path is @~\/./\<app\>/@.
827-- * On Windows, the path is @%APPDATA%\//\<app\>/@
828--   (e.g. @C:\/Users\//\<user\>/\/AppData\/Roaming\//\<app\>/@)
829--
830-- Note: the directory may not actually exist, in which case you would need
831-- to create it. It is expected that the parent directory exists and is
832-- writable.
833--
834-- The operation may fail with:
835--
836-- * 'UnsupportedOperation'
837--   The operating system has no notion of application-specific data
838--   directory.
839--
840-- * 'isDoesNotExistError'
841--   The home directory for the current user does not exist, or cannot be
842--   found.
843getAppUserDataDir ::
844  MonadIO m =>
845  -- | Name of application (used in path construction)
846  String ->
847  m (Path Abs Dir)
848getAppUserDataDir = liftIO . (>>= parseAbsDir) . D.getAppUserDataDirectory
849
850-- | Return the current user's document directory.
851--
852-- The directory returned is expected to be writable by the current user,
853-- but note that it isn't generally considered good practice to store
854-- application-specific data here; use 'getAppUserDataDir' instead.
855--
856-- On Unix, 'getUserDocsDir' returns the value of the @HOME@ environment
857-- variable. On Windows, the system is queried for a suitable path; a
858-- typical path might be @C:\/Users\//\<user\>/\/Documents@.
859--
860-- The operation may fail with:
861--
862-- * 'UnsupportedOperation'
863-- The operating system has no notion of document directory.
864--
865-- * 'isDoesNotExistError'
866-- The document directory for the current user does not exist, or
867-- cannot be found.
868getUserDocsDir :: MonadIO m => m (Path Abs Dir)
869getUserDocsDir = liftIO $ D.getUserDocumentsDirectory >>= parseAbsDir
870
871-- | Return the current directory for temporary files.
872--
873-- On Unix, 'getTempDir' returns the value of the @TMPDIR@ environment
874-- variable or \"\/tmp\" if the variable isn\'t defined. On Windows, the
875-- function checks for the existence of environment variables in the
876-- following order and uses the first path found:
877--
878-- *
879-- TMP environment variable.
880--
881-- *
882-- TEMP environment variable.
883--
884-- *
885-- USERPROFILE environment variable.
886--
887-- *
888-- The Windows directory
889--
890-- The operation may fail with:
891--
892-- * 'UnsupportedOperation'
893-- The operating system has no notion of temporary directory.
894--
895-- The function doesn't verify whether the path exists.
896getTempDir :: MonadIO m => m (Path Abs Dir)
897getTempDir = liftIO D.getTemporaryDirectory >>= resolveDir'
898
899-- | Obtain the paths to special directories for storing user-specific
900-- application data, configuration, and cache files, conforming to the
901-- <http://standards.freedesktop.org/basedir-spec/basedir-spec-latest.html XDG Base Directory Specification>.
902-- Compared with 'getAppUserDataDir', this function provides a more
903-- fine-grained hierarchy as well as greater flexibility for the user.
904--
905-- It also works on Windows, although in that case 'D.XdgData' and
906-- 'D.XdgConfig' will map to the same directory.
907--
908-- Note: The directory may not actually exist, in which case you would need
909-- to create it with file mode @700@ (i.e. only accessible by the owner).
910--
911-- Note also: this is a piece of conditional API, only available if
912-- @directory-1.2.3.0@ or later is used.
913--
914-- @since 1.2.1
915getXdgDir ::
916  MonadIO m =>
917  -- | Which special directory
918  D.XdgDirectory ->
919  -- | A relative path that is appended to the path; if 'Nothing', the
920  -- base path is returned
921  Maybe (Path Rel Dir) ->
922  m (Path Abs Dir)
923getXdgDir xdgDir suffix =
924  liftIO $ (D.getXdgDirectory xdgDir $ maybe "" toFilePath suffix) >>= parseAbsDir
925
926-- | Similar to 'getXdgDir' but retrieves the entire list of XDG
927-- directories.
928--
929-- On Windows, 'D.XdgDataDirs' and 'D.XdgConfigDirs' usually map to the same
930-- list of directories unless overridden.
931--
932-- Refer to the docs of 'D.XdgDirectoryList' for more details.
933--
934-- @since 1.5.0
935getXdgDirList ::
936  MonadIO m =>
937  -- | Which special directory list
938  D.XdgDirectoryList ->
939  m [Path Abs Dir]
940getXdgDirList xdgDirList =
941  liftIO (D.getXdgDirectoryList xdgDirList >>= mapM parseAbsDir)
942
943----------------------------------------------------------------------------
944-- Path transformation
945
946-- | Class of things ('Path's) that can be canonicalized, made absolute, and
947-- made relative to a some base directory.
948class AnyPath path where
949  -- | Type of absolute version of the given @path@.
950  type AbsPath path :: Type
951
952  -- | Type of relative version of the given @path@.
953  type RelPath path :: Type
954
955  -- | Make a path absolute and remove as many indirections from it as
956  -- possible. Indirections include the two special directories @.@ and
957  -- @..@, as well as any symbolic links. The input path need not point to
958  -- an existing file or directory.
959  --
960  -- __Note__: if you require only an absolute path, use 'makeAbsolute'
961  -- instead. Most programs need not care about whether a path contains
962  -- symbolic links.
963  --
964  -- Due to the fact that symbolic links are dependent on the state of the
965  -- existing filesystem, the function can only make a conservative,
966  -- best-effort attempt. Nevertheless, if the input path points to an
967  -- existing file or directory, then the output path shall also point to
968  -- the same file or directory.
969  --
970  -- Formally, symbolic links are removed from the longest prefix of the
971  -- path that still points to an existing file. The function is not atomic,
972  -- therefore concurrent changes in the filesystem may lead to incorrect
973  -- results.
974  --
975  -- (Despite the name, the function does not guarantee canonicity of the
976  -- returned path due to the presence of hard links, mount points, etc.)
977  --
978  -- /Known bug(s)/: on Windows, the function does not resolve symbolic
979  -- links.
980  --
981  -- Please note that before version 1.2.3.0 of the @directory@ package,
982  -- this function had unpredictable behavior on non-existent paths.
983  canonicalizePath ::
984    MonadIO m =>
985    path ->
986    m (AbsPath path)
987
988  -- | Make a path absolute by prepending the current directory (if it isn't
989  -- already absolute) and applying 'F.normalise' to the result.
990  --
991  -- If the path is already absolute, the operation never fails. Otherwise,
992  -- the operation may fail with the same exceptions as 'getCurrentDir'.
993  makeAbsolute ::
994    MonadIO m =>
995    path ->
996    m (AbsPath path)
997
998  -- | Make a path relative to a given directory.
999  --
1000  -- @since 0.3.0
1001  makeRelative ::
1002    MonadThrow m =>
1003    -- | Base directory
1004    Path Abs Dir ->
1005    -- | Path that will be made relative to base directory
1006    path ->
1007    m (RelPath path)
1008
1009  -- | Make a path relative to current working directory.
1010  --
1011  -- @since 0.3.0
1012  makeRelativeToCurrentDir ::
1013    MonadIO m =>
1014    path ->
1015    m (RelPath path)
1016
1017instance AnyPath (Path b File) where
1018  type AbsPath (Path b File) = Path Abs File
1019  type RelPath (Path b File) = Path Rel File
1020
1021  canonicalizePath = liftD $ D.canonicalizePath >=> parseAbsFile
1022  makeAbsolute = liftD $ D.makeAbsolute >=> parseAbsFile
1023  makeRelative b p = parseRelFile (F.makeRelative (toFilePath b) (toFilePath p))
1024  makeRelativeToCurrentDir p = liftIO $ getCurrentDir >>= flip makeRelative p
1025
1026instance AnyPath (Path b Dir) where
1027  type AbsPath (Path b Dir) = Path Abs Dir
1028  type RelPath (Path b Dir) = Path Rel Dir
1029
1030  canonicalizePath = liftD D.canonicalizePath >=> liftIO . parseAbsDir
1031  makeAbsolute = liftD D.makeAbsolute >=> liftIO . parseAbsDir
1032  makeRelative b p = parseRelDir (F.makeRelative (toFilePath b) (toFilePath p))
1033  makeRelativeToCurrentDir p = liftIO $ getCurrentDir >>= flip makeRelative p
1034
1035-- | Append stringly-typed path to an absolute path and then canonicalize
1036-- it.
1037--
1038-- @since 0.3.0
1039resolveFile ::
1040  MonadIO m =>
1041  -- | Base directory
1042  Path Abs Dir ->
1043  -- | Path to resolve
1044  FilePath ->
1045  m (Path Abs File)
1046resolveFile b p = liftIO $ D.canonicalizePath (toFilePath b F.</> p) >>= parseAbsFile
1047
1048-- | The same as 'resolveFile', but uses current working directory.
1049--
1050-- @since 0.3.0
1051resolveFile' ::
1052  MonadIO m =>
1053  -- | Path to resolve
1054  FilePath ->
1055  m (Path Abs File)
1056resolveFile' p = getCurrentDir >>= flip resolveFile p
1057
1058-- | The same as 'resolveFile', but for directories.
1059--
1060-- @since 0.3.0
1061resolveDir ::
1062  MonadIO m =>
1063  -- | Base directory
1064  Path Abs Dir ->
1065  -- | Path to resolve
1066  FilePath ->
1067  m (Path Abs Dir)
1068resolveDir b p = liftIO $ D.canonicalizePath (toFilePath b F.</> p) >>= parseAbsDir
1069
1070-- | The same as 'resolveDir', but uses current working directory.
1071--
1072-- @since 0.3.0
1073resolveDir' ::
1074  MonadIO m =>
1075  -- | Path to resolve
1076  FilePath ->
1077  m (Path Abs Dir)
1078resolveDir' p = getCurrentDir >>= flip resolveDir p
1079
1080----------------------------------------------------------------------------
1081-- Actions on files
1082
1083-- | @'removeFile' file@ removes the directory entry for an existing file
1084-- @file@, where @file@ is not itself a directory. The implementation may
1085-- specify additional constraints which must be satisfied before a file can
1086-- be removed (e.g. the file may not be in use by other processes).
1087--
1088-- The operation may fail with:
1089--
1090-- * 'HardwareFault'
1091-- A physical I\/O error has occurred.
1092-- @[EIO]@
1093--
1094-- * 'InvalidArgument'
1095-- The operand is not a valid file name.
1096-- @[ENAMETOOLONG, ELOOP]@
1097--
1098-- * 'isDoesNotExistError' \/ 'NoSuchThing'
1099-- The file does not exist.
1100-- @[ENOENT, ENOTDIR]@
1101--
1102-- * 'isPermissionError' \/ 'PermissionDenied'
1103-- The process has insufficient privileges to perform the operation.
1104-- @[EROFS, EACCES, EPERM]@
1105--
1106-- * 'UnsatisfiedConstraints'
1107-- Implementation-dependent constraints are not satisfied.
1108-- @[EBUSY]@
1109--
1110-- * 'InappropriateType'
1111-- The operand refers to an existing directory.
1112-- @[EPERM, EINVAL]@
1113removeFile :: MonadIO m => Path b File -> m ()
1114removeFile = liftD D.removeFile
1115
1116-- | @'renameFile' old new@ changes the name of an existing file system
1117-- object from /old/ to /new/. If the /new/ object already exists, it is
1118-- atomically replaced by the /old/ object. Neither path may refer to an
1119-- existing directory. A conformant implementation need not support renaming
1120-- files in all situations (e.g. renaming across different physical
1121-- devices), but the constraints must be documented.
1122--
1123-- The operation may fail with:
1124--
1125-- * 'HardwareFault'
1126-- A physical I\/O error has occurred.
1127-- @[EIO]@
1128--
1129-- * 'InvalidArgument'
1130-- Either operand is not a valid file name.
1131-- @[ENAMETOOLONG, ELOOP]@
1132--
1133-- * 'isDoesNotExistError' \/ 'NoSuchThing'
1134-- The original file does not exist, or there is no path to the target.
1135-- @[ENOENT, ENOTDIR]@
1136--
1137-- * 'isPermissionError' \/ 'PermissionDenied'
1138-- The process has insufficient privileges to perform the operation.
1139-- @[EROFS, EACCES, EPERM]@
1140--
1141-- * 'ResourceExhausted'
1142-- Insufficient resources are available to perform the operation.
1143-- @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
1144--
1145-- * 'UnsatisfiedConstraints'
1146-- Implementation-dependent constraints are not satisfied.
1147-- @[EBUSY]@
1148--
1149-- * 'UnsupportedOperation'
1150-- The implementation does not support renaming in this situation.
1151-- @[EXDEV]@
1152--
1153-- * 'InappropriateType'
1154-- Either path refers to an existing directory.
1155-- @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
1156renameFile ::
1157  MonadIO m =>
1158  -- | Original location
1159  Path b0 File ->
1160  -- | New location
1161  Path b1 File ->
1162  m ()
1163renameFile = liftD2 D.renameFile
1164
1165-- | @'copyFile' old new@ copies the existing file from @old@ to @new@. If
1166-- the @new@ file already exists, it is atomically replaced by the @old@
1167-- file. Neither path may refer to an existing directory. The permissions of
1168-- @old@ are copied to @new@, if possible.
1169copyFile ::
1170  MonadIO m =>
1171  -- | Original location
1172  Path b0 File ->
1173  -- | Where to put copy
1174  Path b1 File ->
1175  m ()
1176copyFile = liftD2 D.copyFile
1177
1178-- | Given an executable file name, search for such file in the directories
1179-- listed in system @PATH@. The returned value is the path to the found
1180-- executable or 'Nothing' if an executable with the given name was not
1181-- found. For example ('findExecutable' \"ghc\") gives you the path to GHC.
1182--
1183-- The path returned by 'findExecutable' corresponds to the program that
1184-- would be executed by 'System.Process.createProcess' when passed the same
1185-- string (as a RawCommand, not a ShellCommand).
1186--
1187-- On Windows, 'findExecutable' calls the Win32 function 'SearchPath', which
1188-- may search other places before checking the directories in @PATH@. Where
1189-- it actually searches depends on registry settings, but notably includes
1190-- the directory containing the current executable. See
1191-- <http://msdn.microsoft.com/en-us/library/aa365527.aspx> for more details.
1192findExecutable ::
1193  MonadIO m =>
1194  -- | Executable file name
1195  Path Rel File ->
1196  -- | Path to found executable
1197  m (Maybe (Path Abs File))
1198findExecutable = fmap (>>= parseAbsFile) . liftD D.findExecutable
1199
1200-- | Search through the given set of directories for the given file.
1201findFile ::
1202  MonadIO m =>
1203  -- | Set of directories to search in
1204  [Path b Dir] ->
1205  -- | Filename of interest
1206  Path Rel File ->
1207  -- | Absolute path to file (if found)
1208  m (Maybe (Path Abs File))
1209findFile [] _ = return Nothing
1210findFile (d : ds) file = do
1211  bfile <- (</> file) <$> makeAbsolute d
1212  exist <- doesFileExist bfile
1213  if exist
1214    then return (Just bfile)
1215    else findFile ds file
1216
1217-- | Search through the given set of directories for the given file and
1218-- return a list of paths where the given file exists.
1219findFiles ::
1220  MonadIO m =>
1221  -- | Set of directories to search in
1222  [Path b Dir] ->
1223  -- | Filename of interest
1224  Path Rel File ->
1225  -- | Absolute paths to all found files
1226  m [Path Abs File]
1227findFiles = findFilesWith (const (return True))
1228
1229-- | Search through the given set of directories for the given file and with
1230-- the given property (usually permissions) and return a list of paths where
1231-- the given file exists and has the property.
1232findFilesWith ::
1233  MonadIO m =>
1234  -- | How to test the files
1235  (Path Abs File -> m Bool) ->
1236  -- | Set of directories to search in
1237  [Path b Dir] ->
1238  -- | Filename of interest
1239  Path Rel File ->
1240  -- | Absolute paths to all found files
1241  m [Path Abs File]
1242findFilesWith _ [] _ = return []
1243findFilesWith f (d : ds) file = do
1244  bfile <- (</> file) <$> makeAbsolute d
1245  exist <- doesFileExist bfile
1246  b <- if exist then f bfile else return False
1247  if b
1248    then (bfile :) <$> findFilesWith f ds file
1249    else findFilesWith f ds file
1250
1251----------------------------------------------------------------------------
1252-- Symbolic links
1253
1254-- | Create a /file/ symbolic link. The target path can be either absolute
1255-- or relative and need not refer to an existing file. The order of
1256-- arguments follows the POSIX convention.
1257--
1258-- To remove an existing file symbolic link, use 'removeFile'.
1259--
1260-- Although the distinction between /file/ symbolic links and /directory/
1261-- symbolic links does not exist on POSIX systems, on Windows this is an
1262-- intrinsic property of every symbolic link and cannot be changed without
1263-- recreating the link. A file symbolic link that actually points to a
1264-- directory will fail to dereference and vice versa. Moreover, creating
1265-- symbolic links on Windows may require privileges unavailable to users
1266-- outside the Administrators group. Portable programs that use symbolic
1267-- links should take both into consideration.
1268--
1269-- On Windows, the function is implemented using @CreateSymbolicLink@. Since
1270-- 1.3.3.0, the @SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE@ flag is
1271-- included if supported by the operating system. On POSIX, the function
1272-- uses @symlink@ and is therefore atomic.
1273--
1274-- Windows-specific errors: This operation may fail with
1275-- 'System.IO.Error.permissionErrorType' if the user lacks the privileges to
1276-- create symbolic links. It may also fail with
1277-- 'System.IO.Error.illegalOperationErrorType' if the file system does not
1278-- support symbolic links.
1279--
1280-- @since 1.5.0
1281createFileLink ::
1282  MonadIO m =>
1283  -- | Path to the target file
1284  Path b0 File ->
1285  -- | Path to the link to be created
1286  Path b1 File ->
1287  m ()
1288createFileLink = liftD2 D.createFileLink
1289
1290-- | Create a /directory/ symbolic link. The target path can be either
1291-- absolute or relative and need not refer to an existing directory. The
1292-- order of arguments follows the POSIX convention.
1293--
1294-- To remove an existing directory symbolic link, use 'removeDirLink'.
1295--
1296-- Although the distinction between /file/ symbolic links and /directory/
1297-- symbolic links does not exist on POSIX systems, on Windows this is an
1298-- intrinsic property of every symbolic link and cannot be changed without
1299-- recreating the link. A file symbolic link that actually points to a
1300-- directory will fail to dereference and vice versa. Moreover, creating
1301-- symbolic links on Windows may require privileges unavailable to users
1302-- outside the Administrators group. Portable programs that use symbolic
1303-- links should take both into consideration.
1304--
1305-- On Windows, the function is implemented using @CreateSymbolicLink@ with
1306-- @SYMBOLIC_LINK_FLAG_DIRECTORY@. Since 1.3.3.0, the
1307-- @SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE@ flag is also included if
1308-- supported by the operating system. On POSIX, this is an alias for
1309-- 'createFileLink' and is therefore atomic.
1310--
1311-- Windows-specific errors: This operation may fail with
1312-- 'System.IO.Error.permissionErrorType' if the user lacks the privileges to
1313-- create symbolic links. It may also fail with
1314-- 'System.IO.Error.illegalOperationErrorType' if the file system does not
1315-- support symbolic links.
1316--
1317-- @since 1.5.0
1318createDirLink ::
1319  MonadIO m =>
1320  -- | Path to the target directory
1321  Path b0 Dir ->
1322  -- | Path to the link to be created
1323  Path b1 Dir ->
1324  m ()
1325createDirLink target' dest' = do
1326  let target = toFilePath target'
1327      dest = F.dropTrailingPathSeparator (toFilePath dest')
1328  liftIO $ D.createDirectoryLink target dest
1329
1330-- | Remove an existing /directory/ symbolic link.
1331--
1332-- On Windows, this is an alias for 'removeDir'. On POSIX systems, this is
1333-- an alias for 'removeFile'.
1334--
1335-- See also: 'removeFile', which can remove an existing /file/ symbolic link.
1336--
1337-- @since 1.5.0
1338removeDirLink ::
1339  MonadIO m =>
1340  -- | Path to the link to be removed
1341  Path b Dir ->
1342  m ()
1343removeDirLink = liftD D.removeDirectoryLink
1344
1345-- | Retrieve the target path of either a file or directory symbolic link.
1346-- The returned path may not exist, and may not even be a valid path.
1347--
1348-- On Windows systems, this calls @DeviceIoControl@ with
1349-- @FSCTL_GET_REPARSE_POINT@. In addition to symbolic links, the function
1350-- also works on junction points. On POSIX systems, this calls @readlink@.
1351--
1352-- Windows-specific errors: This operation may fail with
1353-- 'System.IO.Error.illegalOperationErrorType' if the file system does not
1354-- support symbolic links.
1355--
1356-- @since 1.5.0
1357getSymlinkTarget ::
1358  MonadIO m =>
1359  -- | Symlink path
1360  Path b t ->
1361  m FilePath
1362getSymlinkTarget = liftD (D.getSymbolicLinkTarget . F.dropTrailingPathSeparator)
1363
1364-- | Check whether the path refers to a symbolic link.  An exception is thrown
1365-- if the path does not exist or is inaccessible.
1366--
1367-- On Windows, this checks for @FILE_ATTRIBUTE_REPARSE_POINT@.  In addition to
1368-- symbolic links, the function also returns true on junction points.  On
1369-- POSIX systems, this checks for @S_IFLNK@.
1370--
1371-- @since 1.5.0
1372
1373-- | Check if the given path is a symbolic link.
1374--
1375-- @since 1.3.0
1376isSymlink :: MonadIO m => Path b t -> m Bool
1377isSymlink = liftD (D.pathIsSymbolicLink . F.dropTrailingPathSeparator)
1378
1379----------------------------------------------------------------------------
1380-- Temporary files and directories
1381
1382-- | Use a temporary file that doesn't already exist.
1383--
1384-- Creates a new temporary file inside the given directory, making use of
1385-- the template. The temporary file is deleted after use.
1386--
1387-- @since 0.2.0
1388withTempFile ::
1389  (MonadIO m, MonadMask m) =>
1390  -- | Directory to create the file in
1391  Path b Dir ->
1392  -- | File name template, see 'openTempFile'
1393  String ->
1394  -- | Callback that can use the file
1395  (Path Abs File -> Handle -> m a) ->
1396  m a
1397withTempFile path t action = do
1398  apath <- makeAbsolute path
1399  T.withTempFile (toFilePath apath) t $ \file h ->
1400    parseAbsFile file >>= flip action h
1401
1402-- | Create and use a temporary directory.
1403--
1404-- Creates a new temporary directory inside the given directory, making use
1405-- of the template. The temporary directory is deleted after use.
1406--
1407-- @since 0.2.0
1408withTempDir ::
1409  (MonadIO m, MonadMask m) =>
1410  -- | Directory to create the file in
1411  Path b Dir ->
1412  -- | Directory name template, see 'openTempFile'
1413  String ->
1414  -- | Callback that can use the directory
1415  (Path Abs Dir -> m a) ->
1416  m a
1417withTempDir path t action = do
1418  apath <- makeAbsolute path
1419  T.withTempDirectory (toFilePath apath) t (parseAbsDir >=> action)
1420
1421-- | Create and use a temporary file in the system standard temporary
1422-- directory.
1423--
1424-- Behaves exactly the same as 'withTempFile', except that the parent
1425-- temporary directory will be that returned by 'getTempDir'.
1426--
1427-- @since 0.2.0
1428withSystemTempFile ::
1429  (MonadIO m, MonadMask m) =>
1430  -- | File name template, see 'openTempFile'
1431  String ->
1432  -- | Callback that can use the file
1433  (Path Abs File -> Handle -> m a) ->
1434  m a
1435withSystemTempFile t action =
1436  getTempDir >>= \path ->
1437    withTempFile path t action
1438
1439-- | Create and use a temporary directory in the system standard temporary
1440-- directory.
1441--
1442-- Behaves exactly the same as 'withTempDir', except that the parent
1443-- temporary directory will be that returned by 'getTempDir'.
1444--
1445-- @since 0.2.0
1446withSystemTempDir ::
1447  (MonadIO m, MonadMask m) =>
1448  -- | Directory name template, see 'openTempFile'
1449  String ->
1450  -- | Callback that can use the directory
1451  (Path Abs Dir -> m a) ->
1452  m a
1453withSystemTempDir t action =
1454  getTempDir >>= \path ->
1455    withTempDir path t action
1456
1457-- | The function creates a temporary file in @rw@ mode. The created file
1458-- isn't deleted automatically, so you need to delete it manually.
1459--
1460-- The file is created with permissions such that only the current user can
1461-- read\/write it.
1462--
1463-- With some exceptions (see below), the file will be created securely in
1464-- the sense that an attacker should not be able to cause openTempFile to
1465-- overwrite another file on the filesystem using your credentials, by
1466-- putting symbolic links (on Unix) in the place where the temporary file is
1467-- to be created. On Unix the @O_CREAT@ and @O_EXCL@ flags are used to
1468-- prevent this attack, but note that @O_EXCL@ is sometimes not supported on
1469-- NFS filesystems, so if you rely on this behaviour it is best to use local
1470-- filesystems only.
1471--
1472-- @since 0.2.0
1473openTempFile ::
1474  MonadIO m =>
1475  -- | Directory to create file in
1476  Path b Dir ->
1477  -- | File name template; if the template is "foo.ext" then the created
1478  -- file will be @\"fooXXX.ext\"@ where @XXX@ is some random number
1479  String ->
1480  -- | Name of created file and its 'Handle'
1481  m (Path Abs File, Handle)
1482openTempFile path t = liftIO $ do
1483  apath <- makeAbsolute path
1484  (tfile, h) <- liftD2' T.openTempFile apath t
1485  (,h) <$> parseAbsFile tfile
1486
1487-- | Like 'openTempFile', but opens the file in binary mode. On Windows,
1488-- reading a file in text mode (which is the default) will translate @CRLF@
1489-- to @LF@, and writing will translate @LF@ to @CRLF@. This is usually what
1490-- you want with text files. With binary files this is undesirable; also, as
1491-- usual under Microsoft operating systems, text mode treats control-Z as
1492-- EOF. Binary mode turns off all special treatment of end-of-line and
1493-- end-of-file characters.
1494--
1495-- @since 0.2.0
1496openBinaryTempFile ::
1497  MonadIO m =>
1498  -- | Directory to create file in
1499  Path b Dir ->
1500  -- | File name template, see 'openTempFile'
1501  String ->
1502  -- | Name of created file and its 'Handle'
1503  m (Path Abs File, Handle)
1504openBinaryTempFile path t = liftIO $ do
1505  apath <- makeAbsolute path
1506  (tfile, h) <- liftD2' T.openBinaryTempFile apath t
1507  (,h) <$> parseAbsFile tfile
1508
1509-- | Create a temporary directory. The created directory isn't deleted
1510-- automatically, so you need to delete it manually.
1511--
1512-- The directory is created with permissions such that only the current user
1513-- can read\/write it.
1514--
1515-- @since 0.2.0
1516createTempDir ::
1517  MonadIO m =>
1518  -- | Directory to create file in
1519  Path b Dir ->
1520  -- | Directory name template, see 'openTempFile'
1521  String ->
1522  -- | Name of created temporary directory
1523  m (Path Abs Dir)
1524createTempDir path t =
1525  liftIO $
1526    makeAbsolute path >>= \apath ->
1527      liftD2' T.createTempDirectory apath t >>= parseAbsDir
1528
1529----------------------------------------------------------------------------
1530-- Existence tests
1531
1532-- | The operation 'doesFileExist' returns 'True' if the argument file
1533-- exists and is not a directory, and 'False' otherwise.
1534doesFileExist :: MonadIO m => Path b File -> m Bool
1535doesFileExist = liftD D.doesFileExist
1536
1537-- | The operation 'doesDirExist' returns 'True' if the argument file exists
1538-- and is either a directory or a symbolic link to a directory, and 'False'
1539-- otherwise.
1540doesDirExist :: MonadIO m => Path b Dir -> m Bool
1541doesDirExist = liftD D.doesDirectoryExist
1542
1543-- | Check if there is a file or directory on specified path.
1544isLocationOccupied :: MonadIO m => Path b t -> m Bool
1545isLocationOccupied path = do
1546  let fp = toFilePath path
1547  file <- liftIO (D.doesFileExist fp)
1548  dir <- liftIO (D.doesDirectoryExist fp)
1549  return (file || dir)
1550
1551-- | If argument of the function throws a
1552-- 'System.IO.Error.doesNotExistErrorType', 'Nothing' is returned (other
1553-- exceptions propagate). Otherwise the result is returned inside a 'Just'.
1554--
1555-- @since 0.3.0
1556forgivingAbsence :: (MonadIO m, MonadCatch m) => m a -> m (Maybe a)
1557forgivingAbsence f =
1558  catchIf
1559    isDoesNotExistError
1560    (Just <$> f)
1561    (const $ return Nothing)
1562
1563-- | The same as 'forgivingAbsence', but ignores result.
1564--
1565-- @since 0.3.1
1566ignoringAbsence :: (MonadIO m, MonadCatch m) => m a -> m ()
1567ignoringAbsence = void . forgivingAbsence
1568
1569----------------------------------------------------------------------------
1570-- Permissions
1571
1572-- | The 'getPermissions' operation returns the permissions for the file or
1573-- directory.
1574--
1575-- The operation may fail with:
1576--
1577-- * 'isPermissionError' if the user is not permitted to access
1578--   the permissions; or
1579--
1580-- * 'isDoesNotExistError' if the file or directory does not exist.
1581getPermissions :: MonadIO m => Path b t -> m D.Permissions
1582getPermissions = liftD D.getPermissions
1583
1584-- | The 'setPermissions' operation sets the permissions for the file or
1585-- directory.
1586--
1587-- The operation may fail with:
1588--
1589-- * 'isPermissionError' if the user is not permitted to set
1590--   the permissions; or
1591--
1592-- * 'isDoesNotExistError' if the file or directory does not exist.
1593setPermissions :: MonadIO m => Path b t -> D.Permissions -> m ()
1594setPermissions = liftD2' D.setPermissions
1595
1596-- | Set permissions for the object found on second given path so they match
1597-- permissions of the object on the first path.
1598copyPermissions ::
1599  MonadIO m =>
1600  -- | From where to copy
1601  Path b0 t0 ->
1602  -- | What to modify
1603  Path b1 t1 ->
1604  m ()
1605copyPermissions = liftD2 D.copyPermissions
1606
1607----------------------------------------------------------------------------
1608-- Timestamps
1609
1610-- | Obtain the time at which the file or directory was last accessed.
1611--
1612-- The operation may fail with:
1613--
1614-- * 'isPermissionError' if the user is not permitted to read
1615--   the access time; or
1616--
1617-- * 'isDoesNotExistError' if the file or directory does not exist.
1618--
1619-- Caveat for POSIX systems: This function returns a timestamp with
1620-- sub-second resolution only if this package is compiled against
1621-- @unix-2.6.0.0@ or later and the underlying filesystem supports them.
1622--
1623-- Note: this is a piece of conditional API, only available if
1624-- @directory-1.2.3.0@ or later is used.
1625getAccessTime :: MonadIO m => Path b t -> m UTCTime
1626getAccessTime = liftD D.getAccessTime
1627
1628-- | Change the time at which the file or directory was last accessed.
1629--
1630-- The operation may fail with:
1631--
1632-- * 'isPermissionError' if the user is not permitted to alter the
1633--   access time; or
1634--
1635-- * 'isDoesNotExistError' if the file or directory does not exist.
1636--
1637-- Some caveats for POSIX systems:
1638--
1639-- * Not all systems support @utimensat@, in which case the function can
1640--   only emulate the behavior by reading the modification time and then
1641--   setting both the access and modification times together. On systems
1642--   where @utimensat@ is supported, the access time is set atomically with
1643--   nanosecond precision.
1644--
1645-- * If compiled against a version of @unix@ prior to @2.7.0.0@, the
1646--   function would not be able to set timestamps with sub-second
1647--   resolution. In this case, there would also be loss of precision in the
1648--   modification time.
1649--
1650-- Note: this is a piece of conditional API, only available if
1651-- @directory-1.2.3.0@ or later is used.
1652setAccessTime :: MonadIO m => Path b t -> UTCTime -> m ()
1653setAccessTime = liftD2' D.setAccessTime
1654
1655-- | Change the time at which the file or directory was last modified.
1656--
1657-- The operation may fail with:
1658--
1659-- * 'isPermissionError' if the user is not permitted to alter the
1660--   modification time; or
1661--
1662-- * 'isDoesNotExistError' if the file or directory does not exist.
1663--
1664-- Some caveats for POSIX systems:
1665--
1666-- * Not all systems support @utimensat@, in which case the function can
1667--   only emulate the behavior by reading the access time and then setting
1668--   both the access and modification times together. On systems where
1669--   @utimensat@ is supported, the modification time is set atomically with
1670--   nanosecond precision.
1671--
1672-- * If compiled against a version of @unix@ prior to @2.7.0.0@, the
1673--   function would not be able to set timestamps with sub-second
1674--   resolution. In this case, there would also be loss of precision in the
1675--   access time.
1676--
1677-- Note: this is a piece of conditional API, only available if
1678-- @directory-1.2.3.0@ or later is used.
1679setModificationTime :: MonadIO m => Path b t -> UTCTime -> m ()
1680setModificationTime = liftD2' D.setModificationTime
1681
1682-- | Obtain the time at which the file or directory was last modified.
1683--
1684-- The operation may fail with:
1685--
1686-- * 'isPermissionError' if the user is not permitted to read
1687--   the modification time; or
1688--
1689-- * 'isDoesNotExistError' if the file or directory does not exist.
1690--
1691-- Caveat for POSIX systems: This function returns a timestamp with
1692-- sub-second resolution only if this package is compiled against
1693-- @unix-2.6.0.0@ or later and the underlying filesystem supports them.
1694getModificationTime :: MonadIO m => Path b t -> m UTCTime
1695getModificationTime = liftD D.getModificationTime
1696
1697----------------------------------------------------------------------------
1698-- Helpers
1699
1700-- | Lift action in 'IO' that takes 'FilePath' into action in slightly more
1701-- abstract monad that takes 'Path'.
1702liftD ::
1703  MonadIO m =>
1704  -- | Original action
1705  (FilePath -> IO a) ->
1706  -- | 'Path' argument
1707  Path b t ->
1708  -- | Lifted action
1709  m a
1710liftD m = liftIO . m . toFilePath
1711{-# INLINE liftD #-}
1712
1713-- | Similar to 'liftD' for functions with arity 2.
1714liftD2 ::
1715  MonadIO m =>
1716  -- | Original action
1717  (FilePath -> FilePath -> IO a) ->
1718  -- | First 'Path' argument
1719  Path b0 t0 ->
1720  -- | Second 'Path' argument
1721  Path b1 t1 ->
1722  m a
1723liftD2 m a b = liftIO $ m (toFilePath a) (toFilePath b)
1724{-# INLINE liftD2 #-}
1725
1726-- | Similar to 'liftD2', but allows to pass second argument of arbitrary
1727-- type.
1728liftD2' ::
1729  MonadIO m =>
1730  -- | Original action
1731  (FilePath -> v -> IO a) ->
1732  -- | First 'Path' argument
1733  Path b t ->
1734  -- | Second argument
1735  v ->
1736  m a
1737liftD2' m a v = liftIO $ m (toFilePath a) v
1738{-# INLINE liftD2' #-}
1739
1740-- | Perform an action ignoring IO exceptions it may throw.
1741ignoringIOErrors :: IO () -> IO ()
1742ignoringIOErrors ioe = ioe `catch` handler
1743  where
1744    handler :: Monad m => IOError -> m ()
1745    handler = const (return ())
1746