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.
 
 
 
 

1215 lines
39 KiB

  1. -- |
  2. -- Module : System.Posix.RawFilePath.Directory
  3. -- Copyright : © 2020 Julian Ospald
  4. -- License : BSD3
  5. --
  6. -- Maintainer : Julian Ospald <hasufell@posteo.de>
  7. -- Stability : experimental
  8. -- Portability : portable
  9. --
  10. -- This module provides IO related file operations like
  11. -- copy, delete, move and so on, similar to the 'directory' package.
  12. --
  13. -- Some of these operations are due to their nature __not atomic__, which
  14. -- means they may do multiple syscalls which form one context. Some
  15. -- of them also have to examine the filetypes explicitly before the
  16. -- syscalls, so a reasonable decision can be made. That means
  17. -- the result is undefined if another process changes that context
  18. -- while the non-atomic operation is still happening. However, where
  19. -- possible, as few syscalls as possible are used and the underlying
  20. -- exception handling is kept.
  21. --
  22. -- Note: `BlockDevice`, `CharacterDevice`, `NamedPipe` and `Socket`
  23. -- are ignored by some of the more high-level functions (like `easyCopy`).
  24. -- For other functions (like `copyFile`), the behavior on these file types is
  25. -- unreliable/unsafe. Check the documentation of those functions for details.
  26. --
  27. -- Import as:
  28. -- > import System.Posix.RawFilePath.Directory
  29. {-# LANGUAGE CPP #-}
  30. module System.Posix.RawFilePath.Directory
  31. (
  32. -- * Types
  33. FileType(..)
  34. , RecursiveErrorMode(..)
  35. , CopyMode(..)
  36. -- * File copying
  37. , copyDirRecursive
  38. , recreateSymlink
  39. , copyFile
  40. , easyCopy
  41. -- * File deletion
  42. , deleteFile
  43. , deleteDir
  44. , deleteDirRecursive
  45. , easyDelete
  46. -- * File opening
  47. , openFile
  48. , executeFile
  49. -- * File creation
  50. , createRegularFile
  51. , createDir
  52. , createDirIfMissing
  53. , createDirRecursive
  54. , createSymlink
  55. -- * File renaming/moving
  56. , renameFile
  57. , moveFile
  58. -- * File reading
  59. , readFile
  60. , readFileStream
  61. -- * File writing
  62. , writeFile
  63. , writeFileL
  64. , appendFile
  65. -- * File permissions
  66. , newFilePerms
  67. , newDirPerms
  68. -- * File checks
  69. , doesExist
  70. , doesFileExist
  71. , doesDirectoryExist
  72. , isReadable
  73. , isWritable
  74. , isExecutable
  75. , canOpenDirectory
  76. -- * File times
  77. , getModificationTime
  78. , setModificationTime
  79. , setModificationTimeHiRes
  80. -- * Directory reading
  81. , getDirsFiles
  82. , getDirsFiles'
  83. -- * Filetype operations
  84. , getFileType
  85. -- * Others
  86. , canonicalizePath
  87. , toAbs
  88. )
  89. where
  90. import Control.Applicative ( (<$>) )
  91. import Control.Exception.Safe ( IOException
  92. , bracket
  93. , bracketOnError
  94. , throwIO
  95. , finally
  96. )
  97. import Control.Monad ( unless
  98. , void
  99. , when
  100. )
  101. import Control.Monad.Catch ( MonadThrow(..) )
  102. import Control.Monad.Fail ( MonadFail )
  103. import Control.Monad.IfElse ( unlessM )
  104. import qualified Data.ByteString as BS
  105. import Data.ByteString ( ByteString )
  106. import Data.Traversable ( for )
  107. import Data.Functor ( ($>) )
  108. #if MIN_VERSION_bytestring(0,10,2)
  109. import Data.ByteString.Builder
  110. #else
  111. import Data.ByteString.Lazy.Builder
  112. #endif
  113. ( Builder
  114. , byteString
  115. , toLazyByteString
  116. )
  117. import qualified Data.ByteString.Lazy as L
  118. import Data.ByteString.Unsafe ( unsafePackCStringFinalizer )
  119. import qualified Data.ByteString.UTF8 as UTF8
  120. import Data.Foldable ( for_ )
  121. import Data.IORef ( IORef
  122. , modifyIORef
  123. , newIORef
  124. , readIORef
  125. )
  126. import Data.Maybe ( catMaybes )
  127. import Data.Monoid ( (<>)
  128. , mempty
  129. )
  130. import Data.Time.Clock
  131. import Data.Time.Clock.POSIX ( getPOSIXTime
  132. , posixSecondsToUTCTime
  133. , POSIXTime
  134. )
  135. import Data.Word ( Word8 )
  136. import Foreign.C.Error ( eEXIST
  137. , eNOENT
  138. , eNOTEMPTY
  139. , eXDEV
  140. , getErrno
  141. )
  142. import Foreign.C.Types ( CSize )
  143. import Foreign.Marshal.Alloc ( allocaBytes )
  144. import Foreign.Ptr ( Ptr )
  145. import GHC.IO.Exception ( IOErrorType(..) )
  146. import Prelude hiding ( appendFile
  147. , readFile
  148. , writeFile
  149. )
  150. import Streamly
  151. import Streamly.External.ByteString
  152. import qualified Streamly.External.ByteString.Lazy
  153. as SL
  154. import qualified Streamly.Data.Fold as FL
  155. import Streamly.Memory.Array
  156. import qualified Streamly.FileSystem.Handle as FH
  157. import qualified Streamly.Internal.Data.Unfold as SU
  158. import qualified Streamly.Internal.FileSystem.Handle
  159. as IFH
  160. import qualified Streamly.Internal.Memory.ArrayStream
  161. as AS
  162. import qualified Streamly.Prelude as S
  163. import qualified System.IO as SIO
  164. import System.IO.Error ( catchIOError
  165. , ioeGetErrorType
  166. )
  167. import System.Posix.FilePath
  168. import System.Posix.ByteString ( exclusive )
  169. import System.Posix.RawFilePath.Directory.Errors
  170. import System.Posix.Directory.ByteString
  171. ( createDirectory
  172. , closeDirStream
  173. , getWorkingDirectory
  174. , openDirStream
  175. , removeDirectory
  176. )
  177. import System.Posix.RawFilePath.Directory.Traversals
  178. ( getDirectoryContents' )
  179. import System.Posix.Files.ByteString ( createSymbolicLink
  180. , fileAccess
  181. , fileMode
  182. , getFdStatus
  183. , groupExecuteMode
  184. , groupReadMode
  185. , groupWriteMode
  186. , otherExecuteMode
  187. , otherReadMode
  188. , otherWriteMode
  189. , ownerModes
  190. , ownerReadMode
  191. , ownerWriteMode
  192. , readSymbolicLink
  193. , removeLink
  194. , rename
  195. , setFileMode
  196. , unionFileModes
  197. )
  198. import qualified System.Posix.FilePath as FP
  199. import qualified System.Posix.Files.ByteString as PF
  200. import qualified "unix" System.Posix.IO.ByteString
  201. as SPI
  202. import qualified "unix-bytestring" System.Posix.IO.ByteString
  203. as SPB
  204. import System.Posix.FD ( openFd )
  205. import qualified System.Posix.RawFilePath.Directory.Traversals
  206. as SPDT
  207. import qualified System.Posix.Foreign as SPDF
  208. import qualified System.Posix.Process.ByteString
  209. as SPP
  210. import System.Posix.Types ( FileMode
  211. , ProcessID
  212. , Fd
  213. , EpochTime
  214. )
  215. import System.Posix.Time
  216. -------------
  217. --[ Types ]--
  218. -------------
  219. data FileType = Directory
  220. | RegularFile
  221. | SymbolicLink
  222. | BlockDevice
  223. | CharacterDevice
  224. | NamedPipe
  225. | Socket
  226. deriving (Eq, Show)
  227. -- |The error mode for recursive operations.
  228. --
  229. -- On `FailEarly` the whole operation fails immediately if any of the
  230. -- recursive sub-operations fail, which is sort of the default
  231. -- for IO operations.
  232. --
  233. -- On `CollectFailures` skips errors in the recursion and keeps on recursing.
  234. -- However all errors are collected in the `RecursiveFailure` error type,
  235. -- which is raised finally if there was any error. Also note that
  236. -- `RecursiveFailure` does not give any guarantees on the ordering
  237. -- of the collected exceptions.
  238. data RecursiveErrorMode = FailEarly
  239. | CollectFailures
  240. -- |The mode for copy and file moves.
  241. -- Overwrite mode is usually not very well defined, but is a convenience
  242. -- shortcut.
  243. data CopyMode = Strict -- ^ fail if any target exists
  244. | Overwrite -- ^ overwrite targets
  245. --------------------
  246. --[ File Copying ]--
  247. --------------------
  248. -- |Copies the contents of a directory recursively to the given destination, while preserving permissions.
  249. -- Does not follow symbolic links. This behaves more or less like
  250. -- the following, without descending into the destination if it
  251. -- already exists:
  252. --
  253. -- @
  254. -- cp -a \/source\/dir \/destination\/somedir
  255. -- @
  256. --
  257. -- For directory contents, this will ignore any file type that is not
  258. -- `RegularFile`, `SymbolicLink` or `Directory`.
  259. --
  260. -- For `Overwrite` copy mode this does not prune destination directory
  261. -- contents, so the destination might contain more files than the source after
  262. -- the operation has completed. Permissions of existing directories are
  263. -- fixed.
  264. --
  265. -- Safety/reliability concerns:
  266. --
  267. -- * not atomic
  268. -- * examines filetypes explicitly
  269. -- * an explicit check `throwDestinationInSource` is carried out for the
  270. -- top directory for basic sanity, because otherwise we might end up
  271. -- with an infinite copy loop... however, this operation is not
  272. -- carried out recursively (because it's slow)
  273. --
  274. -- Throws:
  275. --
  276. -- - `NoSuchThing` if source directory does not exist
  277. -- - `PermissionDenied` if source directory can't be opened
  278. -- - `SameFile` if source and destination are the same file
  279. -- (`HPathIOException`)
  280. -- - `DestinationInSource` if destination is contained in source
  281. -- (`HPathIOException`)
  282. --
  283. -- Throws in `FailEarly` RecursiveErrorMode only:
  284. --
  285. -- - `PermissionDenied` if output directory is not writable
  286. -- - `InvalidArgument` if source directory is wrong type (symlink)
  287. -- - `InappropriateType` if source directory is wrong type (regular file)
  288. --
  289. -- Throws in `CollectFailures` RecursiveErrorMode only:
  290. --
  291. -- - `RecursiveFailure` if any of the recursive operations that are not
  292. -- part of the top-directory sanity-checks fail (`HPathIOException`)
  293. --
  294. -- Throws in `Strict` CopyMode only:
  295. --
  296. -- - `AlreadyExists` if destination already exists
  297. --
  298. -- Note: may call `getcwd` (only if destination is a relative path)
  299. copyDirRecursive :: RawFilePath -- ^ source dir
  300. -> RawFilePath -- ^ destination (parent dirs
  301. -- are not automatically created)
  302. -> CopyMode
  303. -> RecursiveErrorMode
  304. -> IO ()
  305. copyDirRecursive fromp destdirp cm rm = do
  306. ce <- newIORef []
  307. -- for performance, sanity checks are only done for the top dir
  308. throwSameFile fromp destdirp
  309. throwDestinationInSource fromp destdirp
  310. go ce fromp destdirp
  311. collectedExceptions <- readIORef ce
  312. unless (null collectedExceptions)
  313. (throwIO . RecursiveFailure $ collectedExceptions)
  314. where
  315. basename :: MonadFail m => RawFilePath -> m RawFilePath
  316. basename x =
  317. let b = takeBaseName x
  318. in if BS.null b then fail ("No base name" :: String) else pure b
  319. go :: IORef [(RecursiveFailureHint, IOException)]
  320. -> RawFilePath
  321. -> RawFilePath
  322. -> IO ()
  323. go ce from destdir = do
  324. -- NOTE: order is important here, so we don't get empty directories
  325. -- on failure
  326. -- get the contents of the source dir
  327. contents <- handleIOE (ReadContentsFailed from destdir) ce [] $ do
  328. contents <- getDirsFiles from
  329. -- create the destination dir and
  330. -- only return contents if we succeed
  331. handleIOE (CreateDirFailed from destdir) ce [] $ do
  332. fmode' <- PF.fileMode <$> PF.getSymbolicLinkStatus from
  333. case cm of
  334. Strict -> createDirectory destdir fmode'
  335. Overwrite -> catchIOError (createDirectory destdir fmode') $ \e ->
  336. case ioeGetErrorType e of
  337. AlreadyExists -> setFileMode destdir fmode'
  338. _ -> ioError e
  339. return contents
  340. -- NOTE: we can't use `easyCopy` here, because we want to call `go`
  341. -- recursively to skip the top-level sanity checks
  342. -- if reading the contents and creating the destination dir worked,
  343. -- then copy the contents to the destination too
  344. for_ contents $ \f -> do
  345. ftype <- getFileType f
  346. newdest <- (destdir </>) <$> basename f
  347. case ftype of
  348. SymbolicLink ->
  349. handleIOE (RecreateSymlinkFailed f newdest) ce ()
  350. $ recreateSymlink f newdest cm
  351. Directory -> go ce f newdest
  352. RegularFile ->
  353. handleIOE (CopyFileFailed f newdest) ce () $ copyFile f newdest cm
  354. _ -> return ()
  355. -- helper to handle errors for both RecursiveErrorModes and return a
  356. -- default value
  357. handleIOE :: RecursiveFailureHint
  358. -> IORef [(RecursiveFailureHint, IOException)]
  359. -> a
  360. -> IO a
  361. -> IO a
  362. handleIOE hint ce def = case rm of
  363. FailEarly -> handleIOError throwIO
  364. CollectFailures ->
  365. handleIOError (\e -> modifyIORef ce ((hint, e) :) >> return def)
  366. -- |Recreate a symlink.
  367. --
  368. -- In `Overwrite` copy mode only files and empty directories are deleted.
  369. --
  370. -- Safety/reliability concerns:
  371. --
  372. -- * `Overwrite` mode is inherently non-atomic
  373. --
  374. -- Throws:
  375. --
  376. -- - `InvalidArgument` if source file is wrong type (not a symlink)
  377. -- - `PermissionDenied` if output directory cannot be written to
  378. -- - `PermissionDenied` if source directory cannot be opened
  379. -- - `SameFile` if source and destination are the same file
  380. -- (`HPathIOException`)
  381. --
  382. --
  383. -- Throws in `Strict` mode only:
  384. --
  385. -- - `AlreadyExists` if destination already exists
  386. --
  387. -- Throws in `Overwrite` mode only:
  388. --
  389. -- - `UnsatisfiedConstraints` if destination file is non-empty directory
  390. --
  391. -- Notes:
  392. --
  393. -- - calls `symlink`
  394. -- - calls `getcwd` in Overwrite mode (if destination is a relative path)
  395. recreateSymlink :: RawFilePath -- ^ the old symlink file
  396. -> RawFilePath -- ^ destination file
  397. -> CopyMode
  398. -> IO ()
  399. recreateSymlink symsource newsym cm = do
  400. throwSameFile symsource newsym
  401. sympoint <- readSymbolicLink symsource
  402. case cm of
  403. Strict -> return ()
  404. Overwrite -> do
  405. writable <- do
  406. e <- doesExist newsym
  407. if e then isWritable newsym else pure False
  408. isfile <- doesFileExist newsym
  409. isdir <- doesDirectoryExist newsym
  410. when (writable && isfile) (deleteFile newsym)
  411. when (writable && isdir) (deleteDir newsym)
  412. createSymbolicLink sympoint newsym
  413. -- |Copies the given regular file to the given destination.
  414. -- Neither follows symbolic links, nor accepts them.
  415. -- For "copying" symbolic links, use `recreateSymlink` instead.
  416. --
  417. -- Note that this is still sort of a low-level function and doesn't
  418. -- examine file types. For a more high-level version, use `easyCopy`
  419. -- instead.
  420. --
  421. -- In `Overwrite` copy mode only overwrites actual files, not directories.
  422. -- In `Strict` mode the destination file must not exist.
  423. --
  424. -- Safety/reliability concerns:
  425. --
  426. -- * `Overwrite` mode is not atomic
  427. -- * when used on `CharacterDevice`, reads the "contents" and copies
  428. -- them to a regular file, which might take indefinitely
  429. -- * when used on `BlockDevice`, may either read the "contents"
  430. -- and copy them to a regular file (potentially hanging indefinitely)
  431. -- or may create a regular empty destination file
  432. -- * when used on `NamedPipe`, will hang indefinitely
  433. --
  434. -- Throws:
  435. --
  436. -- - `NoSuchThing` if source file does not exist
  437. -- - `NoSuchThing` if source file is a a `Socket`
  438. -- - `PermissionDenied` if output directory is not writable
  439. -- - `PermissionDenied` if source directory can't be opened
  440. -- - `InvalidArgument` if source file is wrong type (symlink or directory)
  441. -- - `SameFile` if source and destination are the same file
  442. -- (`HPathIOException`)
  443. --
  444. -- Throws in `Strict` mode only:
  445. --
  446. -- - `AlreadyExists` if destination already exists
  447. --
  448. -- Notes:
  449. --
  450. -- - may call `getcwd` in Overwrite mode (if destination is a relative path)
  451. copyFile :: RawFilePath -- ^ source file
  452. -> RawFilePath -- ^ destination file
  453. -> CopyMode
  454. -> IO ()
  455. copyFile from to cm = do
  456. throwSameFile from to
  457. bracket
  458. (do
  459. fd <- openFd from SPI.ReadOnly [SPDF.oNofollow] Nothing
  460. handle <- SPI.fdToHandle fd
  461. pure (fd, handle)
  462. )
  463. (\(_, handle) -> SIO.hClose handle)
  464. $ \(fromFd, fH) -> do
  465. sourceFileMode <- System.Posix.Files.ByteString.fileMode
  466. <$> getFdStatus fromFd
  467. let dflags =
  468. [ SPDF.oNofollow
  469. , case cm of
  470. Strict -> SPDF.oExcl
  471. Overwrite -> SPDF.oTrunc
  472. ]
  473. bracketeer
  474. (do
  475. fd <- openFd to SPI.WriteOnly dflags $ Just sourceFileMode
  476. handle <- SPI.fdToHandle fd
  477. pure (fd, handle)
  478. )
  479. (\(_, handle) -> SIO.hClose handle)
  480. (\(_, handle) -> do
  481. SIO.hClose handle
  482. case cm of
  483. -- if we created the file and copying failed, it's
  484. -- safe to clean up
  485. Strict -> deleteFile to
  486. Overwrite -> pure ()
  487. )
  488. $ \(_, tH) -> do
  489. SIO.hSetBinaryMode fH True
  490. SIO.hSetBinaryMode tH True
  491. streamlyCopy (fH, tH)
  492. where
  493. streamlyCopy (fH, tH) =
  494. S.fold (FH.writeChunks tH) $ IFH.toChunksWithBufferOf (256 * 1024) fH
  495. -- |Copies a regular file, directory or symbolic link. In case of a
  496. -- symbolic link it is just recreated, even if it points to a directory.
  497. -- Any other file type is ignored.
  498. --
  499. -- Safety/reliability concerns:
  500. --
  501. -- * examines filetypes explicitly
  502. -- * calls `copyDirRecursive` for directories
  503. --
  504. -- Note: may call `getcwd` in Overwrite mode (if destination is a relative path)
  505. easyCopy :: RawFilePath
  506. -> RawFilePath
  507. -> CopyMode
  508. -> RecursiveErrorMode
  509. -> IO ()
  510. easyCopy from to cm rm = do
  511. ftype <- getFileType from
  512. case ftype of
  513. SymbolicLink -> recreateSymlink from to cm
  514. RegularFile -> copyFile from to cm
  515. Directory -> copyDirRecursive from to cm rm
  516. _ -> return ()
  517. ---------------------
  518. --[ File Deletion ]--
  519. ---------------------
  520. -- |Deletes the given file. Raises `eISDIR`
  521. -- if run on a directory. Does not follow symbolic links.
  522. --
  523. -- Throws:
  524. --
  525. -- - `InappropriateType` for wrong file type (directory)
  526. -- - `NoSuchThing` if the file does not exist
  527. -- - `PermissionDenied` if the directory cannot be read
  528. --
  529. -- Notes: calls `unlink`
  530. deleteFile :: RawFilePath -> IO ()
  531. deleteFile = removeLink
  532. -- |Deletes the given directory, which must be empty, never symlinks.
  533. --
  534. -- Throws:
  535. --
  536. -- - `InappropriateType` for wrong file type (symlink to directory)
  537. -- - `InappropriateType` for wrong file type (regular file)
  538. -- - `NoSuchThing` if directory does not exist
  539. -- - `UnsatisfiedConstraints` if directory is not empty
  540. -- - `PermissionDenied` if we can't open or write to parent directory
  541. --
  542. -- Notes: calls `rmdir`
  543. deleteDir :: RawFilePath -> IO ()
  544. deleteDir = removeDirectory
  545. -- |Deletes the given directory recursively. Does not follow symbolic
  546. -- links. Tries `deleteDir` first before attemtping a recursive
  547. -- deletion.
  548. --
  549. -- On directory contents this behaves like `easyDelete`
  550. -- and thus will ignore any file type that is not `RegularFile`,
  551. -- `SymbolicLink` or `Directory`.
  552. --
  553. -- Safety/reliability concerns:
  554. --
  555. -- * not atomic
  556. -- * examines filetypes explicitly
  557. --
  558. -- Throws:
  559. --
  560. -- - `InappropriateType` for wrong file type (symlink to directory)
  561. -- - `InappropriateType` for wrong file type (regular file)
  562. -- - `NoSuchThing` if directory does not exist
  563. -- - `PermissionDenied` if we can't open or write to parent directory
  564. deleteDirRecursive :: RawFilePath -> IO ()
  565. deleteDirRecursive p = catchErrno [eNOTEMPTY, eEXIST] (deleteDir p) $ do
  566. files <- getDirsFiles p
  567. for_ files $ \file -> do
  568. ftype <- getFileType file
  569. case ftype of
  570. SymbolicLink -> deleteFile file
  571. Directory -> deleteDirRecursive file
  572. RegularFile -> deleteFile file
  573. _ -> return ()
  574. removeDirectory p
  575. -- |Deletes a file, directory or symlink.
  576. -- In case of directory, performs recursive deletion. In case of
  577. -- a symlink, the symlink file is deleted.
  578. -- Any other file type is ignored.
  579. --
  580. -- Safety/reliability concerns:
  581. --
  582. -- * examines filetypes explicitly
  583. -- * calls `deleteDirRecursive` for directories
  584. easyDelete :: RawFilePath -> IO ()
  585. easyDelete p = do
  586. ftype <- getFileType p
  587. case ftype of
  588. SymbolicLink -> deleteFile p
  589. Directory -> deleteDirRecursive p
  590. RegularFile -> deleteFile p
  591. _ -> return ()
  592. --------------------
  593. --[ File Opening ]--
  594. --------------------
  595. -- |Opens a file appropriately by invoking xdg-open. The file type
  596. -- is not checked. This forks a process.
  597. openFile :: RawFilePath -> IO ProcessID
  598. openFile fp = SPP.forkProcess
  599. $ SPP.executeFile (UTF8.fromString "xdg-open") True [fp] Nothing
  600. -- |Executes a program with the given arguments. This forks a process.
  601. executeFile :: RawFilePath -- ^ program
  602. -> [ByteString] -- ^ arguments
  603. -> IO ProcessID
  604. executeFile fp args = SPP.forkProcess $ SPP.executeFile fp True args Nothing
  605. ---------------------
  606. --[ File Creation ]--
  607. ---------------------
  608. -- |Create an empty regular file at the given directory with the given
  609. -- filename.
  610. --
  611. -- Throws:
  612. --
  613. -- - `PermissionDenied` if output directory cannot be written to
  614. -- - `AlreadyExists` if destination already exists
  615. -- - `NoSuchThing` if any of the parent components of the path
  616. -- do not exist
  617. createRegularFile :: FileMode -> RawFilePath -> IO ()
  618. createRegularFile fm destBS = bracket
  619. (SPI.openFd destBS
  620. SPI.WriteOnly
  621. (Just fm)
  622. (SPI.defaultFileFlags { exclusive = True })
  623. )
  624. SPI.closeFd
  625. (\_ -> return ())
  626. -- |Create an empty directory at the given directory with the given filename.
  627. --
  628. -- Throws:
  629. --
  630. -- - `PermissionDenied` if output directory cannot be written to
  631. -- - `AlreadyExists` if destination already exists
  632. -- - `NoSuchThing` if any of the parent components of the path
  633. -- do not exist
  634. createDir :: FileMode -> RawFilePath -> IO ()
  635. createDir fm destBS = createDirectory destBS fm
  636. -- |Create an empty directory at the given directory with the given filename.
  637. --
  638. -- Throws:
  639. --
  640. -- - `PermissionDenied` if output directory cannot be written to
  641. -- - `NoSuchThing` if any of the parent components of the path
  642. -- do not exist
  643. createDirIfMissing :: FileMode -> RawFilePath -> IO ()
  644. createDirIfMissing fm destBS =
  645. hideError AlreadyExists $ createDirectory destBS fm
  646. -- |Create an empty directory at the given directory with the given filename.
  647. -- All parent directories are created with the same filemode. This
  648. -- basically behaves like:
  649. --
  650. -- @
  651. -- mkdir -p \/some\/dir
  652. -- @
  653. --
  654. -- Safety/reliability concerns:
  655. --
  656. -- * not atomic
  657. --
  658. -- Throws:
  659. --
  660. -- - `PermissionDenied` if any part of the path components do not
  661. -- exist and cannot be written to
  662. -- - `AlreadyExists` if destination already exists and
  663. -- is *not* a directory
  664. --
  665. -- Note: calls `getcwd` if the input path is a relative path
  666. createDirRecursive :: FileMode -> RawFilePath -> IO ()
  667. createDirRecursive fm p = go p
  668. where
  669. go :: RawFilePath -> IO ()
  670. go dest = do
  671. catchIOError (createDirectory dest fm) $ \e -> do
  672. errno <- getErrno
  673. case errno of
  674. en
  675. | en == eEXIST
  676. -> unlessM (doesDirectoryExist dest) (ioError e)
  677. | en == eNOENT
  678. -> createDirRecursive fm (takeDirectory dest)
  679. >> createDirectory dest fm
  680. | otherwise
  681. -> ioError e
  682. -- |Create a symlink.
  683. --
  684. -- Throws:
  685. --
  686. -- - `PermissionDenied` if output directory cannot be written to
  687. -- - `AlreadyExists` if destination file already exists
  688. -- - `NoSuchThing` if any of the parent components of the path
  689. -- do not exist
  690. --
  691. -- Note: calls `symlink`
  692. createSymlink :: RawFilePath -- ^ destination file
  693. -> RawFilePath -- ^ path the symlink points to
  694. -> IO ()
  695. createSymlink destBS sympoint = createSymbolicLink sympoint destBS
  696. ----------------------------
  697. --[ File Renaming/Moving ]--
  698. ----------------------------
  699. -- |Rename a given file with the provided filename. Destination and source
  700. -- must be on the same device, otherwise `eXDEV` will be raised.
  701. --
  702. -- Does not follow symbolic links, but renames the symbolic link file.
  703. --
  704. -- Safety/reliability concerns:
  705. --
  706. -- * has a separate set of exception handling, apart from the syscall
  707. --
  708. -- Throws:
  709. --
  710. -- - `NoSuchThing` if source file does not exist
  711. -- - `PermissionDenied` if output directory cannot be written to
  712. -- - `PermissionDenied` if source directory cannot be opened
  713. -- - `UnsupportedOperation` if source and destination are on different
  714. -- devices
  715. -- - `AlreadyExists` if destination already exists
  716. -- - `SameFile` if destination and source are the same file
  717. -- (`HPathIOException`)
  718. --
  719. -- Note: calls `rename` (but does not allow to rename over existing files)
  720. renameFile :: RawFilePath -> RawFilePath -> IO ()
  721. renameFile fromf tof = do
  722. throwSameFile fromf tof
  723. throwFileDoesExist tof
  724. throwDirDoesExist tof
  725. rename fromf tof
  726. -- |Move a file. This also works across devices by copy-delete fallback.
  727. -- And also works on directories.
  728. --
  729. -- Does not follow symbolic links, but renames the symbolic link file.
  730. --
  731. --
  732. -- Safety/reliability concerns:
  733. --
  734. -- * `Overwrite` mode is not atomic
  735. -- * copy-delete fallback is inherently non-atomic
  736. -- * since this function calls `easyCopy` and `easyDelete` as a fallback
  737. -- to `renameFile`, file types that are not `RegularFile`, `SymbolicLink`
  738. -- or `Directory` may be ignored
  739. -- * for `Overwrite` mode, the destination will be deleted (not recursively)
  740. -- before moving
  741. --
  742. -- Throws:
  743. --
  744. -- - `NoSuchThing` if source file does not exist
  745. -- - `PermissionDenied` if output directory cannot be written to
  746. -- - `PermissionDenied` if source directory cannot be opened
  747. -- - `SameFile` if destination and source are the same file
  748. -- (`HPathIOException`)
  749. --
  750. -- Throws in `Strict` mode only:
  751. --
  752. -- - `AlreadyExists` if destination already exists
  753. --
  754. -- Notes:
  755. --
  756. -- - calls `rename` (but does not allow to rename over existing files)
  757. -- - calls `getcwd` in Overwrite mode if destination is a relative path
  758. moveFile :: RawFilePath -- ^ file to move
  759. -> RawFilePath -- ^ destination
  760. -> CopyMode
  761. -> IO ()
  762. moveFile from to cm = do
  763. throwSameFile from to
  764. case cm of
  765. Strict -> catchErrno [eXDEV] (renameFile from to) $ do
  766. easyCopy from to Strict FailEarly
  767. easyDelete from
  768. Overwrite -> do
  769. ft <- getFileType from
  770. writable <- do
  771. e <- doesFileExist to
  772. if e then isWritable to else pure False
  773. case ft of
  774. RegularFile -> do
  775. exists <- doesFileExist to
  776. when (exists && writable) (deleteFile to)
  777. SymbolicLink -> do
  778. exists <- doesFileExist to
  779. when (exists && writable) (deleteFile to)
  780. Directory -> do
  781. exists <- doesDirectoryExist to
  782. when (exists && writable) (deleteDir to)
  783. _ -> return ()
  784. moveFile from to Strict
  785. --------------------
  786. --[ File Reading ]--
  787. --------------------
  788. -- |Read the given file *at once* into memory as a lazy ByteString.
  789. -- Symbolic links are followed, no sanity checks on file size
  790. -- or file type. File must exist. Uses Builders under the hood
  791. -- (hence lazy ByteString).
  792. --
  793. -- Safety/reliability concerns:
  794. --
  795. -- * the whole file is read into memory, this doesn't read lazily
  796. --
  797. -- Throws:
  798. --
  799. -- - `InappropriateType` if file is not a regular file or a symlink
  800. -- - `PermissionDenied` if we cannot read the file or the directory
  801. -- containting it
  802. -- - `NoSuchThing` if the file does not exist
  803. readFile :: RawFilePath -> IO L.ByteString
  804. readFile path = do
  805. stream <- readFileStream path
  806. toLazyByteString <$> S.fold FL.mconcat (fmap byteString stream)
  807. -- | Open the given file as a filestream. Once the filestream is
  808. -- exits, the filehandle is cleaned up.
  809. --
  810. -- Throws:
  811. --
  812. -- - `InappropriateType` if file is not a regular file or a symlink
  813. -- - `PermissionDenied` if we cannot read the file or the directory
  814. -- containting it
  815. -- - `NoSuchThing` if the file does not exist
  816. readFileStream :: RawFilePath -> IO (SerialT IO ByteString)
  817. readFileStream fp = do
  818. fd <- openFd fp SPI.ReadOnly [] Nothing
  819. handle <- SPI.fdToHandle fd
  820. let stream =
  821. fmap fromArray (S.unfold (SU.finally SIO.hClose FH.readChunks) handle)
  822. pure stream
  823. --------------------
  824. --[ File Writing ]--
  825. --------------------
  826. -- |Write a given ByteString to a file, truncating the file beforehand.
  827. -- Follows symlinks.
  828. --
  829. -- Throws:
  830. --
  831. -- - `InappropriateType` if file is not a regular file or a symlink
  832. -- - `PermissionDenied` if we cannot read the file or the directory
  833. -- containting it
  834. -- - `NoSuchThing` if the file does not exist
  835. writeFile :: RawFilePath
  836. -> Maybe FileMode -- ^ if Nothing, file must exist
  837. -> ByteString
  838. -> IO ()
  839. writeFile fp fmode bs =
  840. bracket (openFd fp SPI.WriteOnly [SPDF.oTrunc] fmode) (SPI.closeFd)
  841. $ \fd -> void $ SPB.fdWrite fd bs
  842. -- |Write a given lazy ByteString to a file, truncating the file beforehand.
  843. -- Follows symlinks.
  844. --
  845. -- Throws:
  846. --
  847. -- - `InappropriateType` if file is not a regular file or a symlink
  848. -- - `PermissionDenied` if we cannot read the file or the directory
  849. -- containting it
  850. -- - `NoSuchThing` if the file does not exist
  851. --
  852. -- Note: uses streamly under the hood
  853. writeFileL :: RawFilePath
  854. -> Maybe FileMode -- ^ if Nothing, file must exist
  855. -> L.ByteString
  856. -> IO ()
  857. writeFileL fp fmode lbs = do
  858. handle <-
  859. bracketOnError (openFd fp SPI.WriteOnly [SPDF.oTrunc] fmode) (SPI.closeFd)
  860. $ SPI.fdToHandle
  861. finally (streamlyCopy handle) (SIO.hClose handle)
  862. where streamlyCopy tH = S.fold (FH.writeChunks tH) $ SL.toChunks lbs
  863. -- |Append a given ByteString to a file.
  864. -- The file must exist. Follows symlinks.
  865. --
  866. -- Throws:
  867. --
  868. -- - `InappropriateType` if file is not a regular file or a symlink
  869. -- - `PermissionDenied` if we cannot read the file or the directory
  870. -- containting it
  871. -- - `NoSuchThing` if the file does not exist
  872. appendFile :: RawFilePath -> ByteString -> IO ()
  873. appendFile fp bs =
  874. bracket (openFd fp SPI.WriteOnly [SPDF.oAppend] Nothing) (SPI.closeFd)
  875. $ \fd -> void $ SPB.fdWrite fd bs
  876. -----------------------
  877. --[ File Permissions]--
  878. -----------------------
  879. -- |Default permissions for a new file.
  880. newFilePerms :: FileMode
  881. newFilePerms =
  882. ownerWriteMode
  883. `unionFileModes` ownerReadMode
  884. `unionFileModes` groupWriteMode
  885. `unionFileModes` groupReadMode
  886. `unionFileModes` otherWriteMode
  887. `unionFileModes` otherReadMode
  888. -- |Default permissions for a new directory.
  889. newDirPerms :: FileMode
  890. newDirPerms =
  891. ownerModes
  892. `unionFileModes` groupExecuteMode
  893. `unionFileModes` groupReadMode
  894. `unionFileModes` otherExecuteMode
  895. `unionFileModes` otherReadMode
  896. -------------------
  897. --[ File checks ]--
  898. -------------------
  899. -- |Checks if the given file exists.
  900. -- Does not follow symlinks.
  901. --
  902. -- Only eNOENT is catched (and returns False).
  903. doesExist :: RawFilePath -> IO Bool
  904. doesExist bs =
  905. catchErrno
  906. [eNOENT]
  907. (do
  908. _ <- PF.getSymbolicLinkStatus bs
  909. return $ True
  910. )
  911. $ return False
  912. -- |Checks if the given file exists and is not a directory.
  913. -- Does not follow symlinks.
  914. --
  915. -- Only eNOENT is catched (and returns False).
  916. doesFileExist :: RawFilePath -> IO Bool
  917. doesFileExist bs =
  918. catchErrno
  919. [eNOENT]
  920. (do
  921. fs <- PF.getSymbolicLinkStatus bs
  922. return $ not . PF.isDirectory $ fs
  923. )
  924. $ return False
  925. -- |Checks if the given file exists and is a directory.
  926. -- Does not follow symlinks.
  927. --
  928. -- Only eNOENT is catched (and returns False).
  929. doesDirectoryExist :: RawFilePath -> IO Bool
  930. doesDirectoryExist bs =
  931. catchErrno
  932. [eNOENT]
  933. (do
  934. fs <- PF.getSymbolicLinkStatus bs
  935. return $ PF.isDirectory fs
  936. )
  937. $ return False
  938. -- |Checks whether a file or folder is readable.
  939. --
  940. -- Only eACCES, eROFS, eTXTBSY, ePERM are catched (and return False).
  941. --
  942. -- Throws:
  943. --
  944. -- - `NoSuchThing` if the file does not exist
  945. isReadable :: RawFilePath -> IO Bool
  946. isReadable bs = fileAccess bs True False False
  947. -- |Checks whether a file or folder is writable.
  948. --
  949. -- Only eACCES, eROFS, eTXTBSY, ePERM are catched (and return False).
  950. --
  951. -- Throws:
  952. --
  953. -- - `NoSuchThing` if the file does not exist
  954. isWritable :: RawFilePath -> IO Bool
  955. isWritable bs = fileAccess bs False True False
  956. -- |Checks whether a file or folder is executable.
  957. --
  958. -- Only eACCES, eROFS, eTXTBSY, ePERM are catched (and return False).
  959. --
  960. -- Throws:
  961. --
  962. -- - `NoSuchThing` if the file does not exist
  963. isExecutable :: RawFilePath -> IO Bool
  964. isExecutable bs = fileAccess bs False False True
  965. -- |Checks whether the directory at the given path exists and can be
  966. -- opened. This invokes `openDirStream` which follows symlinks.
  967. canOpenDirectory :: RawFilePath -> IO Bool
  968. canOpenDirectory bs = handleIOError (\_ -> return False) $ do
  969. bracket (openDirStream bs) closeDirStream (\_ -> return ())
  970. return True
  971. ------------------
  972. --[ File times ]--
  973. ------------------
  974. getModificationTime :: RawFilePath -> IO UTCTime
  975. getModificationTime bs = do
  976. fs <- PF.getFileStatus bs
  977. pure $ posixSecondsToUTCTime $ PF.modificationTimeHiRes fs
  978. setModificationTime :: RawFilePath -> EpochTime -> IO ()
  979. setModificationTime bs t = do
  980. -- TODO: setFileTimes doesn't allow to pass NULL to utime
  981. ctime <- epochTime
  982. PF.setFileTimes bs ctime t
  983. setModificationTimeHiRes :: RawFilePath -> POSIXTime -> IO ()
  984. setModificationTimeHiRes bs t = do
  985. -- TODO: setFileTimesHiRes doesn't allow to pass NULL to utimes
  986. ctime <- getPOSIXTime
  987. PF.setFileTimesHiRes bs ctime t
  988. -------------------------
  989. --[ Directory reading ]--
  990. -------------------------
  991. -- |Gets all filenames of the given directory. This excludes "." and "..".
  992. -- This version does not follow symbolic links.
  993. --
  994. -- The contents are not sorted and there is no guarantee on the ordering.
  995. --
  996. -- Throws:
  997. --
  998. -- - `NoSuchThing` if directory does not exist
  999. -- - `InappropriateType` if file type is wrong (file)
  1000. -- - `InappropriateType` if file type is wrong (symlink to file)
  1001. -- - `InappropriateType` if file type is wrong (symlink to dir)
  1002. -- - `PermissionDenied` if directory cannot be opened
  1003. getDirsFiles :: RawFilePath -- ^ dir to read
  1004. -> IO [RawFilePath]
  1005. getDirsFiles p = do
  1006. contents <- getDirsFiles' p
  1007. pure $ fmap (p </>) contents
  1008. -- | Like 'getDirsFiles', but returns the filename only, instead
  1009. -- of prepending the base path.
  1010. getDirsFiles' :: RawFilePath -- ^ dir to read
  1011. -> IO [RawFilePath]
  1012. getDirsFiles' fp = do
  1013. fd <- openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing
  1014. rawContents <- getDirectoryContents' fd
  1015. fmap catMaybes $ for rawContents $ \(_, f) ->
  1016. if FP.isSpecialDirectoryEntry f then pure Nothing else pure $ Just f
  1017. ---------------------------
  1018. --[ FileType operations ]--
  1019. ---------------------------
  1020. -- |Get the file type of the file located at the given path. Does
  1021. -- not follow symbolic links.
  1022. --
  1023. -- Throws:
  1024. --
  1025. -- - `NoSuchThing` if the file does not exist
  1026. -- - `PermissionDenied` if any part of the path is not accessible
  1027. getFileType :: RawFilePath -> IO FileType
  1028. getFileType fp = do
  1029. fs <- PF.getSymbolicLinkStatus fp
  1030. decide fs
  1031. where
  1032. decide fs | PF.isDirectory fs = return Directory
  1033. | PF.isRegularFile fs = return RegularFile
  1034. | PF.isSymbolicLink fs = return SymbolicLink
  1035. | PF.isBlockDevice fs = return BlockDevice
  1036. | PF.isCharacterDevice fs = return CharacterDevice
  1037. | PF.isNamedPipe fs = return NamedPipe
  1038. | PF.isSocket fs = return Socket
  1039. | otherwise = ioError $ userError "No filetype?!"
  1040. --------------
  1041. --[ Others ]--
  1042. --------------
  1043. -- |Applies `realpath` on the given path.
  1044. --
  1045. -- Throws:
  1046. --
  1047. -- - `NoSuchThing` if the file at the given path does not exist
  1048. -- - `NoSuchThing` if the symlink is broken
  1049. canonicalizePath :: RawFilePath -> IO RawFilePath
  1050. canonicalizePath = SPDT.realpath
  1051. -- |Converts any path to an absolute path.
  1052. -- This is done in the following way:
  1053. --
  1054. -- - if the path is already an absolute one, just return it
  1055. -- - if it's a relative path, prepend the current directory to it
  1056. toAbs :: RawFilePath -> IO RawFilePath
  1057. toAbs bs = do
  1058. case isAbsolute bs of
  1059. True -> return bs
  1060. False -> do
  1061. cwd <- getWorkingDirectory
  1062. return $ cwd </> bs