You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 

866 lines
26 KiB

  1. -- |
  2. -- Module : HPath.IO
  3. -- Copyright : © 2016 Julian Ospald
  4. -- License : BSD3
  5. --
  6. -- Maintainer : Julian Ospald <hasufell@posteo.de>
  7. -- Stability : experimental
  8. -- Portability : portable
  9. --
  10. -- This module provides high-level IO related file operations like
  11. -- copy, delete, move and so on. It only operates on /Path x/ which
  12. -- guarantees us well-typed paths. This is a thin wrapper over
  13. -- System.Posix.RawFilePath.Directory in 'hpath-directory'. It's
  14. -- encouraged to use this module.
  15. --
  16. -- Some of these operations are due to their nature __not atomic__, which
  17. -- means they may do multiple syscalls which form one context. Some
  18. -- of them also have to examine the filetypes explicitly before the
  19. -- syscalls, so a reasonable decision can be made. That means
  20. -- the result is undefined if another process changes that context
  21. -- while the non-atomic operation is still happening. However, where
  22. -- possible, as few syscalls as possible are used and the underlying
  23. -- exception handling is kept.
  24. --
  25. -- Note: `BlockDevice`, `CharacterDevice`, `NamedPipe` and `Socket`
  26. -- are ignored by some of the more high-level functions (like `easyCopy`).
  27. -- For other functions (like `copyFile`), the behavior on these file types is
  28. -- unreliable/unsafe. Check the documentation of those functions for details.
  29. {-# LANGUAGE FlexibleContexts #-} -- streamly
  30. {-# LANGUAGE PackageImports #-}
  31. module HPath.IO
  32. (
  33. -- * Types
  34. FileType(..)
  35. , RecursiveErrorMode(..)
  36. , CopyMode(..)
  37. -- * File copying
  38. , copyDirRecursive
  39. , recreateSymlink
  40. , copyFile
  41. , easyCopy
  42. -- * File deletion
  43. , deleteFile
  44. , deleteDir
  45. , deleteDirRecursive
  46. , easyDelete
  47. -- * File opening
  48. , openFile
  49. , executeFile
  50. -- * File creation
  51. , createRegularFile
  52. , createDir
  53. , createDirIfMissing
  54. , createDirRecursive
  55. , createSymlink
  56. -- * File renaming/moving
  57. , renameFile
  58. , moveFile
  59. -- * File reading
  60. , readFile
  61. , readFileStream
  62. -- * File writing
  63. , writeFile
  64. , writeFileL
  65. , appendFile
  66. -- * File permissions
  67. , RD.newFilePerms
  68. , RD.newDirPerms
  69. -- * File checks
  70. , doesExist
  71. , doesFileExist
  72. , doesDirectoryExist
  73. , isReadable
  74. , isWritable
  75. , isExecutable
  76. , canOpenDirectory
  77. -- * File times
  78. , getModificationTime
  79. , setModificationTime
  80. , setModificationTimeHiRes
  81. -- * Directory reading
  82. , getDirsFiles
  83. , getDirsFiles'
  84. , getDirsFilesStream
  85. -- * Filetype operations
  86. , getFileType
  87. -- * Others
  88. , canonicalizePath
  89. , toAbs
  90. , withRawFilePath
  91. , withHandle
  92. , module System.Posix.RawFilePath.Directory.Errors
  93. )
  94. where
  95. import Control.Exception.Safe ( MonadMask
  96. , MonadCatch
  97. , bracketOnError
  98. , finally
  99. )
  100. import Control.Monad.Catch ( MonadThrow(..) )
  101. import Data.ByteString ( ByteString )
  102. import Data.Traversable ( for )
  103. import qualified Data.ByteString.Lazy as L
  104. import Data.Time.Clock
  105. import Data.Time.Clock.POSIX ( POSIXTime )
  106. import HPath
  107. import Prelude hiding ( appendFile
  108. , readFile
  109. , writeFile
  110. )
  111. import Streamly
  112. import qualified System.IO as SIO
  113. import System.Posix.Directory.ByteString
  114. ( getWorkingDirectory )
  115. import qualified "unix" System.Posix.IO.ByteString
  116. as SPI
  117. import System.Posix.FD ( openFd )
  118. import System.Posix.RawFilePath.Directory.Errors
  119. import System.Posix.Types ( FileMode
  120. , ProcessID
  121. , EpochTime
  122. )
  123. import qualified System.Posix.RawFilePath.Directory
  124. as RD
  125. import System.Posix.RawFilePath.Directory
  126. ( FileType
  127. , RecursiveErrorMode
  128. , CopyMode
  129. )
  130. --------------------
  131. --[ File Copying ]--
  132. --------------------
  133. -- |Copies the contents of a directory recursively to the given destination, while preserving permissions.
  134. -- Does not follow symbolic links. This behaves more or less like
  135. -- the following, without descending into the destination if it
  136. -- already exists:
  137. --
  138. -- @
  139. -- cp -a \/source\/dir \/destination\/somedir
  140. -- @
  141. --
  142. -- For directory contents, this will ignore any file type that is not
  143. -- `RegularFile`, `SymbolicLink` or `Directory`.
  144. --
  145. -- For `Overwrite` copy mode this does not prune destination directory
  146. -- contents, so the destination might contain more files than the source after
  147. -- the operation has completed. Permissions of existing directories are
  148. -- fixed.
  149. --
  150. -- Safety/reliability concerns:
  151. --
  152. -- * not atomic
  153. -- * examines filetypes explicitly
  154. -- * an explicit check `throwDestinationInSource` is carried out for the
  155. -- top directory for basic sanity, because otherwise we might end up
  156. -- with an infinite copy loop... however, this operation is not
  157. -- carried out recursively (because it's slow)
  158. --
  159. -- Throws:
  160. --
  161. -- - `NoSuchThing` if source directory does not exist
  162. -- - `PermissionDenied` if source directory can't be opened
  163. -- - `SameFile` if source and destination are the same file
  164. -- (`HPathIOException`)
  165. -- - `DestinationInSource` if destination is contained in source
  166. -- (`HPathIOException`)
  167. --
  168. -- Throws in `FailEarly` RecursiveErrorMode only:
  169. --
  170. -- - `PermissionDenied` if output directory is not writable
  171. -- - `InvalidArgument` if source directory is wrong type (symlink)
  172. -- - `InappropriateType` if source directory is wrong type (regular file)
  173. --
  174. -- Throws in `CollectFailures` RecursiveErrorMode only:
  175. --
  176. -- - `RecursiveFailure` if any of the recursive operations that are not
  177. -- part of the top-directory sanity-checks fail (`HPathIOException`)
  178. --
  179. -- Throws in `Strict` CopyMode only:
  180. --
  181. -- - `AlreadyExists` if destination already exists
  182. --
  183. -- Note: may call `getcwd` (only if destination is a relative path)
  184. copyDirRecursive :: Path b1 -- ^ source dir
  185. -> Path b2 -- ^ destination (parent dirs
  186. -- are not automatically created)
  187. -> CopyMode
  188. -> RecursiveErrorMode
  189. -> IO ()
  190. copyDirRecursive (Path fromp) (Path destdirp) cm rm =
  191. RD.copyDirRecursive fromp destdirp cm rm
  192. -- |Recreate a symlink.
  193. --
  194. -- In `Overwrite` copy mode only files and empty directories are deleted.
  195. --
  196. -- Safety/reliability concerns:
  197. --
  198. -- * `Overwrite` mode is inherently non-atomic
  199. --
  200. -- Throws:
  201. --
  202. -- - `InvalidArgument` if source file is wrong type (not a symlink)
  203. -- - `PermissionDenied` if output directory cannot be written to
  204. -- - `PermissionDenied` if source directory cannot be opened
  205. -- - `SameFile` if source and destination are the same file
  206. -- (`HPathIOException`)
  207. --
  208. --
  209. -- Throws in `Strict` mode only:
  210. --
  211. -- - `AlreadyExists` if destination already exists
  212. --
  213. -- Throws in `Overwrite` mode only:
  214. --
  215. -- - `UnsatisfiedConstraints` if destination file is non-empty directory
  216. --
  217. -- Notes:
  218. --
  219. -- - calls `symlink`
  220. -- - calls `getcwd` in Overwrite mode (if destination is a relative path)
  221. recreateSymlink :: Path b1 -- ^ the old symlink file
  222. -> Path b2 -- ^ destination file
  223. -> CopyMode
  224. -> IO ()
  225. recreateSymlink (Path symsourceBS) (Path newsymBS) cm =
  226. RD.recreateSymlink symsourceBS newsymBS cm
  227. -- |Copies the given regular file to the given destination.
  228. -- Neither follows symbolic links, nor accepts them.
  229. -- For "copying" symbolic links, use `recreateSymlink` instead.
  230. --
  231. -- Note that this is still sort of a low-level function and doesn't
  232. -- examine file types. For a more high-level version, use `easyCopy`
  233. -- instead.
  234. --
  235. -- In `Overwrite` copy mode only overwrites actual files, not directories.
  236. -- In `Strict` mode the destination file must not exist.
  237. --
  238. -- Safety/reliability concerns:
  239. --
  240. -- * `Overwrite` mode is not atomic
  241. -- * when used on `CharacterDevice`, reads the "contents" and copies
  242. -- them to a regular file, which might take indefinitely
  243. -- * when used on `BlockDevice`, may either read the "contents"
  244. -- and copy them to a regular file (potentially hanging indefinitely)
  245. -- or may create a regular empty destination file
  246. -- * when used on `NamedPipe`, will hang indefinitely
  247. --
  248. -- Throws:
  249. --
  250. -- - `NoSuchThing` if source file does not exist
  251. -- - `NoSuchThing` if source file is a a `Socket`
  252. -- - `PermissionDenied` if output directory is not writable
  253. -- - `PermissionDenied` if source directory can't be opened
  254. -- - `InvalidArgument` if source file is wrong type (symlink or directory)
  255. -- - `SameFile` if source and destination are the same file
  256. -- (`HPathIOException`)
  257. --
  258. -- Throws in `Strict` mode only:
  259. --
  260. -- - `AlreadyExists` if destination already exists
  261. --
  262. -- Notes:
  263. --
  264. -- - may call `getcwd` in Overwrite mode (if destination is a relative path)
  265. copyFile :: Path b1 -- ^ source file
  266. -> Path b2 -- ^ destination file
  267. -> CopyMode
  268. -> IO ()
  269. copyFile (Path from) (Path to) cm = RD.copyFile from to cm
  270. -- |Copies a regular file, directory or symbolic link. In case of a
  271. -- symbolic link it is just recreated, even if it points to a directory.
  272. -- Any other file type is ignored.
  273. --
  274. -- Safety/reliability concerns:
  275. --
  276. -- * examines filetypes explicitly
  277. -- * calls `copyDirRecursive` for directories
  278. --
  279. -- Note: may call `getcwd` in Overwrite mode (if destination is a relative path)
  280. easyCopy :: Path b1 -> Path b2 -> CopyMode -> RecursiveErrorMode -> IO ()
  281. easyCopy (Path from) (Path to) cm rm = RD.easyCopy from to cm rm
  282. ---------------------
  283. --[ File Deletion ]--
  284. ---------------------
  285. -- |Deletes the given file. Raises `eISDIR`
  286. -- if run on a directory. Does not follow symbolic links.
  287. --
  288. -- Throws:
  289. --
  290. -- - `InappropriateType` for wrong file type (directory)
  291. -- - `NoSuchThing` if the file does not exist
  292. -- - `PermissionDenied` if the directory cannot be read
  293. deleteFile :: Path b -> IO ()
  294. deleteFile (Path p) = RD.deleteFile p
  295. -- |Deletes the given directory, which must be empty, never symlinks.
  296. --
  297. -- Throws:
  298. --
  299. -- - `InappropriateType` for wrong file type (symlink to directory)
  300. -- - `InappropriateType` for wrong file type (regular file)
  301. -- - `NoSuchThing` if directory does not exist
  302. -- - `UnsatisfiedConstraints` if directory is not empty
  303. -- - `PermissionDenied` if we can't open or write to parent directory
  304. --
  305. -- Notes: calls `rmdir`
  306. deleteDir :: Path b -> IO ()
  307. deleteDir (Path p) = RD.deleteDir p
  308. -- |Deletes the given directory recursively. Does not follow symbolic
  309. -- links. Tries `deleteDir` first before attemtping a recursive
  310. -- deletion.
  311. --
  312. -- On directory contents this behaves like `easyDelete`
  313. -- and thus will ignore any file type that is not `RegularFile`,
  314. -- `SymbolicLink` or `Directory`.
  315. --
  316. -- Safety/reliability concerns:
  317. --
  318. -- * not atomic
  319. -- * examines filetypes explicitly
  320. --
  321. -- Throws:
  322. --
  323. -- - `InappropriateType` for wrong file type (symlink to directory)
  324. -- - `InappropriateType` for wrong file type (regular file)
  325. -- - `NoSuchThing` if directory does not exist
  326. -- - `PermissionDenied` if we can't open or write to parent directory
  327. deleteDirRecursive :: Path b -> IO ()
  328. deleteDirRecursive (Path p) = RD.deleteDirRecursive p
  329. -- |Deletes a file, directory or symlink.
  330. -- In case of directory, performs recursive deletion. In case of
  331. -- a symlink, the symlink file is deleted.
  332. -- Any other file type is ignored.
  333. --
  334. -- Safety/reliability concerns:
  335. --
  336. -- * examines filetypes explicitly
  337. -- * calls `deleteDirRecursive` for directories
  338. easyDelete :: Path b -> IO ()
  339. easyDelete (Path p) = RD.easyDelete p
  340. --------------------
  341. --[ File Opening ]--
  342. --------------------
  343. -- |Opens a file appropriately by invoking xdg-open. The file type
  344. -- is not checked. This forks a process.
  345. openFile :: Path b -> IO ProcessID
  346. openFile (Path fp) = RD.openFile fp
  347. -- |Executes a program with the given arguments. This forks a process.
  348. executeFile :: Path b -- ^ program
  349. -> [ByteString] -- ^ arguments
  350. -> IO ProcessID
  351. executeFile (Path fp) args = RD.executeFile fp args
  352. ---------------------
  353. --[ File Creation ]--
  354. ---------------------
  355. -- |Create an empty regular file at the given directory with the given
  356. -- filename.
  357. --
  358. -- Throws:
  359. --
  360. -- - `PermissionDenied` if output directory cannot be written to
  361. -- - `AlreadyExists` if destination already exists
  362. -- - `NoSuchThing` if any of the parent components of the path
  363. -- do not exist
  364. createRegularFile :: FileMode -> Path b -> IO ()
  365. createRegularFile fm (Path destBS) = RD.createRegularFile fm destBS
  366. -- |Create an empty directory at the given directory with the given filename.
  367. --
  368. -- Throws:
  369. --
  370. -- - `PermissionDenied` if output directory cannot be written to
  371. -- - `AlreadyExists` if destination already exists
  372. -- - `NoSuchThing` if any of the parent components of the path
  373. -- do not exist
  374. createDir :: FileMode -> Path b -> IO ()
  375. createDir fm (Path destBS) = RD.createDir fm destBS
  376. -- |Create an empty directory at the given directory with the given filename.
  377. --
  378. -- Throws:
  379. --
  380. -- - `PermissionDenied` if output directory cannot be written to
  381. -- - `NoSuchThing` if any of the parent components of the path
  382. -- do not exist
  383. createDirIfMissing :: FileMode -> Path b -> IO ()
  384. createDirIfMissing fm (Path destBS) = RD.createDirIfMissing fm destBS
  385. -- |Create an empty directory at the given directory with the given filename.
  386. -- All parent directories are created with the same filemode. This
  387. -- basically behaves like:
  388. --
  389. -- @
  390. -- mkdir -p \/some\/dir
  391. -- @
  392. --
  393. -- Safety/reliability concerns:
  394. --
  395. -- * not atomic
  396. --
  397. -- Throws:
  398. --
  399. -- - `PermissionDenied` if any part of the path components do not
  400. -- exist and cannot be written to
  401. -- - `AlreadyExists` if destination already exists and
  402. -- is *not* a directory
  403. --
  404. -- Note: calls `getcwd` if the input path is a relative path
  405. createDirRecursive :: FileMode -> Path b -> IO ()
  406. createDirRecursive fm (Path p) = RD.createDirRecursive fm p
  407. -- |Create a symlink.
  408. --
  409. -- Throws:
  410. --
  411. -- - `PermissionDenied` if output directory cannot be written to
  412. -- - `AlreadyExists` if destination file already exists
  413. -- - `NoSuchThing` if any of the parent components of the path
  414. -- do not exist
  415. --
  416. -- Note: calls `symlink`
  417. createSymlink :: Path b -- ^ destination file
  418. -> ByteString -- ^ path the symlink points to
  419. -> IO ()
  420. createSymlink (Path destBS) sympoint = RD.createSymlink destBS sympoint
  421. ----------------------------
  422. --[ File Renaming/Moving ]--
  423. ----------------------------
  424. -- |Rename a given file with the provided filename. Destination and source
  425. -- must be on the same device, otherwise `eXDEV` will be raised.
  426. --
  427. -- Does not follow symbolic links, but renames the symbolic link file.
  428. --
  429. -- Safety/reliability concerns:
  430. --
  431. -- * has a separate set of exception handling, apart from the syscall
  432. --
  433. -- Throws:
  434. --
  435. -- - `NoSuchThing` if source file does not exist
  436. -- - `PermissionDenied` if output directory cannot be written to
  437. -- - `PermissionDenied` if source directory cannot be opened
  438. -- - `UnsupportedOperation` if source and destination are on different
  439. -- devices
  440. -- - `AlreadyExists` if destination already exists
  441. -- - `SameFile` if destination and source are the same file
  442. -- (`HPathIOException`)
  443. --
  444. -- Note: calls `rename` (but does not allow to rename over existing files)
  445. renameFile :: Path b1 -> Path b2 -> IO ()
  446. renameFile (Path from) (Path to) = RD.renameFile from to
  447. -- |Move a file. This also works across devices by copy-delete fallback.
  448. -- And also works on directories.
  449. --
  450. -- Does not follow symbolic links, but renames the symbolic link file.
  451. --
  452. --
  453. -- Safety/reliability concerns:
  454. --
  455. -- * `Overwrite` mode is not atomic
  456. -- * copy-delete fallback is inherently non-atomic
  457. -- * since this function calls `easyCopy` and `easyDelete` as a fallback
  458. -- to `renameFile`, file types that are not `RegularFile`, `SymbolicLink`
  459. -- or `Directory` may be ignored
  460. -- * for `Overwrite` mode, the destination will be deleted (not recursively)
  461. -- before moving
  462. --
  463. -- Throws:
  464. --
  465. -- - `NoSuchThing` if source file does not exist
  466. -- - `PermissionDenied` if output directory cannot be written to
  467. -- - `PermissionDenied` if source directory cannot be opened
  468. -- - `SameFile` if destination and source are the same file
  469. -- (`HPathIOException`)
  470. --
  471. -- Throws in `Strict` mode only:
  472. --
  473. -- - `AlreadyExists` if destination already exists
  474. --
  475. -- Notes:
  476. --
  477. -- - calls `rename` (but does not allow to rename over existing files)
  478. -- - calls `getcwd` in Overwrite mode if destination is a relative path
  479. moveFile :: Path b1 -- ^ file to move
  480. -> Path b2 -- ^ destination
  481. -> CopyMode
  482. -> IO ()
  483. moveFile (Path from) (Path to) cm = RD.moveFile from to cm
  484. --------------------
  485. --[ File Reading ]--
  486. --------------------
  487. -- |Read the given file *at once* into memory as a lazy ByteString.
  488. -- Symbolic links are followed, no sanity checks on file size
  489. -- or file type. File must exist. Uses Builders under the hood
  490. -- (hence lazy ByteString).
  491. --
  492. -- Safety/reliability concerns:
  493. --
  494. -- * the whole file is read into memory, this doesn't read lazily
  495. --
  496. -- Throws:
  497. --
  498. -- - `InappropriateType` if file is not a regular file or a symlink
  499. -- - `PermissionDenied` if we cannot read the file or the directory
  500. -- containting it
  501. -- - `NoSuchThing` if the file does not exist
  502. readFile :: Path b -> IO L.ByteString
  503. readFile (Path path) = RD.readFile path
  504. -- | Open the given file as a filestream. Once the filestream is
  505. -- exits, the filehandle is cleaned up.
  506. --
  507. -- Throws:
  508. --
  509. -- - `InappropriateType` if file is not a regular file or a symlink
  510. -- - `PermissionDenied` if we cannot read the file or the directory
  511. -- containting it
  512. -- - `NoSuchThing` if the file does not exist
  513. readFileStream :: Path b -> IO (SerialT IO ByteString)
  514. readFileStream (Path fp) = RD.readFileStream fp
  515. --------------------
  516. --[ File Writing ]--
  517. --------------------
  518. -- |Write a given ByteString to a file, truncating the file beforehand.
  519. -- Follows symlinks.
  520. --
  521. -- Throws:
  522. --
  523. -- - `InappropriateType` if file is not a regular file or a symlink
  524. -- - `PermissionDenied` if we cannot read the file or the directory
  525. -- containting it
  526. -- - `NoSuchThing` if the file does not exist
  527. writeFile :: Path b
  528. -> Maybe FileMode -- ^ if Nothing, file must exist
  529. -> ByteString
  530. -> IO ()
  531. writeFile (Path fp) fmode bs = RD.writeFile fp fmode bs
  532. -- |Write a given lazy ByteString to a file, truncating the file beforehand.
  533. -- Follows symlinks.
  534. --
  535. -- Throws:
  536. --
  537. -- - `InappropriateType` if file is not a regular file or a symlink
  538. -- - `PermissionDenied` if we cannot read the file or the directory
  539. -- containting it
  540. -- - `NoSuchThing` if the file does not exist
  541. --
  542. -- Note: uses streamly under the hood
  543. writeFileL :: Path b
  544. -> Maybe FileMode -- ^ if Nothing, file must exist
  545. -> L.ByteString
  546. -> IO ()
  547. writeFileL (Path fp) fmode lbs = RD.writeFileL fp fmode lbs
  548. -- |Append a given ByteString to a file.
  549. -- The file must exist. Follows symlinks.
  550. --
  551. -- Throws:
  552. --
  553. -- - `InappropriateType` if file is not a regular file or a symlink
  554. -- - `PermissionDenied` if we cannot read the file or the directory
  555. -- containting it
  556. -- - `NoSuchThing` if the file does not exist
  557. appendFile :: Path b -> ByteString -> IO ()
  558. appendFile (Path fp) bs = RD.appendFile fp bs
  559. -------------------
  560. --[ File checks ]--
  561. -------------------
  562. -- |Checks if the given file exists.
  563. -- Does not follow symlinks.
  564. --
  565. -- Only eNOENT is catched (and returns False).
  566. doesExist :: Path b -> IO Bool
  567. doesExist (Path bs) = RD.doesExist bs
  568. -- |Checks if the given file exists and is not a directory.
  569. -- Does not follow symlinks.
  570. --
  571. -- Only eNOENT is catched (and returns False).
  572. doesFileExist :: Path b -> IO Bool
  573. doesFileExist (Path bs) = RD.doesFileExist bs
  574. -- |Checks if the given file exists and is a directory.
  575. -- Does not follow symlinks.
  576. --
  577. -- Only eNOENT is catched (and returns False).
  578. doesDirectoryExist :: Path b -> IO Bool
  579. doesDirectoryExist (Path bs) = RD.doesDirectoryExist bs
  580. -- |Checks whether a file or folder is readable.
  581. --
  582. -- Only eACCES, eROFS, eTXTBSY, ePERM are catched (and return False).
  583. --
  584. -- Throws:
  585. --
  586. -- - `NoSuchThing` if the file does not exist
  587. isReadable :: Path b -> IO Bool
  588. isReadable (Path bs) = RD.isReadable bs
  589. -- |Checks whether a file or folder is writable.
  590. --
  591. -- Only eACCES, eROFS, eTXTBSY, ePERM are catched (and return False).
  592. --
  593. -- Throws:
  594. --
  595. -- - `NoSuchThing` if the file does not exist
  596. isWritable :: Path b -> IO Bool
  597. isWritable (Path bs) = RD.isWritable bs
  598. -- |Checks whether a file or folder is executable.
  599. --
  600. -- Only eACCES, eROFS, eTXTBSY, ePERM are catched (and return False).
  601. --
  602. -- Throws:
  603. --
  604. -- - `NoSuchThing` if the file does not exist
  605. isExecutable :: Path b -> IO Bool
  606. isExecutable (Path bs) = RD.isExecutable bs
  607. -- |Checks whether the directory at the given path exists and can be
  608. -- opened. This invokes `openDirStream` which follows symlinks.
  609. canOpenDirectory :: Path b -> IO Bool
  610. canOpenDirectory (Path bs) = RD.canOpenDirectory bs
  611. ------------------
  612. --[ File times ]--
  613. ------------------
  614. getModificationTime :: Path b -> IO UTCTime
  615. getModificationTime (Path bs) = RD.getModificationTime bs
  616. setModificationTime :: Path b -> EpochTime -> IO ()
  617. setModificationTime (Path bs) t = RD.setModificationTime bs t
  618. setModificationTimeHiRes :: Path b -> POSIXTime -> IO ()
  619. setModificationTimeHiRes (Path bs) t = RD.setModificationTimeHiRes bs t
  620. -------------------------
  621. --[ Directory reading ]--
  622. -------------------------
  623. -- |Gets all filenames of the given directory. This excludes "." and "..".
  624. -- This version does not follow symbolic links.
  625. --
  626. -- The contents are not sorted and there is no guarantee on the ordering.
  627. --
  628. -- Throws:
  629. --
  630. -- - `NoSuchThing` if directory does not exist
  631. -- - `InappropriateType` if file type is wrong (file)
  632. -- - `InappropriateType` if file type is wrong (symlink to file)
  633. -- - `InappropriateType` if file type is wrong (symlink to dir)
  634. -- - `PermissionDenied` if directory cannot be opened
  635. -- - `PathParseException` if a filename could not be parsed (should never happen)
  636. getDirsFiles :: Path b -- ^ dir to read
  637. -> IO [Path b]
  638. getDirsFiles p = do
  639. contents <- getDirsFiles' p
  640. pure $ fmap (p </>) contents
  641. -- | Like 'getDirsFiles', but returns the filename only, instead
  642. -- of prepending the base path.
  643. getDirsFiles' :: Path b -- ^ dir to read
  644. -> IO [Path Rel]
  645. getDirsFiles' (Path fp) = do
  646. rawContents <- RD.getDirsFiles' fp
  647. for rawContents $ \r -> parseRel r
  648. -- | Like 'getDirsFiles'', except returning a Stream.
  649. getDirsFilesStream :: (MonadCatch m, MonadAsync m, MonadMask m)
  650. => Path b
  651. -> IO (SerialT m (Path Rel))
  652. getDirsFilesStream (Path fp) = do
  653. s <- RD.getDirsFilesStream fp
  654. pure (s >>= parseRel)
  655. ---------------------------
  656. --[ FileType operations ]--
  657. ---------------------------
  658. -- |Get the file type of the file located at the given path. Does
  659. -- not follow symbolic links.
  660. --
  661. -- Throws:
  662. --
  663. -- - `NoSuchThing` if the file does not exist
  664. -- - `PermissionDenied` if any part of the path is not accessible
  665. getFileType :: Path b -> IO FileType
  666. getFileType (Path fp) = RD.getFileType fp
  667. --------------
  668. --[ Others ]--
  669. --------------
  670. -- |Applies `realpath` on the given path.
  671. --
  672. -- Throws:
  673. --
  674. -- - `NoSuchThing` if the file at the given path does not exist
  675. -- - `NoSuchThing` if the symlink is broken
  676. -- - `PathParseException` if realpath does not return an absolute path
  677. canonicalizePath :: Path b -> IO (Path Abs)
  678. canonicalizePath (Path l) = do
  679. nl <- RD.canonicalizePath l
  680. parseAbs nl
  681. -- |Converts any path to an absolute path.
  682. -- This is done in the following way:
  683. --
  684. -- - if the path is already an absolute one, just return it
  685. -- - if it's a relative path, prepend the current directory to it
  686. toAbs :: Path b -> IO (Path Abs)
  687. toAbs (Path bs) = do
  688. let mabs = parseAbs bs :: Maybe (Path Abs)
  689. case mabs of
  690. Just a -> return a
  691. Nothing -> do
  692. cwd <- getWorkingDirectory >>= parseAbs
  693. r <- parseRel bs -- we know it must be relative now
  694. return $ cwd </> r
  695. -- | Helper function to use the Path library without
  696. -- buying into the Path type too much. This uses 'parseAny'
  697. -- under the hood and may throw `PathParseException`.
  698. --
  699. -- Throws:
  700. --
  701. -- - `PathParseException` if the bytestring could neither be parsed as
  702. -- relative or absolute Path
  703. withRawFilePath :: MonadThrow m
  704. => ByteString
  705. -> (Either (Path Abs) (Path Rel) -> m b)
  706. -> m b
  707. withRawFilePath bs action = do
  708. path <- parseAny bs
  709. action path
  710. -- | Convenience function to open the path as a handle.
  711. --
  712. -- If the file does not exist, it will be created with 'newFilePerms'.
  713. --
  714. -- Throws:
  715. --
  716. -- - `PathParseException` if the bytestring could neither be parsed as
  717. -- relative or absolute Path
  718. withHandle :: ByteString
  719. -> SPI.OpenMode
  720. -> ((SIO.Handle, Either (Path Abs) (Path Rel)) -> IO a)
  721. -> IO a
  722. withHandle bs mode action = do
  723. path <- parseAny bs
  724. handle <-
  725. bracketOnError (openFd bs mode [] (Just RD.newFilePerms)) (SPI.closeFd)
  726. $ SPI.fdToHandle
  727. finally (action (handle, path)) (SIO.hClose handle)