1{-# LANGUAGE CPP #-}
2
3#if !MIN_VERSION_base(4, 8, 0)
4-- In base-4.8.0 the Foreign module became Safe
5{-# LANGUAGE Trustworthy #-}
6#endif
7
8-----------------------------------------------------------------------------
9-- |
10-- Module      :  System.Directory
11-- Copyright   :  (c) The University of Glasgow 2001
12-- License     :  BSD-style (see the file libraries/base/LICENSE)
13--
14-- Maintainer  :  libraries@haskell.org
15-- Stability   :  stable
16-- Portability :  portable
17--
18-- System-independent interface to directory manipulation.
19--
20-----------------------------------------------------------------------------
21
22module System.Directory
23   (
24    -- $intro
25
26    -- * Actions on directories
27      createDirectory
28    , createDirectoryIfMissing
29    , removeDirectory
30    , removeDirectoryRecursive
31    , removePathForcibly
32    , renameDirectory
33    , listDirectory
34    , getDirectoryContents
35    -- ** Current working directory
36    , getCurrentDirectory
37    , setCurrentDirectory
38    , withCurrentDirectory
39
40    -- * Pre-defined directories
41    , getHomeDirectory
42    , XdgDirectory(..)
43    , getXdgDirectory
44    , XdgDirectoryList(..)
45    , getXdgDirectoryList
46    , getAppUserDataDirectory
47    , getUserDocumentsDirectory
48    , getTemporaryDirectory
49
50    -- * Actions on files
51    , removeFile
52    , renameFile
53    , renamePath
54    , copyFile
55    , copyFileWithMetadata
56    , getFileSize
57
58    , canonicalizePath
59    , makeAbsolute
60    , makeRelativeToCurrentDirectory
61
62    -- * Existence tests
63    , doesPathExist
64    , doesFileExist
65    , doesDirectoryExist
66
67    , findExecutable
68    , findExecutables
69    , findExecutablesInDirectories
70    , findFile
71    , findFiles
72    , findFileWith
73    , findFilesWith
74    , exeExtension
75
76    -- * Symbolic links
77    , createFileLink
78    , createDirectoryLink
79    , removeDirectoryLink
80    , pathIsSymbolicLink
81    , getSymbolicLinkTarget
82
83    -- * Permissions
84
85    -- $permissions
86
87    , Permissions
88    , emptyPermissions
89    , readable
90    , writable
91    , executable
92    , searchable
93    , setOwnerReadable
94    , setOwnerWritable
95    , setOwnerExecutable
96    , setOwnerSearchable
97
98    , getPermissions
99    , setPermissions
100    , copyPermissions
101
102    -- * Timestamps
103
104    , getAccessTime
105    , getModificationTime
106    , setAccessTime
107    , setModificationTime
108
109    -- * Deprecated
110    , isSymbolicLink
111
112   ) where
113import Prelude ()
114import System.Directory.Internal
115import System.Directory.Internal.Prelude
116import System.FilePath
117  ( (<.>)
118  , (</>)
119  , addTrailingPathSeparator
120  , dropTrailingPathSeparator
121  , hasTrailingPathSeparator
122  , isAbsolute
123  , joinPath
124  , makeRelative
125  , splitDirectories
126  , splitSearchPath
127  , takeDirectory
128  )
129import Data.Time (UTCTime)
130import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
131
132{- $intro
133A directory contains a series of entries, each of which is a named
134reference to a file system object (file, directory etc.).  Some
135entries may be hidden, inaccessible, or have some administrative
136function (e.g. @.@ or @..@ under
137<http://www.opengroup.org/onlinepubs/009695399 POSIX>), but in
138this standard all such entries are considered to form part of the
139directory contents. Entries in sub-directories are not, however,
140considered to form part of the directory contents.
141
142Each file system object is referenced by a /path/.  There is
143normally at least one absolute path to each file system object.  In
144some operating systems, it may also be possible to have paths which
145are relative to the current directory.
146
147Unless otherwise documented:
148
149* 'IO' operations in this package may throw any 'IOError'.  No other types of
150  exceptions shall be thrown.
151
152* The list of possible 'IOErrorType's in the API documentation is not
153  exhaustive.  The full list may vary by platform and/or evolve over time.
154
155-}
156
157-----------------------------------------------------------------------------
158-- Permissions
159
160{- $permissions
161
162directory offers a limited (and quirky) interface for reading and setting file
163and directory permissions; see 'getPermissions' and 'setPermissions' for a
164discussion of their limitations.  Because permissions are very difficult to
165implement portably across different platforms, users who wish to do more
166sophisticated things with permissions are advised to use other,
167platform-specific libraries instead.  For example, if you are only interested
168in permissions on POSIX-like platforms,
169<https://hackage.haskell.org/package/unix/docs/System-Posix-Files.html unix>
170offers much more flexibility.
171
172 The 'Permissions' type is used to record whether certain operations are
173 permissible on a file\/directory. 'getPermissions' and 'setPermissions'
174 get and set these permissions, respectively. Permissions apply both to
175 files and directories. For directories, the executable field will be
176 'False', and for files the searchable field will be 'False'. Note that
177 directories may be searchable without being readable, if permission has
178 been given to use them as part of a path, but not to examine the
179 directory contents.
180
181Note that to change some, but not all permissions, a construct on the following lines must be used.
182
183>  makeReadable f = do
184>     p <- getPermissions f
185>     setPermissions f (p {readable = True})
186
187-}
188
189emptyPermissions :: Permissions
190emptyPermissions = Permissions {
191                       readable   = False,
192                       writable   = False,
193                       executable = False,
194                       searchable = False
195                   }
196
197setOwnerReadable :: Bool -> Permissions -> Permissions
198setOwnerReadable b p = p { readable = b }
199
200setOwnerWritable :: Bool -> Permissions -> Permissions
201setOwnerWritable b p = p { writable = b }
202
203setOwnerExecutable :: Bool -> Permissions -> Permissions
204setOwnerExecutable b p = p { executable = b }
205
206setOwnerSearchable :: Bool -> Permissions -> Permissions
207setOwnerSearchable b p = p { searchable = b }
208
209-- | Get the permissions of a file or directory.
210--
211-- On Windows, the 'writable' permission corresponds to the "read-only"
212-- attribute.  The 'executable' permission is set if the file extension is of
213-- an executable file type.  The 'readable' permission is always set.
214--
215-- On POSIX systems, this returns the result of @access@.
216--
217-- The operation may fail with:
218--
219-- * 'isPermissionError' if the user is not permitted to access the
220--   permissions, or
221--
222-- * 'isDoesNotExistError' if the file or directory does not exist.
223getPermissions :: FilePath -> IO Permissions
224getPermissions path =
225  (`ioeAddLocation` "getPermissions") `modifyIOError` do
226    getAccessPermissions (emptyToCurDir path)
227
228-- | Set the permissions of a file or directory.
229--
230-- On Windows, this is only capable of changing the 'writable' permission,
231-- which corresponds to the "read-only" attribute.  Changing the other
232-- permissions has no effect.
233--
234-- On POSIX systems, this sets the /owner/ permissions.
235--
236-- The operation may fail with:
237--
238-- * 'isPermissionError' if the user is not permitted to set the permissions,
239--   or
240--
241-- * 'isDoesNotExistError' if the file or directory does not exist.
242setPermissions :: FilePath -> Permissions -> IO ()
243setPermissions path p =
244  (`ioeAddLocation` "setPermissions") `modifyIOError` do
245    setAccessPermissions (emptyToCurDir path) p
246
247-- | Copy the permissions of one file to another.  This reproduces the
248-- permissions more accurately than using 'getPermissions' followed by
249-- 'setPermissions'.
250--
251-- On Windows, this copies only the read-only attribute.
252--
253-- On POSIX systems, this is equivalent to @stat@ followed by @chmod@.
254copyPermissions :: FilePath -> FilePath -> IO ()
255copyPermissions src dst =
256  (`ioeAddLocation` "copyPermissions") `modifyIOError` do
257    m <- getFileMetadata src
258    copyPermissionsFromMetadata m dst
259
260copyPermissionsFromMetadata :: Metadata -> FilePath -> IO ()
261copyPermissionsFromMetadata m dst = do
262  -- instead of setFileMode, setFilePermissions is used here
263  -- this is to retain backward compatibility in copyPermissions
264  setFilePermissions dst (modeFromMetadata m)
265
266-----------------------------------------------------------------------------
267-- Implementation
268
269{- |@'createDirectory' dir@ creates a new directory @dir@ which is
270initially empty, or as near to empty as the operating system
271allows.
272
273The operation may fail with:
274
275* 'isPermissionError'
276The process has insufficient privileges to perform the operation.
277@[EROFS, EACCES]@
278
279* 'isAlreadyExistsError'
280The operand refers to a directory that already exists.
281@ [EEXIST]@
282
283* @HardwareFault@
284A physical I\/O error has occurred.
285@[EIO]@
286
287* @InvalidArgument@
288The operand is not a valid directory name.
289@[ENAMETOOLONG, ELOOP]@
290
291* 'isDoesNotExistError'
292There is no path to the directory.
293@[ENOENT, ENOTDIR]@
294
295* 'System.IO.isFullError'
296Insufficient resources (virtual memory, process file descriptors,
297physical disk space, etc.) are available to perform the operation.
298@[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
299
300* @InappropriateType@
301The path refers to an existing non-directory object.
302@[EEXIST]@
303
304-}
305
306createDirectory :: FilePath -> IO ()
307createDirectory = createDirectoryInternal
308
309-- | @'createDirectoryIfMissing' parents dir@ creates a new directory
310-- @dir@ if it doesn\'t exist. If the first argument is 'True'
311-- the function will also create all parent directories if they are missing.
312createDirectoryIfMissing :: Bool     -- ^ Create its parents too?
313                         -> FilePath -- ^ The path to the directory you want to make
314                         -> IO ()
315createDirectoryIfMissing create_parents path0
316  | create_parents = createDirs (parents path0)
317  | otherwise      = createDirs (take 1 (parents path0))
318  where
319    parents = reverse . scanl1 (</>) . splitDirectories . simplify
320
321    createDirs []         = pure ()
322    createDirs (dir:[])   = createDir dir ioError
323    createDirs (dir:dirs) =
324      createDir dir $ \_ -> do
325        createDirs dirs
326        createDir dir ioError
327
328    createDir dir notExistHandler = do
329      r <- tryIOError (createDirectory dir)
330      case r of
331        Right ()                   -> pure ()
332        Left  e
333          | isDoesNotExistError  e -> notExistHandler e
334          -- createDirectory (and indeed POSIX mkdir) does not distinguish
335          -- between a dir already existing and a file already existing. So we
336          -- check for it here. Unfortunately there is a slight race condition
337          -- here, but we think it is benign. It could report an exeption in
338          -- the case that the dir did exist but another process deletes the
339          -- directory and creates a file in its place before we can check
340          -- that the directory did indeed exist.
341          -- We also follow this path when we get a permissions error, as
342          -- trying to create "." when in the root directory on Windows
343          -- fails with
344          --     CreateDirectory ".": permission denied (Access is denied.)
345          -- This caused GHCi to crash when loading a module in the root
346          -- directory.
347          | isAlreadyExistsError e
348         || isPermissionError    e -> do
349              canIgnore <- pathIsDirectory dir
350                             `catchIOError` \ _ ->
351                               pure (isAlreadyExistsError e)
352              unless canIgnore (ioError e)
353          | otherwise              -> ioError e
354
355
356{- | @'removeDirectory' dir@ removes an existing directory /dir/.  The
357implementation may specify additional constraints which must be
358satisfied before a directory can be removed (e.g. the directory has to
359be empty, or may not be in use by other processes).  It is not legal
360for an implementation to partially remove a directory unless the
361entire directory is removed. A conformant implementation need not
362support directory removal in all situations (e.g. removal of the root
363directory).
364
365The operation may fail with:
366
367* @HardwareFault@
368A physical I\/O error has occurred.
369@[EIO]@
370
371* @InvalidArgument@
372The operand is not a valid directory name.
373@[ENAMETOOLONG, ELOOP]@
374
375* 'isDoesNotExistError'
376The directory does not exist.
377@[ENOENT, ENOTDIR]@
378
379* 'isPermissionError'
380The process has insufficient privileges to perform the operation.
381@[EROFS, EACCES, EPERM]@
382
383* @UnsatisfiedConstraints@
384Implementation-dependent constraints are not satisfied.
385@[EBUSY, ENOTEMPTY, EEXIST]@
386
387* @UnsupportedOperation@
388The implementation does not support removal in this situation.
389@[EINVAL]@
390
391* @InappropriateType@
392The operand refers to an existing non-directory object.
393@[ENOTDIR]@
394
395-}
396
397removeDirectory :: FilePath -> IO ()
398removeDirectory = removePathInternal True
399
400-- | @'removeDirectoryRecursive' dir@ removes an existing directory /dir/
401-- together with its contents and subdirectories. Within this directory,
402-- symbolic links are removed without affecting their targets.
403--
404-- On Windows, the operation fails if /dir/ is a directory symbolic link.
405removeDirectoryRecursive :: FilePath -> IO ()
406removeDirectoryRecursive path =
407  (`ioeAddLocation` "removeDirectoryRecursive") `modifyIOError` do
408    m <- getSymbolicLinkMetadata path
409    case fileTypeFromMetadata m of
410      Directory ->
411        removeContentsRecursive path
412      DirectoryLink ->
413        ioError (err `ioeSetErrorString` "is a directory symbolic link")
414      _ ->
415        ioError (err `ioeSetErrorString` "not a directory")
416  where err = mkIOError InappropriateType "" Nothing (Just path)
417
418-- | @removePathRecursive path@ removes an existing file or directory at
419-- /path/ together with its contents and subdirectories. Symbolic links are
420-- removed without affecting their the targets.
421removePathRecursive :: FilePath -> IO ()
422removePathRecursive path =
423  (`ioeAddLocation` "removePathRecursive") `modifyIOError` do
424    m <- getSymbolicLinkMetadata path
425    case fileTypeFromMetadata m of
426      Directory     -> removeContentsRecursive path
427      DirectoryLink -> removeDirectory path
428      _             -> removeFile path
429
430-- | @removeContentsRecursive dir@ removes the contents of the directory
431-- /dir/ recursively. Symbolic links are removed without affecting their the
432-- targets.
433removeContentsRecursive :: FilePath -> IO ()
434removeContentsRecursive path =
435  (`ioeAddLocation` "removeContentsRecursive") `modifyIOError` do
436    cont <- listDirectory path
437    traverse_ removePathRecursive [path </> x | x <- cont]
438    removeDirectory path
439
440-- | Removes a file or directory at /path/ together with its contents and
441-- subdirectories. Symbolic links are removed without affecting their
442-- targets. If the path does not exist, nothing happens.
443--
444-- Unlike other removal functions, this function will also attempt to delete
445-- files marked as read-only or otherwise made unremovable due to permissions.
446-- As a result, if the removal is incomplete, the permissions or attributes on
447-- the remaining files may be altered.  If there are hard links in the
448-- directory, then permissions on all related hard links may be altered.
449--
450-- If an entry within the directory vanishes while @removePathForcibly@ is
451-- running, it is silently ignored.
452--
453-- If an exception occurs while removing an entry, @removePathForcibly@ will
454-- still try to remove as many entries as it can before failing with an
455-- exception.  The first exception that it encountered is re-thrown.
456--
457-- @since 1.2.7.0
458removePathForcibly :: FilePath -> IO ()
459removePathForcibly path =
460  (`ioeAddLocation` "removePathForcibly") `modifyIOError` do
461    makeRemovable path `catchIOError` \ _ -> pure ()
462    ignoreDoesNotExistError $ do
463      m <- getSymbolicLinkMetadata path
464      case fileTypeFromMetadata m of
465        DirectoryLink -> removeDirectory path
466        Directory     -> do
467          names <- listDirectory path
468          sequenceWithIOErrors_ $
469            [ removePathForcibly (path </> name) | name <- names ] ++
470            [ removeDirectory path ]
471        _             -> removeFile path
472  where
473
474    ignoreDoesNotExistError :: IO () -> IO ()
475    ignoreDoesNotExistError action =
476      () <$ tryIOErrorType isDoesNotExistError action
477
478    makeRemovable :: FilePath -> IO ()
479    makeRemovable p = do
480      perms <- getPermissions p
481      setPermissions path perms{ readable = True
482                               , searchable = True
483                               , writable = True }
484
485{- |'removeFile' /file/ removes the directory entry for an existing file
486/file/, where /file/ is not itself a directory. The
487implementation may specify additional constraints which must be
488satisfied before a file can be removed (e.g. the file may not be in
489use by other processes).
490
491The operation may fail with:
492
493* @HardwareFault@
494A physical I\/O error has occurred.
495@[EIO]@
496
497* @InvalidArgument@
498The operand is not a valid file name.
499@[ENAMETOOLONG, ELOOP]@
500
501* 'isDoesNotExistError'
502The file does not exist.
503@[ENOENT, ENOTDIR]@
504
505* 'isPermissionError'
506The process has insufficient privileges to perform the operation.
507@[EROFS, EACCES, EPERM]@
508
509* @UnsatisfiedConstraints@
510Implementation-dependent constraints are not satisfied.
511@[EBUSY]@
512
513* @InappropriateType@
514The operand refers to an existing directory.
515@[EPERM, EINVAL]@
516
517-}
518
519removeFile :: FilePath -> IO ()
520removeFile = removePathInternal False
521
522{- |@'renameDirectory' old new@ changes the name of an existing
523directory from /old/ to /new/.  If the /new/ directory
524already exists, it is atomically replaced by the /old/ directory.
525If the /new/ directory is neither the /old/ directory nor an
526alias of the /old/ directory, it is removed as if by
527'removeDirectory'.  A conformant implementation need not support
528renaming directories in all situations (e.g. renaming to an existing
529directory, or across different physical devices), but the constraints
530must be documented.
531
532On Win32 platforms, @renameDirectory@ fails if the /new/ directory already
533exists.
534
535The operation may fail with:
536
537* @HardwareFault@
538A physical I\/O error has occurred.
539@[EIO]@
540
541* @InvalidArgument@
542Either operand is not a valid directory name.
543@[ENAMETOOLONG, ELOOP]@
544
545* 'isDoesNotExistError'
546The original directory does not exist, or there is no path to the target.
547@[ENOENT, ENOTDIR]@
548
549* 'isPermissionError'
550The process has insufficient privileges to perform the operation.
551@[EROFS, EACCES, EPERM]@
552
553* 'System.IO.isFullError'
554Insufficient resources are available to perform the operation.
555@[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
556
557* @UnsatisfiedConstraints@
558Implementation-dependent constraints are not satisfied.
559@[EBUSY, ENOTEMPTY, EEXIST]@
560
561* @UnsupportedOperation@
562The implementation does not support renaming in this situation.
563@[EINVAL, EXDEV]@
564
565* @InappropriateType@
566Either path refers to an existing non-directory object.
567@[ENOTDIR, EISDIR]@
568
569-}
570
571renameDirectory :: FilePath -> FilePath -> IO ()
572renameDirectory opath npath =
573   (`ioeAddLocation` "renameDirectory") `modifyIOError` do
574     -- XXX this test isn't performed atomically with the following rename
575     isDir <- pathIsDirectory opath
576     when (not isDir) $ do
577       ioError . (`ioeSetErrorString` "not a directory") $
578         (mkIOError InappropriateType "renameDirectory" Nothing (Just opath))
579     renamePath opath npath
580
581{- |@'renameFile' old new@ changes the name of an existing file system
582object from /old/ to /new/.  If the /new/ object already
583exists, it is atomically replaced by the /old/ object.  Neither
584path may refer to an existing directory.  A conformant implementation
585need not support renaming files in all situations (e.g. renaming
586across different physical devices), but the constraints must be
587documented.
588
589The operation may fail with:
590
591* @HardwareFault@
592A physical I\/O error has occurred.
593@[EIO]@
594
595* @InvalidArgument@
596Either operand is not a valid file name.
597@[ENAMETOOLONG, ELOOP]@
598
599* 'isDoesNotExistError'
600The original file does not exist, or there is no path to the target.
601@[ENOENT, ENOTDIR]@
602
603* 'isPermissionError'
604The process has insufficient privileges to perform the operation.
605@[EROFS, EACCES, EPERM]@
606
607* 'System.IO.isFullError'
608Insufficient resources are available to perform the operation.
609@[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
610
611* @UnsatisfiedConstraints@
612Implementation-dependent constraints are not satisfied.
613@[EBUSY]@
614
615* @UnsupportedOperation@
616The implementation does not support renaming in this situation.
617@[EXDEV]@
618
619* @InappropriateType@
620Either path refers to an existing directory.
621@[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
622
623-}
624
625renameFile :: FilePath -> FilePath -> IO ()
626renameFile opath npath =
627  (`ioeAddLocation` "renameFile") `modifyIOError` do
628    -- XXX the tests are not performed atomically with the rename
629    checkNotDir opath
630    renamePath opath npath
631      -- The underlying rename implementation can throw odd exceptions when the
632      -- destination is a directory.  For example, Windows typically throws a
633      -- permission error, while POSIX systems may throw a resource busy error
634      -- if one of the paths refers to the current directory.  In these cases,
635      -- we check if the destination is a directory and, if so, throw an
636      -- InappropriateType error.
637      `catchIOError` \ err -> do
638        checkNotDir npath
639        ioError err
640  where checkNotDir path = do
641          m <- tryIOError (getSymbolicLinkMetadata path)
642          case fileTypeIsDirectory . fileTypeFromMetadata <$> m of
643            Right True -> ioError . (`ioeSetErrorString` "is a directory") $
644                          mkIOError InappropriateType "" Nothing (Just path)
645            _          -> pure ()
646
647-- | Rename a file or directory.  If the destination path already exists, it
648-- is replaced atomically.  The destination path must not point to an existing
649-- directory.  A conformant implementation need not support renaming files in
650-- all situations (e.g. renaming across different physical devices), but the
651-- constraints must be documented.
652--
653-- The operation may fail with:
654--
655-- * @HardwareFault@
656-- A physical I\/O error has occurred.
657-- @[EIO]@
658--
659-- * @InvalidArgument@
660-- Either operand is not a valid file name.
661-- @[ENAMETOOLONG, ELOOP]@
662--
663-- * 'isDoesNotExistError'
664-- The original file does not exist, or there is no path to the target.
665-- @[ENOENT, ENOTDIR]@
666--
667-- * 'isPermissionError'
668-- The process has insufficient privileges to perform the operation.
669-- @[EROFS, EACCES, EPERM]@
670--
671-- * 'System.IO.isFullError'
672-- Insufficient resources are available to perform the operation.
673-- @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
674--
675-- * @UnsatisfiedConstraints@
676-- Implementation-dependent constraints are not satisfied.
677-- @[EBUSY]@
678--
679-- * @UnsupportedOperation@
680-- The implementation does not support renaming in this situation.
681-- @[EXDEV]@
682--
683-- * @InappropriateType@
684-- Either the destination path refers to an existing directory, or one of the
685-- parent segments in the destination path is not a directory.
686-- @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
687--
688-- @since 1.2.7.0
689renamePath :: FilePath                  -- ^ Old path
690           -> FilePath                  -- ^ New path
691           -> IO ()
692renamePath opath npath =
693  (`ioeAddLocation` "renamePath") `modifyIOError` do
694    renamePathInternal opath npath
695
696-- | Copy a file with its permissions.  If the destination file already exists,
697-- it is replaced atomically.  Neither path may refer to an existing
698-- directory.  No exceptions are thrown if the permissions could not be
699-- copied.
700copyFile :: FilePath                    -- ^ Source filename
701         -> FilePath                    -- ^ Destination filename
702         -> IO ()
703copyFile fromFPath toFPath =
704  (`ioeAddLocation` "copyFile") `modifyIOError` do
705    atomicCopyFileContents fromFPath toFPath
706      (ignoreIOExceptions . copyPermissions fromFPath)
707
708-- | Copy the contents of a source file to a destination file, replacing the
709-- destination file atomically via @withReplacementFile@, resetting the
710-- attributes of the destination file to the defaults.
711atomicCopyFileContents :: FilePath            -- ^ Source filename
712                       -> FilePath            -- ^ Destination filename
713                       -> (FilePath -> IO ()) -- ^ Post-action
714                       -> IO ()
715atomicCopyFileContents fromFPath toFPath postAction =
716  (`ioeAddLocation` "atomicCopyFileContents") `modifyIOError` do
717    withReplacementFile toFPath postAction $ \ hTo -> do
718      copyFileToHandle fromFPath hTo
719
720-- | A helper function useful for replacing files in an atomic manner.  The
721-- function creates a temporary file in the directory of the destination file,
722-- opens it, performs the main action with its handle, closes it, performs the
723-- post-action with its path, and finally replaces the destination file with
724-- the temporary file.  If an error occurs during any step of this process,
725-- the temporary file is removed and the destination file remains untouched.
726withReplacementFile :: FilePath            -- ^ Destination file
727                    -> (FilePath -> IO ()) -- ^ Post-action
728                    -> (Handle -> IO a)    -- ^ Main action
729                    -> IO a
730withReplacementFile path postAction action =
731  (`ioeAddLocation` "withReplacementFile") `modifyIOError` do
732    mask $ \ restore -> do
733      (tmpFPath, hTmp) <- openBinaryTempFile (takeDirectory path)
734                                             ".copyFile.tmp"
735      (`onException` ignoreIOExceptions (removeFile tmpFPath)) $ do
736        r <- (`onException` ignoreIOExceptions (hClose hTmp)) $ do
737          restore (action hTmp)
738        hClose hTmp
739        restore (postAction tmpFPath)
740        renameFile tmpFPath path
741        pure r
742
743-- | Copy a file with its associated metadata.  If the destination file
744-- already exists, it is overwritten.  There is no guarantee of atomicity in
745-- the replacement of the destination file.  Neither path may refer to an
746-- existing directory.  If the source and/or destination are symbolic links,
747-- the copy is performed on the targets of the links.
748--
749-- On Windows, it behaves like the Win32 function
750-- <https://msdn.microsoft.com/en-us/library/windows/desktop/aa363851.aspx CopyFile>,
751-- which copies various kinds of metadata including file attributes and
752-- security resource properties.
753--
754-- On Unix-like systems, permissions, access time, and modification time are
755-- preserved.  If possible, the owner and group are also preserved.  Note that
756-- the very act of copying can change the access time of the source file,
757-- hence the access times of the two files may differ after the operation
758-- completes.
759--
760-- @since 1.2.6.0
761copyFileWithMetadata :: FilePath        -- ^ Source file
762                     -> FilePath        -- ^ Destination file
763                     -> IO ()
764copyFileWithMetadata src dst =
765  (`ioeAddLocation` "copyFileWithMetadata") `modifyIOError`
766    copyFileWithMetadataInternal copyPermissionsFromMetadata
767                                 copyTimesFromMetadata
768                                 src
769                                 dst
770
771copyTimesFromMetadata :: Metadata -> FilePath -> IO ()
772copyTimesFromMetadata st dst = do
773  let atime = accessTimeFromMetadata st
774  let mtime = modificationTimeFromMetadata st
775  setFileTimes dst (Just atime, Just mtime)
776
777-- | Make a path absolute, normalize the path, and remove as many indirections
778-- from it as possible.  Any trailing path separators are discarded via
779-- 'dropTrailingPathSeparator'.  Additionally, on Windows the letter case of
780-- the path is canonicalized.
781--
782-- __Note__: This function is a very big hammer.  If you only need an absolute
783-- path, 'makeAbsolute' is sufficient for removing dependence on the current
784-- working directory.
785--
786-- Indirections include the two special directories @.@ and @..@, as well as
787-- any symbolic links (and junction points on Windows).  The input path need
788-- not point to an existing file or directory.  Canonicalization is performed
789-- on the longest prefix of the path that points to an existing file or
790-- directory.  The remaining portion of the path that does not point to an
791-- existing file or directory will still be normalized, but case
792-- canonicalization and indirection removal are skipped as they are impossible
793-- to do on a nonexistent path.
794--
795-- Most programs should not worry about the canonicity of a path.  In
796-- particular, despite the name, the function does not truly guarantee
797-- canonicity of the returned path due to the presence of hard links, mount
798-- points, etc.
799--
800-- If the path points to an existing file or directory, then the output path
801-- shall also point to the same file or directory, subject to the condition
802-- that the relevant parts of the file system do not change while the function
803-- is still running.  In other words, the function is definitively not atomic.
804-- The results can be utterly wrong if the portions of the path change while
805-- this function is running.
806--
807-- Since some indirections (symbolic links on all systems, @..@ on non-Windows
808-- systems, and junction points on Windows) are dependent on the state of the
809-- existing filesystem, the function can only make a conservative attempt by
810-- removing such indirections from the longest prefix of the path that still
811-- points to an existing file or directory.
812--
813-- Note that on Windows parent directories @..@ are always fully expanded
814-- before the symbolic links, as consistent with the rest of the Windows API
815-- (such as @GetFullPathName@).  In contrast, on POSIX systems parent
816-- directories @..@ are expanded alongside symbolic links from left to right.
817-- To put this more concretely: if @L@ is a symbolic link for @R/P@, then on
818-- Windows @L\\..@ refers to @.@, whereas on other operating systems @L/..@
819-- refers to @R@.
820--
821-- Similar to 'System.FilePath.normalise', passing an empty path is equivalent
822-- to passing the current directory.
823--
824-- @canonicalizePath@ can resolve at least 64 indirections in a single path,
825-- more than what is supported by most operating systems.  Therefore, it may
826-- return the fully resolved path even though the operating system itself
827-- would have long given up.
828--
829-- On Windows XP or earlier systems, junction expansion is not performed due
830-- to their lack of @GetFinalPathNameByHandle@.
831--
832-- /Changes since 1.2.3.0:/ The function has been altered to be more robust
833-- and has the same exception behavior as 'makeAbsolute'.
834--
835-- /Changes since 1.3.0.0:/ The function no longer preserves the trailing path
836-- separator.  File symbolic links that appear in the middle of a path are
837-- properly dereferenced.  Case canonicalization and symbolic link expansion
838-- are now performed on Windows.
839--
840canonicalizePath :: FilePath -> IO FilePath
841canonicalizePath = \ path ->
842  ((`ioeAddLocation` "canonicalizePath") .
843   (`ioeSetFileName` path)) `modifyIOError` do
844    -- simplify does more stuff, like upper-casing the drive letter
845    dropTrailingPathSeparator . simplify <$>
846      (canonicalizePathWith attemptRealpath =<< prependCurrentDirectory path)
847  where
848
849    -- allow up to 64 cycles before giving up
850    attemptRealpath realpath =
851      attemptRealpathWith (64 :: Int) Nothing realpath
852      <=< canonicalizePathSimplify
853
854    -- n is a counter to make sure we don't run into an infinite loop; we
855    -- don't try to do any cycle detection here because an adversary could DoS
856    -- any arbitrarily clever algorithm
857    attemptRealpathWith n mFallback realpath path =
858      case mFallback of
859        -- too many indirections ... giving up.
860        Just fallback | n <= 0 -> pure fallback
861        -- either mFallback == Nothing (first attempt)
862        --     or n > 0 (still have some attempts left)
863        _ -> realpathPrefix (reverse (zip prefixes suffixes))
864
865      where
866
867        segments = splitDirectories path
868        prefixes = scanl1 (</>) segments
869        suffixes = tail (scanr (</>) "" segments)
870
871        -- try to call realpath on the largest possible prefix
872        realpathPrefix candidates =
873          case candidates of
874            [] -> pure path
875            (prefix, suffix) : rest -> do
876              exist <- doesPathExist prefix
877              if not exist
878                -- never call realpath on an inaccessible path
879                -- (to avoid bugs in system realpath implementations)
880                -- try a smaller prefix instead
881                then realpathPrefix rest
882                else do
883                  mp <- tryIOError (realpath prefix)
884                  case mp of
885                    -- realpath failed: try a smaller prefix instead
886                    Left _ -> realpathPrefix rest
887                    -- realpath succeeded: fine-tune the result
888                    Right p -> realpathFurther (p </> suffix) p suffix
889
890        -- by now we have a reasonable fallback value that we can use if we
891        -- run into too many indirections; the fallback value is the same
892        -- result that we have been returning in versions prior to 1.3.1.0
893        -- (this is essentially the fix to #64)
894        realpathFurther fallback p suffix =
895          case splitDirectories suffix of
896            [] -> pure fallback
897            next : restSuffix -> do
898              -- see if the 'next' segment is a symlink
899              mTarget <- tryIOError (getSymbolicLinkTarget (p </> next))
900              case mTarget of
901                Left _ -> pure fallback
902                Right target -> do
903                  -- if so, dereference it and restart the whole cycle
904                  let mFallback' = Just (fromMaybe fallback mFallback)
905                  path' <- canonicalizePathSimplify
906                             (p </> target </> joinPath restSuffix)
907                  attemptRealpathWith (n - 1) mFallback' realpath path'
908
909-- | Convert a path into an absolute path.  If the given path is relative, the
910-- current directory is prepended and then the combined result is normalized.
911-- If the path is already absolute, the path is simply normalized.  The
912-- function preserves the presence or absence of the trailing path separator
913-- unless the path refers to the root directory @/@.
914--
915-- If the path is already absolute, the operation never fails.  Otherwise, the
916-- operation may fail with the same exceptions as 'getCurrentDirectory'.
917--
918-- @since 1.2.2.0
919--
920makeAbsolute :: FilePath -> IO FilePath
921makeAbsolute path =
922  ((`ioeAddLocation` "makeAbsolute") .
923   (`ioeSetFileName` path)) `modifyIOError` do
924    matchTrailingSeparator path . simplify <$> prependCurrentDirectory path
925
926-- | Add or remove the trailing path separator in the second path so as to
927-- match its presence in the first path.
928--
929-- (internal API)
930matchTrailingSeparator :: FilePath -> FilePath -> FilePath
931matchTrailingSeparator path
932  | hasTrailingPathSeparator path = addTrailingPathSeparator
933  | otherwise                     = dropTrailingPathSeparator
934
935-- | Construct a path relative to the current directory, similar to
936-- 'makeRelative'.
937--
938-- The operation may fail with the same exceptions as 'getCurrentDirectory'.
939makeRelativeToCurrentDirectory :: FilePath -> IO FilePath
940makeRelativeToCurrentDirectory x = do
941  (`makeRelative` x) <$> getCurrentDirectory
942
943-- | Given the name or path of an executable file, 'findExecutable' searches
944-- for such a file in a list of system-defined locations, which generally
945-- includes @PATH@ and possibly more.  The full path to the executable is
946-- returned if found.  For example, @(findExecutable \"ghc\")@ would normally
947-- give you the path to GHC.
948--
949-- The path returned by @'findExecutable' name@ corresponds to the program
950-- that would be executed by
951-- @<http://hackage.haskell.org/package/process/docs/System-Process.html#v:createProcess createProcess>@
952-- when passed the same string (as a @RawCommand@, not a @ShellCommand@),
953-- provided that @name@ is not a relative path with more than one segment.
954--
955-- On Windows, 'findExecutable' calls the Win32 function
956-- @<https://msdn.microsoft.com/en-us/library/aa365527.aspx SearchPath>@,
957-- which may search other places before checking the directories in the @PATH@
958-- environment variable.  Where it actually searches depends on registry
959-- settings, but notably includes the directory containing the current
960-- executable.
961--
962-- On non-Windows platforms, the behavior is equivalent to 'findFileWith'
963-- using the search directories from the @PATH@ environment variable and
964-- testing each file for executable permissions.  Details can be found in the
965-- documentation of 'findFileWith'.
966findExecutable :: String -> IO (Maybe FilePath)
967findExecutable binary =
968  listTHead
969    (findExecutablesLazyInternal findExecutablesInDirectoriesLazy binary)
970
971-- | Search for executable files in a list of system-defined locations, which
972-- generally includes @PATH@ and possibly more.
973--
974-- On Windows, this /only returns the first ocurrence/, if any.  Its behavior
975-- is therefore equivalent to 'findExecutable'.
976--
977-- On non-Windows platforms, the behavior is equivalent to
978-- 'findExecutablesInDirectories' using the search directories from the @PATH@
979-- environment variable.  Details can be found in the documentation of
980-- 'findExecutablesInDirectories'.
981--
982-- @since 1.2.2.0
983findExecutables :: String -> IO [FilePath]
984findExecutables binary =
985  listTToList
986    (findExecutablesLazyInternal findExecutablesInDirectoriesLazy binary)
987
988-- | Given a name or path, 'findExecutable' appends the 'exeExtension' to the
989-- query and searches for executable files in the list of given search
990-- directories and returns all occurrences.
991--
992-- The behavior is equivalent to 'findFileWith' using the given search
993-- directories and testing each file for executable permissions.  Details can
994-- be found in the documentation of 'findFileWith'.
995--
996-- Unlike other similarly named functions, 'findExecutablesInDirectories' does
997-- not use @SearchPath@ from the Win32 API.  The behavior of this function on
998-- Windows is therefore equivalent to those on non-Windows platforms.
999--
1000-- @since 1.2.4.0
1001findExecutablesInDirectories :: [FilePath] -> String -> IO [FilePath]
1002findExecutablesInDirectories path binary =
1003  listTToList (findExecutablesInDirectoriesLazy path binary)
1004
1005findExecutablesInDirectoriesLazy :: [FilePath] -> String -> ListT IO FilePath
1006findExecutablesInDirectoriesLazy path binary =
1007  findFilesWithLazy isExecutable path (binary <.> exeExtension)
1008
1009-- | Test whether a file has executable permissions.
1010isExecutable :: FilePath -> IO Bool
1011isExecutable file = executable <$> getPermissions file
1012
1013-- | Search through the given list of directories for the given file.
1014--
1015-- The behavior is equivalent to 'findFileWith', returning only the first
1016-- occurrence.  Details can be found in the documentation of 'findFileWith'.
1017findFile :: [FilePath] -> String -> IO (Maybe FilePath)
1018findFile = findFileWith (\ _ -> pure True)
1019
1020-- | Search through the given list of directories for the given file and
1021-- returns all paths where the given file exists.
1022--
1023-- The behavior is equivalent to 'findFilesWith'.  Details can be found in the
1024-- documentation of 'findFilesWith'.
1025--
1026-- @since 1.2.1.0
1027findFiles :: [FilePath] -> String -> IO [FilePath]
1028findFiles = findFilesWith (\ _ -> pure True)
1029
1030-- | Search through a given list of directories for a file that has the given
1031-- name and satisfies the given predicate and return the path of the first
1032-- occurrence.  The directories are checked in a left-to-right order.
1033--
1034-- This is essentially a more performant version of 'findFilesWith' that
1035-- always returns the first result, if any.  Details can be found in the
1036-- documentation of 'findFilesWith'.
1037--
1038-- @since 1.2.6.0
1039findFileWith :: (FilePath -> IO Bool) -> [FilePath] -> String -> IO (Maybe FilePath)
1040findFileWith f ds name = listTHead (findFilesWithLazy f ds name)
1041
1042-- | @findFilesWith predicate dirs name@ searches through the list of
1043-- directories (@dirs@) for files that have the given @name@ and satisfy the
1044-- given @predicate@ ands return the paths of those files.  The directories
1045-- are checked in a left-to-right order and the paths are returned in the same
1046-- order.
1047--
1048-- If the @name@ is a relative path, then for every search directory @dir@,
1049-- the function checks whether @dir '</>' name@ exists and satisfies the
1050-- predicate.  If so, @dir '</>' name@ is returned as one of the results.  In
1051-- other words, the returned paths can be either relative or absolute
1052-- depending on the search directories were used.  If there are no search
1053-- directories, no results are ever returned.
1054--
1055-- If the @name@ is an absolute path, then the function will return a single
1056-- result if the file exists and satisfies the predicate and no results
1057-- otherwise.  This is irrespective of what search directories were given.
1058--
1059-- @since 1.2.1.0
1060findFilesWith :: (FilePath -> IO Bool) -> [FilePath] -> String -> IO [FilePath]
1061findFilesWith f ds name = listTToList (findFilesWithLazy f ds name)
1062
1063findFilesWithLazy
1064  :: (FilePath -> IO Bool) -> [FilePath] -> String -> ListT IO FilePath
1065findFilesWithLazy f dirs path
1066  -- make sure absolute paths are handled properly irrespective of 'dirs'
1067  -- https://github.com/haskell/directory/issues/72
1068  | isAbsolute path = ListT (find [""])
1069  | otherwise       = ListT (find dirs)
1070
1071  where
1072
1073    find []       = pure Nothing
1074    find (d : ds) = do
1075      let p = d </> path
1076      found <- doesFileExist p `andM` f p
1077      if found
1078        then pure (Just (p, ListT (find ds)))
1079        else find ds
1080
1081-- | Filename extension for executable files (including the dot if any)
1082--   (usually @\"\"@ on POSIX systems and @\".exe\"@ on Windows or OS\/2).
1083--
1084-- @since 1.2.4.0
1085exeExtension :: String
1086exeExtension = exeExtensionInternal
1087
1088-- | Similar to 'listDirectory', but always includes the special entries (@.@
1089-- and @..@).  (This applies to Windows as well.)
1090--
1091-- The operation may fail with the same exceptions as 'listDirectory'.
1092getDirectoryContents :: FilePath -> IO [FilePath]
1093getDirectoryContents path =
1094  ((`ioeSetFileName` path) .
1095   (`ioeAddLocation` "getDirectoryContents")) `modifyIOError` do
1096    getDirectoryContentsInternal path
1097
1098-- | @'listDirectory' dir@ returns a list of /all/ entries in /dir/ without
1099-- the special entries (@.@ and @..@).
1100--
1101-- The operation may fail with:
1102--
1103-- * @HardwareFault@
1104--   A physical I\/O error has occurred.
1105--   @[EIO]@
1106--
1107-- * @InvalidArgument@
1108--   The operand is not a valid directory name.
1109--   @[ENAMETOOLONG, ELOOP]@
1110--
1111-- * 'isDoesNotExistError'
1112--   The directory does not exist.
1113--   @[ENOENT, ENOTDIR]@
1114--
1115-- * 'isPermissionError'
1116--   The process has insufficient privileges to perform the operation.
1117--   @[EACCES]@
1118--
1119-- * 'System.IO.isFullError'
1120--   Insufficient resources are available to perform the operation.
1121--   @[EMFILE, ENFILE]@
1122--
1123-- * @InappropriateType@
1124--   The path refers to an existing non-directory object.
1125--   @[ENOTDIR]@
1126--
1127-- @since 1.2.5.0
1128--
1129listDirectory :: FilePath -> IO [FilePath]
1130listDirectory path = filter f <$> getDirectoryContents path
1131  where f filename = filename /= "." && filename /= ".."
1132
1133-- | Obtain the current working directory as an absolute path.
1134--
1135-- In a multithreaded program, the current working directory is a global state
1136-- shared among all threads of the process.  Therefore, when performing
1137-- filesystem operations from multiple threads, it is highly recommended to
1138-- use absolute rather than relative paths (see: 'makeAbsolute').
1139--
1140-- The operation may fail with:
1141--
1142-- * @HardwareFault@
1143-- A physical I\/O error has occurred.
1144-- @[EIO]@
1145--
1146-- * 'isDoesNotExistError'
1147-- There is no path referring to the working directory.
1148-- @[EPERM, ENOENT, ESTALE...]@
1149--
1150-- * 'isPermissionError'
1151-- The process has insufficient privileges to perform the operation.
1152-- @[EACCES]@
1153--
1154-- * 'System.IO.isFullError'
1155-- Insufficient resources are available to perform the operation.
1156--
1157-- * @UnsupportedOperation@
1158-- The operating system has no notion of current working directory.
1159--
1160getCurrentDirectory :: IO FilePath
1161getCurrentDirectory =
1162  (`ioeAddLocation` "getCurrentDirectory") `modifyIOError` do
1163    specializeErrorString
1164      "Current working directory no longer exists"
1165      isDoesNotExistError
1166      getCurrentDirectoryInternal
1167
1168-- | Change the working directory to the given path.
1169--
1170-- In a multithreaded program, the current working directory is a global state
1171-- shared among all threads of the process.  Therefore, when performing
1172-- filesystem operations from multiple threads, it is highly recommended to
1173-- use absolute rather than relative paths (see: 'makeAbsolute').
1174--
1175-- The operation may fail with:
1176--
1177-- * @HardwareFault@
1178-- A physical I\/O error has occurred.
1179-- @[EIO]@
1180--
1181-- * @InvalidArgument@
1182-- The operand is not a valid directory name.
1183-- @[ENAMETOOLONG, ELOOP]@
1184--
1185-- * 'isDoesNotExistError'
1186-- The directory does not exist.
1187-- @[ENOENT, ENOTDIR]@
1188--
1189-- * 'isPermissionError'
1190-- The process has insufficient privileges to perform the operation.
1191-- @[EACCES]@
1192--
1193-- * @UnsupportedOperation@
1194-- The operating system has no notion of current working directory, or the
1195-- working directory cannot be dynamically changed.
1196--
1197-- * @InappropriateType@
1198-- The path refers to an existing non-directory object.
1199-- @[ENOTDIR]@
1200--
1201setCurrentDirectory :: FilePath -> IO ()
1202setCurrentDirectory = setCurrentDirectoryInternal
1203
1204-- | Run an 'IO' action with the given working directory and restore the
1205-- original working directory afterwards, even if the given action fails due
1206-- to an exception.
1207--
1208-- The operation may fail with the same exceptions as 'getCurrentDirectory'
1209-- and 'setCurrentDirectory'.
1210--
1211-- @since 1.2.3.0
1212--
1213withCurrentDirectory :: FilePath  -- ^ Directory to execute in
1214                     -> IO a      -- ^ Action to be executed
1215                     -> IO a
1216withCurrentDirectory dir action =
1217  bracket getCurrentDirectory setCurrentDirectory $ \ _ -> do
1218    setCurrentDirectory dir
1219    action
1220
1221-- | Obtain the size of a file in bytes.
1222--
1223-- @since 1.2.7.0
1224getFileSize :: FilePath -> IO Integer
1225getFileSize path =
1226  (`ioeAddLocation` "getFileSize") `modifyIOError` do
1227    fileSizeFromMetadata <$> getFileMetadata path
1228
1229-- | Test whether the given path points to an existing filesystem object.  If
1230-- the user lacks necessary permissions to search the parent directories, this
1231-- function may return false even if the file does actually exist.
1232--
1233-- @since 1.2.7.0
1234doesPathExist :: FilePath -> IO Bool
1235doesPathExist path = do
1236  (True <$ getFileMetadata path)
1237    `catchIOError` \ _ ->
1238      pure False
1239
1240{- |The operation 'doesDirectoryExist' returns 'True' if the argument file
1241exists and is either a directory or a symbolic link to a directory,
1242and 'False' otherwise.
1243-}
1244
1245doesDirectoryExist :: FilePath -> IO Bool
1246doesDirectoryExist path = do
1247  pathIsDirectory path
1248    `catchIOError` \ _ ->
1249      pure False
1250
1251{- |The operation 'doesFileExist' returns 'True'
1252if the argument file exists and is not a directory, and 'False' otherwise.
1253-}
1254
1255doesFileExist :: FilePath -> IO Bool
1256doesFileExist path = do
1257  (not <$> pathIsDirectory path)
1258    `catchIOError` \ _ ->
1259      pure False
1260
1261pathIsDirectory :: FilePath -> IO Bool
1262pathIsDirectory path =
1263  (`ioeAddLocation` "pathIsDirectory") `modifyIOError` do
1264    fileTypeIsDirectory . fileTypeFromMetadata <$> getFileMetadata path
1265
1266-- | Create a /file/ symbolic link.  The target path can be either absolute or
1267-- relative and need not refer to an existing file.  The order of arguments
1268-- follows the POSIX convention.
1269--
1270-- To remove an existing file symbolic link, use 'removeFile'.
1271--
1272-- Although the distinction between /file/ symbolic links and /directory/
1273-- symbolic links does not exist on POSIX systems, on Windows this is an
1274-- intrinsic property of every symbolic link and cannot be changed without
1275-- recreating the link.  A file symbolic link that actually points to a
1276-- directory will fail to dereference and vice versa.  Moreover, creating
1277-- symbolic links on Windows may require privileges unavailable to users
1278-- outside the Administrators group.  Portable programs that use symbolic
1279-- links should take both into consideration.
1280--
1281-- On Windows, the function is implemented using @CreateSymbolicLink@.  Since
1282-- 1.3.3.0, the @SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE@ flag is included
1283-- if supported by the operating system.  On POSIX, the function uses @symlink@
1284-- and is therefore atomic.
1285--
1286-- Windows-specific errors: This operation may fail with 'permissionErrorType'
1287-- if the user lacks the privileges to create symbolic links.  It may also
1288-- fail with 'illegalOperationErrorType' if the file system does not support
1289-- symbolic links.
1290--
1291-- @since 1.3.1.0
1292createFileLink
1293  :: FilePath                           -- ^ path to the target file
1294  -> FilePath                           -- ^ path of the link to be created
1295  -> IO ()
1296createFileLink target link =
1297  (`ioeAddLocation` "createFileLink") `modifyIOError` do
1298    createSymbolicLink False target link
1299
1300-- | Create a /directory/ symbolic link.  The target path can be either
1301-- absolute or relative and need not refer to an existing directory.  The
1302-- order of arguments follows the POSIX convention.
1303--
1304-- To remove an existing directory symbolic link, use 'removeDirectoryLink'.
1305--
1306-- Although the distinction between /file/ symbolic links and /directory/
1307-- symbolic links does not exist on POSIX systems, on Windows this is an
1308-- intrinsic property of every symbolic link and cannot be changed without
1309-- recreating the link.  A file symbolic link that actually points to a
1310-- directory will fail to dereference and vice versa.  Moreover, creating
1311-- symbolic links on Windows may require privileges unavailable to users
1312-- outside the Administrators group.  Portable programs that use symbolic
1313-- links should take both into consideration.
1314--
1315-- On Windows, the function is implemented using @CreateSymbolicLink@ with
1316-- @SYMBOLIC_LINK_FLAG_DIRECTORY@.  Since 1.3.3.0, the
1317-- @SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE@ flag is also included if
1318-- supported by the operating system.   On POSIX, this is an alias for
1319-- 'createFileLink' and is therefore atomic.
1320--
1321-- Windows-specific errors: This operation may fail with 'permissionErrorType'
1322-- if the user lacks the privileges to create symbolic links.  It may also
1323-- fail with 'illegalOperationErrorType' if the file system does not support
1324-- symbolic links.
1325--
1326-- @since 1.3.1.0
1327createDirectoryLink
1328  :: FilePath                           -- ^ path to the target directory
1329  -> FilePath                           -- ^ path of the link to be created
1330  -> IO ()
1331createDirectoryLink target link =
1332  (`ioeAddLocation` "createDirectoryLink") `modifyIOError` do
1333    createSymbolicLink True target link
1334
1335-- | Remove an existing /directory/ symbolic link.
1336--
1337-- On Windows, this is an alias for 'removeDirectory'.  On POSIX systems, this
1338-- is an alias for 'removeFile'.
1339--
1340-- See also: 'removeFile', which can remove an existing /file/ symbolic link.
1341--
1342-- @since 1.3.1.0
1343removeDirectoryLink :: FilePath -> IO ()
1344removeDirectoryLink path =
1345  (`ioeAddLocation` "removeDirectoryLink") `modifyIOError` do
1346    removePathInternal linkToDirectoryIsDirectory path
1347
1348-- | Check whether an existing @path@ is a symbolic link.  If @path@ is a
1349-- regular file or directory, 'False' is returned.  If @path@ does not exist
1350-- or is otherwise inaccessible, an exception is thrown (see below).
1351--
1352-- On Windows, this checks for @FILE_ATTRIBUTE_REPARSE_POINT@.  In addition to
1353-- symbolic links, the function also returns true on junction points.  On
1354-- POSIX systems, this checks for @S_IFLNK@.
1355--
1356-- The operation may fail with:
1357--
1358-- * 'isDoesNotExistError' if the symbolic link does not exist; or
1359--
1360-- * 'isPermissionError' if the user is not permitted to read the symbolic
1361--   link.
1362--
1363-- @since 1.3.0.0
1364pathIsSymbolicLink :: FilePath -> IO Bool
1365pathIsSymbolicLink path =
1366  ((`ioeAddLocation` "pathIsSymbolicLink") .
1367   (`ioeSetFileName` path)) `modifyIOError` do
1368     fileTypeIsLink . fileTypeFromMetadata <$> getSymbolicLinkMetadata path
1369
1370{-# DEPRECATED isSymbolicLink "Use 'pathIsSymbolicLink' instead" #-}
1371isSymbolicLink :: FilePath -> IO Bool
1372isSymbolicLink = pathIsSymbolicLink
1373
1374-- | Retrieve the target path of either a file or directory symbolic link.
1375-- The returned path may not be absolute, may not exist, and may not even be a
1376-- valid path.
1377--
1378-- On Windows systems, this calls @DeviceIoControl@ with
1379-- @FSCTL_GET_REPARSE_POINT@.  In addition to symbolic links, the function
1380-- also works on junction points.  On POSIX systems, this calls @readlink@.
1381--
1382-- Windows-specific errors: This operation may fail with
1383-- 'illegalOperationErrorType' if the file system does not support symbolic
1384-- links.
1385--
1386-- @since 1.3.1.0
1387getSymbolicLinkTarget :: FilePath -> IO FilePath
1388getSymbolicLinkTarget path =
1389  (`ioeAddLocation` "getSymbolicLinkTarget") `modifyIOError` do
1390    readSymbolicLink path
1391
1392-- | Obtain the time at which the file or directory was last accessed.
1393--
1394-- The operation may fail with:
1395--
1396-- * 'isPermissionError' if the user is not permitted to read
1397--   the access time; or
1398--
1399-- * 'isDoesNotExistError' if the file or directory does not exist.
1400--
1401-- Caveat for POSIX systems: This function returns a timestamp with sub-second
1402-- resolution only if this package is compiled against @unix-2.6.0.0@ or later
1403-- and the underlying filesystem supports them.
1404--
1405-- @since 1.2.3.0
1406--
1407getAccessTime :: FilePath -> IO UTCTime
1408getAccessTime path =
1409  (`ioeAddLocation` "getAccessTime") `modifyIOError` do
1410    accessTimeFromMetadata <$> getFileMetadata (emptyToCurDir path)
1411
1412-- | Obtain the time at which the file or directory was last modified.
1413--
1414-- The operation may fail with:
1415--
1416-- * 'isPermissionError' if the user is not permitted to read
1417--   the modification time; or
1418--
1419-- * 'isDoesNotExistError' if the file or directory does not exist.
1420--
1421-- Caveat for POSIX systems: This function returns a timestamp with sub-second
1422-- resolution only if this package is compiled against @unix-2.6.0.0@ or later
1423-- and the underlying filesystem supports them.
1424--
1425getModificationTime :: FilePath -> IO UTCTime
1426getModificationTime path =
1427  (`ioeAddLocation` "getModificationTime") `modifyIOError` do
1428    modificationTimeFromMetadata <$> getFileMetadata (emptyToCurDir path)
1429
1430-- | Change the time at which the file or directory was last accessed.
1431--
1432-- The operation may fail with:
1433--
1434-- * 'isPermissionError' if the user is not permitted to alter the
1435--   access time; or
1436--
1437-- * 'isDoesNotExistError' if the file or directory does not exist.
1438--
1439-- Some caveats for POSIX systems:
1440--
1441-- * Not all systems support @utimensat@, in which case the function can only
1442--   emulate the behavior by reading the modification time and then setting
1443--   both the access and modification times together.  On systems where
1444--   @utimensat@ is supported, the access time is set atomically with
1445--   nanosecond precision.
1446--
1447-- * If compiled against a version of @unix@ prior to @2.7.0.0@, the function
1448--   would not be able to set timestamps with sub-second resolution.  In this
1449--   case, there would also be loss of precision in the modification time.
1450--
1451-- @since 1.2.3.0
1452--
1453setAccessTime :: FilePath -> UTCTime -> IO ()
1454setAccessTime path atime =
1455  (`ioeAddLocation` "setAccessTime") `modifyIOError` do
1456    setFileTimes path (Just atime, Nothing)
1457
1458-- | Change the time at which the file or directory was last modified.
1459--
1460-- The operation may fail with:
1461--
1462-- * 'isPermissionError' if the user is not permitted to alter the
1463--   modification time; or
1464--
1465-- * 'isDoesNotExistError' if the file or directory does not exist.
1466--
1467-- Some caveats for POSIX systems:
1468--
1469-- * Not all systems support @utimensat@, in which case the function can only
1470--   emulate the behavior by reading the access time and then setting both the
1471--   access and modification times together.  On systems where @utimensat@ is
1472--   supported, the modification time is set atomically with nanosecond
1473--   precision.
1474--
1475-- * If compiled against a version of @unix@ prior to @2.7.0.0@, the function
1476--   would not be able to set timestamps with sub-second resolution.  In this
1477--   case, there would also be loss of precision in the access time.
1478--
1479-- @since 1.2.3.0
1480--
1481setModificationTime :: FilePath -> UTCTime -> IO ()
1482setModificationTime path mtime =
1483  (`ioeAddLocation` "setModificationTime") `modifyIOError` do
1484    setFileTimes path (Nothing, Just mtime)
1485
1486setFileTimes :: FilePath -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
1487setFileTimes _ (Nothing, Nothing) = return ()
1488setFileTimes path (atime, mtime) =
1489  ((`ioeAddLocation` "setFileTimes") .
1490   (`ioeSetFileName` path)) `modifyIOError` do
1491    setTimes (emptyToCurDir path)
1492             (utcTimeToPOSIXSeconds <$> atime, utcTimeToPOSIXSeconds <$> mtime)
1493
1494{- | Returns the current user's home directory.
1495
1496The directory returned is expected to be writable by the current user,
1497but note that it isn't generally considered good practice to store
1498application-specific data here; use 'getXdgDirectory' or
1499'getAppUserDataDirectory' instead.
1500
1501On Unix, 'getHomeDirectory' behaves as follows:
1502
1503* Returns $HOME env variable if set (including to an empty string).
1504* Otherwise uses home directory returned by `getpwuid_r` using the UID of the current proccesses user. This basically reads the /etc/passwd file. An empty home directory field is considered valid.
1505
1506On Windows, the system is queried for a suitable path; a typical path might be @C:\/Users\//\<user\>/@.
1507
1508The operation may fail with:
1509
1510* @UnsupportedOperation@
1511The operating system has no notion of home directory.
1512
1513* 'isDoesNotExistError'
1514The home directory for the current user does not exist, or
1515cannot be found.
1516-}
1517getHomeDirectory :: IO FilePath
1518getHomeDirectory =
1519  (`ioeAddLocation` "getHomeDirectory") `modifyIOError` do
1520    getHomeDirectoryInternal
1521
1522-- | Obtain the paths to special directories for storing user-specific
1523--   application data, configuration, and cache files, conforming to the
1524--   <http://standards.freedesktop.org/basedir-spec/basedir-spec-latest.html XDG Base Directory Specification>.
1525--   Compared with 'getAppUserDataDirectory', this function provides a more
1526--   fine-grained hierarchy as well as greater flexibility for the user.
1527--
1528--   On Windows, 'XdgData' and 'XdgConfig' usually map to the same directory
1529--   unless overridden.
1530--
1531--   Refer to the docs of 'XdgDirectory' for more details.
1532--
1533--   The second argument is usually the name of the application.  Since it
1534--   will be integrated into the path, it must consist of valid path
1535--   characters.  Note: if the second argument is an absolute path, it will
1536--   just return the second argument.
1537--
1538--   Note: The directory may not actually exist, in which case you would need
1539--   to create it with file mode @700@ (i.e. only accessible by the owner).
1540--
1541--   As of 1.3.5.0, the environment variable is ignored if set to a relative
1542--   path, per revised XDG Base Directory Specification.  See
1543--   <https://github.com/haskell/directory/issues/100 #100>.
1544--
1545--   @since 1.2.3.0
1546getXdgDirectory :: XdgDirectory         -- ^ which special directory
1547                -> FilePath             -- ^ a relative path that is appended
1548                                        --   to the path; if empty, the base
1549                                        --   path is returned
1550                -> IO FilePath
1551getXdgDirectory xdgDir suffix =
1552  (`ioeAddLocation` "getXdgDirectory") `modifyIOError` do
1553    simplify . (</> suffix) <$> do
1554      env <- lookupEnv $ case xdgDir of
1555        XdgData   -> "XDG_DATA_HOME"
1556        XdgConfig -> "XDG_CONFIG_HOME"
1557        XdgCache  -> "XDG_CACHE_HOME"
1558      case env of
1559        Just path | isAbsolute path -> pure path
1560        _                           -> getXdgDirectoryFallback getHomeDirectory xdgDir
1561
1562-- | Similar to 'getXdgDirectory' but retrieves the entire list of XDG
1563-- directories.
1564--
1565-- On Windows, 'XdgDataDirs' and 'XdgConfigDirs' usually map to the same list
1566-- of directories unless overridden.
1567--
1568-- Refer to the docs of 'XdgDirectoryList' for more details.
1569getXdgDirectoryList :: XdgDirectoryList -- ^ which special directory list
1570                    -> IO [FilePath]
1571getXdgDirectoryList xdgDirs =
1572  (`ioeAddLocation` "getXdgDirectoryList") `modifyIOError` do
1573    env <- lookupEnv $ case xdgDirs of
1574      XdgDataDirs   -> "XDG_DATA_DIRS"
1575      XdgConfigDirs -> "XDG_CONFIG_DIRS"
1576    case env of
1577      Nothing    -> getXdgDirectoryListFallback xdgDirs
1578      Just paths -> pure (splitSearchPath paths)
1579
1580-- | Obtain the path to a special directory for storing user-specific
1581--   application data (traditional Unix location).  Newer applications may
1582--   prefer the the XDG-conformant location provided by 'getXdgDirectory'
1583--   (<https://github.com/haskell/directory/issues/6#issuecomment-96521020 migration guide>).
1584--
1585--   The argument is usually the name of the application.  Since it will be
1586--   integrated into the path, it must consist of valid path characters.
1587--
1588--   * On Unix-like systems, the path is @~\/./\<app\>/@.
1589--   * On Windows, the path is @%APPDATA%\//\<app\>/@
1590--     (e.g. @C:\/Users\//\<user\>/\/AppData\/Roaming\//\<app\>/@)
1591--
1592--   Note: the directory may not actually exist, in which case you would need
1593--   to create it.  It is expected that the parent directory exists and is
1594--   writable.
1595--
1596--   The operation may fail with:
1597--
1598--   * @UnsupportedOperation@
1599--     The operating system has no notion of application-specific data
1600--     directory.
1601--
1602--   * 'isDoesNotExistError'
1603--     The home directory for the current user does not exist, or cannot be
1604--     found.
1605--
1606getAppUserDataDirectory :: FilePath     -- ^ a relative path that is appended
1607                                        --   to the path
1608                        -> IO FilePath
1609getAppUserDataDirectory appName = do
1610  (`ioeAddLocation` "getAppUserDataDirectory") `modifyIOError` do
1611    getAppUserDataDirectoryInternal appName
1612
1613{- | Returns the current user's document directory.
1614
1615The directory returned is expected to be writable by the current user,
1616but note that it isn't generally considered good practice to store
1617application-specific data here; use 'getXdgDirectory' or
1618'getAppUserDataDirectory' instead.
1619
1620On Unix, 'getUserDocumentsDirectory' returns the value of the @HOME@
1621environment variable.  On Windows, the system is queried for a
1622suitable path; a typical path might be @C:\/Users\//\<user\>/\/Documents@.
1623
1624The operation may fail with:
1625
1626* @UnsupportedOperation@
1627The operating system has no notion of document directory.
1628
1629* 'isDoesNotExistError'
1630The document directory for the current user does not exist, or
1631cannot be found.
1632-}
1633getUserDocumentsDirectory :: IO FilePath
1634getUserDocumentsDirectory = do
1635  (`ioeAddLocation` "getUserDocumentsDirectory") `modifyIOError` do
1636    getUserDocumentsDirectoryInternal
1637
1638{- | Returns the current directory for temporary files.
1639
1640On Unix, 'getTemporaryDirectory' returns the value of the @TMPDIR@
1641environment variable or \"\/tmp\" if the variable isn\'t defined.
1642On Windows, the function checks for the existence of environment variables in
1643the following order and uses the first path found:
1644
1645*
1646TMP environment variable.
1647
1648*
1649TEMP environment variable.
1650
1651*
1652USERPROFILE environment variable.
1653
1654*
1655The Windows directory
1656
1657The operation may fail with:
1658
1659* @UnsupportedOperation@
1660The operating system has no notion of temporary directory.
1661
1662The function doesn\'t verify whether the path exists.
1663-}
1664getTemporaryDirectory :: IO FilePath
1665getTemporaryDirectory = getTemporaryDirectoryInternal
1666