2015-12-24 17:25:05 +00:00
|
|
|
{--
|
|
|
|
HSFM, a filemanager written in Haskell.
|
2016-03-30 22:28:23 +00:00
|
|
|
Copyright (C) 2016 Julian Ospald
|
2015-12-24 17:25:05 +00:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or
|
|
|
|
modify it under the terms of the GNU General Public License
|
|
|
|
version 2 as published by the Free Software Foundation.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
|
|
|
--}
|
|
|
|
|
2016-04-04 22:56:36 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2016-04-03 16:19:02 +00:00
|
|
|
{-# LANGUAGE PackageImports #-}
|
2016-05-08 18:14:30 +00:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2016-04-04 22:56:36 +00:00
|
|
|
{-# OPTIONS_HADDOCK ignore-exports #-}
|
2015-12-17 03:42:22 +00:00
|
|
|
|
2016-05-02 18:36:22 +00:00
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
-- |This module provides high-level IO related file operations like
|
|
|
|
-- copy, delete, move and so on. It only operates on `Path Abs` which
|
2016-05-02 18:36:22 +00:00
|
|
|
-- guarantees us well-typed paths which are absolute.
|
|
|
|
--
|
|
|
|
-- Some functions are just path-safe wrappers around
|
|
|
|
-- unix functions, others have stricter exception handling
|
|
|
|
-- and some implement functionality that doesn't have a unix
|
|
|
|
-- counterpart (like `copyDirRecursive`).
|
|
|
|
--
|
|
|
|
-- Some of these operations are due to their nature not _atomic_, which
|
|
|
|
-- means they may do multiple syscalls which form one context. Some
|
|
|
|
-- of them also have to examine the filetypes explicitly before the
|
|
|
|
-- syscalls, so a reasonable decision can be made. That means
|
|
|
|
-- the result is undefined if another process changes that context
|
|
|
|
-- while the non-atomic operation is still happening. However, where
|
|
|
|
-- possible, as few syscalls as possible are used and the underlying
|
2016-05-02 18:38:59 +00:00
|
|
|
-- exception handling is kept.
|
2016-03-30 18:16:34 +00:00
|
|
|
module HSFM.FileSystem.FileOperations where
|
2015-12-17 03:42:22 +00:00
|
|
|
|
|
|
|
|
|
|
|
import Control.Exception
|
|
|
|
(
|
2016-04-06 01:10:07 +00:00
|
|
|
bracket
|
2016-05-02 17:06:53 +00:00
|
|
|
, bracketOnError
|
2016-04-06 01:10:07 +00:00
|
|
|
, throw
|
2015-12-17 03:42:22 +00:00
|
|
|
)
|
2015-12-28 02:04:02 +00:00
|
|
|
import Control.Monad
|
|
|
|
(
|
2016-05-08 16:48:17 +00:00
|
|
|
void
|
2016-04-10 20:04:07 +00:00
|
|
|
, when
|
2015-12-28 02:04:02 +00:00
|
|
|
)
|
2016-04-04 22:56:36 +00:00
|
|
|
import Data.ByteString
|
|
|
|
(
|
|
|
|
ByteString
|
|
|
|
)
|
2015-12-18 03:22:13 +00:00
|
|
|
import Data.Foldable
|
|
|
|
(
|
|
|
|
for_
|
|
|
|
)
|
2016-05-02 17:06:53 +00:00
|
|
|
import Data.Maybe
|
|
|
|
(
|
|
|
|
catMaybes
|
|
|
|
)
|
2016-04-10 01:58:20 +00:00
|
|
|
import Data.Word
|
|
|
|
(
|
|
|
|
Word8
|
|
|
|
)
|
2015-12-27 15:25:24 +00:00
|
|
|
import Foreign.C.Error
|
|
|
|
(
|
2016-05-03 09:54:25 +00:00
|
|
|
eEXIST
|
|
|
|
, eINVAL
|
2016-04-10 01:58:20 +00:00
|
|
|
, eNOSYS
|
2016-05-03 09:54:25 +00:00
|
|
|
, eNOTEMPTY
|
2016-05-02 17:06:53 +00:00
|
|
|
, eXDEV
|
2016-04-10 01:58:20 +00:00
|
|
|
)
|
2016-04-10 16:58:06 +00:00
|
|
|
import Foreign.C.Types
|
|
|
|
(
|
|
|
|
CSize
|
|
|
|
)
|
2016-04-10 01:58:20 +00:00
|
|
|
import Foreign.Marshal.Alloc
|
|
|
|
(
|
|
|
|
allocaBytes
|
|
|
|
)
|
|
|
|
import Foreign.Ptr
|
|
|
|
(
|
|
|
|
Ptr
|
2015-12-27 15:25:24 +00:00
|
|
|
)
|
2016-05-08 16:48:17 +00:00
|
|
|
import GHC.IO.Exception
|
|
|
|
(
|
|
|
|
IOErrorType(..)
|
|
|
|
)
|
2016-03-30 00:50:32 +00:00
|
|
|
import HPath
|
2016-04-10 01:58:20 +00:00
|
|
|
(
|
|
|
|
Path
|
2016-04-10 16:52:51 +00:00
|
|
|
, Abs
|
2016-04-10 01:58:20 +00:00
|
|
|
, Fn
|
|
|
|
)
|
2016-03-30 00:50:32 +00:00
|
|
|
import qualified HPath as P
|
2016-03-30 18:16:34 +00:00
|
|
|
import HSFM.FileSystem.Errors
|
2016-05-08 16:48:17 +00:00
|
|
|
import HSFM.Utils.IO
|
2016-04-10 16:52:51 +00:00
|
|
|
import Prelude hiding (readFile)
|
2016-05-08 16:48:17 +00:00
|
|
|
import System.IO.Error
|
|
|
|
(
|
|
|
|
catchIOError
|
|
|
|
, ioeGetErrorType
|
|
|
|
)
|
2016-05-02 17:06:53 +00:00
|
|
|
import System.Posix.ByteString
|
|
|
|
(
|
|
|
|
exclusive
|
|
|
|
)
|
2016-04-04 22:56:36 +00:00
|
|
|
import System.Posix.Directory.ByteString
|
2015-12-26 15:02:25 +00:00
|
|
|
(
|
|
|
|
createDirectory
|
|
|
|
, removeDirectory
|
|
|
|
)
|
2016-05-02 17:06:53 +00:00
|
|
|
import System.Posix.Directory.Traversals
|
|
|
|
(
|
2016-05-02 17:14:52 +00:00
|
|
|
getDirectoryContents'
|
2016-05-02 17:06:53 +00:00
|
|
|
)
|
2016-04-04 22:56:36 +00:00
|
|
|
import System.Posix.Files.ByteString
|
2015-12-18 03:22:13 +00:00
|
|
|
(
|
|
|
|
createSymbolicLink
|
2016-04-10 01:58:20 +00:00
|
|
|
, fileMode
|
|
|
|
, getFdStatus
|
2015-12-26 15:02:25 +00:00
|
|
|
, groupExecuteMode
|
2015-12-25 21:51:45 +00:00
|
|
|
, groupReadMode
|
|
|
|
, groupWriteMode
|
2015-12-26 15:02:25 +00:00
|
|
|
, otherExecuteMode
|
2015-12-25 21:51:45 +00:00
|
|
|
, otherReadMode
|
|
|
|
, otherWriteMode
|
2015-12-26 15:02:25 +00:00
|
|
|
, ownerModes
|
2015-12-25 21:51:45 +00:00
|
|
|
, ownerReadMode
|
|
|
|
, ownerWriteMode
|
2016-04-10 20:04:07 +00:00
|
|
|
, readSymbolicLink
|
|
|
|
, removeLink
|
2015-12-26 02:04:28 +00:00
|
|
|
, rename
|
2016-05-08 16:48:17 +00:00
|
|
|
, setFileMode
|
2015-12-25 21:51:45 +00:00
|
|
|
, unionFileModes
|
|
|
|
)
|
2016-04-10 01:58:20 +00:00
|
|
|
import qualified System.Posix.Files.ByteString as PF
|
2016-04-04 22:56:36 +00:00
|
|
|
import qualified "unix" System.Posix.IO.ByteString as SPI
|
2016-04-10 01:58:20 +00:00
|
|
|
import qualified "unix-bytestring" System.Posix.IO.ByteString as SPB
|
2016-05-02 17:06:53 +00:00
|
|
|
import qualified System.Posix.Directory.Traversals as SPDT
|
|
|
|
import qualified System.Posix.Directory.Foreign as SPDF
|
2016-04-16 17:14:08 +00:00
|
|
|
import System.Posix.IO.Sendfile.ByteString
|
|
|
|
(
|
|
|
|
sendfileFd
|
|
|
|
, FileRange(EntireFile)
|
|
|
|
)
|
2016-04-04 22:56:36 +00:00
|
|
|
import qualified System.Posix.Process.ByteString as SPP
|
2015-12-26 15:02:25 +00:00
|
|
|
import System.Posix.Types
|
|
|
|
(
|
|
|
|
FileMode
|
2016-04-04 22:56:36 +00:00
|
|
|
, ProcessID
|
2016-04-10 01:58:20 +00:00
|
|
|
, Fd
|
2015-12-26 15:02:25 +00:00
|
|
|
)
|
2015-12-17 03:42:22 +00:00
|
|
|
|
2015-12-19 15:13:48 +00:00
|
|
|
|
2015-12-17 22:08:02 +00:00
|
|
|
|
2015-12-28 00:49:18 +00:00
|
|
|
-- TODO: make sure we do the right thing for BlockDev, CharDev etc...
|
|
|
|
-- most operations are not implemented for these
|
2015-12-18 03:24:47 +00:00
|
|
|
|
2015-12-18 15:55:46 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
data FileType = Directory
|
|
|
|
| RegularFile
|
|
|
|
| SymbolicLink
|
|
|
|
| BlockDevice
|
|
|
|
| CharacterDevice
|
|
|
|
| NamedPipe
|
|
|
|
| Socket
|
2016-05-02 20:13:19 +00:00
|
|
|
deriving (Eq, Show)
|
2015-12-18 15:55:46 +00:00
|
|
|
|
2015-12-17 22:08:02 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
2015-12-18 14:28:56 +00:00
|
|
|
|
2015-12-19 15:13:48 +00:00
|
|
|
--------------------
|
|
|
|
--[ File Copying ]--
|
|
|
|
--------------------
|
|
|
|
|
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
|
2016-05-02 20:19:19 +00:00
|
|
|
-- |Copies a directory recursively to the given destination.
|
|
|
|
-- Does not follow symbolic links.
|
2016-05-02 17:06:53 +00:00
|
|
|
--
|
2016-05-02 18:36:22 +00:00
|
|
|
-- Safety/reliability concerns:
|
2016-05-02 18:49:08 +00:00
|
|
|
--
|
|
|
|
-- * not atomic
|
|
|
|
-- * examines filetypes explicitly
|
|
|
|
-- * an explicit check `throwDestinationInSource` is carried out for the
|
|
|
|
-- top directory for basic sanity, because otherwise we might end up
|
|
|
|
-- with an infinite copy loop... however, this operation is not
|
|
|
|
-- carried out recursively (because it's slow)
|
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if source directory does not exist
|
|
|
|
-- - `PermissionDenied` if output directory is not writable
|
|
|
|
-- - `PermissionDenied` if source directory can't be opened
|
|
|
|
-- - `InvalidArgument` if source directory is wrong type (symlink)
|
|
|
|
-- - `InvalidArgument` if source directory is wrong type (regular file)
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `SameFile` if source and destination are the same file (`FmIOException`)
|
2016-05-02 18:49:08 +00:00
|
|
|
-- - `AlreadyExists` if destination already exists
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `DestinationInSource` if destination is contained in source (`FmIOException`)
|
2016-05-02 17:06:53 +00:00
|
|
|
copyDirRecursive :: Path Abs -- ^ source dir
|
|
|
|
-> Path Abs -- ^ full destination
|
|
|
|
-> IO ()
|
|
|
|
copyDirRecursive fromp destdirp
|
2015-12-22 13:15:48 +00:00
|
|
|
= do
|
2016-04-10 01:58:20 +00:00
|
|
|
-- for performance, sanity checks are only done for the top dir
|
2016-05-08 16:48:17 +00:00
|
|
|
throwSameFile fromp destdirp
|
2016-03-31 13:49:35 +00:00
|
|
|
throwDestinationInSource fromp destdirp
|
2016-05-02 17:06:53 +00:00
|
|
|
go fromp destdirp
|
2015-12-18 14:42:24 +00:00
|
|
|
where
|
2016-05-02 17:06:53 +00:00
|
|
|
go :: Path Abs -> Path Abs -> IO ()
|
|
|
|
go fromp' destdirp' = do
|
|
|
|
-- order is important here, so we don't get empty directories
|
|
|
|
-- on failure
|
|
|
|
contents <- getDirsFiles fromp'
|
|
|
|
|
|
|
|
fmode' <- PF.fileMode <$> PF.getSymbolicLinkStatus (P.fromAbs fromp')
|
|
|
|
createDirectory (P.fromAbs destdirp') fmode'
|
|
|
|
|
|
|
|
for_ contents $ \f -> do
|
|
|
|
ftype <- getFileType f
|
|
|
|
newdest <- (destdirp' P.</>) <$> P.basename f
|
|
|
|
case ftype of
|
|
|
|
SymbolicLink -> recreateSymlink f newdest
|
|
|
|
Directory -> go f newdest
|
|
|
|
RegularFile -> copyFile f newdest
|
|
|
|
_ -> ioError $ userError $ "No idea what to do with the" ++
|
|
|
|
"given filetype: " ++ show ftype
|
2015-12-21 17:32:53 +00:00
|
|
|
|
2016-05-08 16:48:17 +00:00
|
|
|
-- |Like `copyDirRecursive` except it overwrites contents of directories
|
|
|
|
-- if any.
|
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if source directory does not exist
|
|
|
|
-- - `PermissionDenied` if output directory is not writable
|
|
|
|
-- - `PermissionDenied` if source directory can't be opened
|
|
|
|
-- - `InvalidArgument` if source directory is wrong type (symlink)
|
|
|
|
-- - `InvalidArgument` if source directory is wrong type (regular file)
|
|
|
|
-- - `SameFile` if source and destination are the same file (`FmIOException`)
|
|
|
|
-- - `DestinationInSource` if destination is contained in source (`FmIOException`)
|
|
|
|
copyDirRecursiveOverwrite :: Path Abs -- ^ source dir
|
|
|
|
-> Path Abs -- ^ full destination
|
|
|
|
-> IO ()
|
|
|
|
copyDirRecursiveOverwrite fromp destdirp
|
|
|
|
= do
|
|
|
|
-- for performance, sanity checks are only done for the top dir
|
|
|
|
throwSameFile fromp destdirp
|
|
|
|
throwDestinationInSource fromp destdirp
|
|
|
|
go fromp destdirp
|
|
|
|
where
|
|
|
|
go :: Path Abs -> Path Abs -> IO ()
|
|
|
|
go fromp' destdirp' = do
|
|
|
|
-- order is important here, so we don't get empty directories
|
|
|
|
-- on failure
|
|
|
|
contents <- getDirsFiles fromp'
|
|
|
|
|
|
|
|
fmode' <- PF.fileMode <$> PF.getSymbolicLinkStatus (P.fromAbs fromp')
|
|
|
|
catchIOError (createDirectory (P.fromAbs destdirp') fmode') $ \e ->
|
|
|
|
case ioeGetErrorType e of
|
|
|
|
AlreadyExists -> setFileMode (P.fromAbs destdirp') fmode'
|
|
|
|
_ -> ioError e
|
|
|
|
|
|
|
|
for_ contents $ \f -> do
|
|
|
|
ftype <- getFileType f
|
|
|
|
newdest <- (destdirp' P.</>) <$> P.basename f
|
|
|
|
case ftype of
|
|
|
|
SymbolicLink -> whenM (doesFileExist newdest) (deleteFile newdest)
|
|
|
|
>> recreateSymlink f newdest
|
|
|
|
Directory -> go f newdest
|
|
|
|
RegularFile -> copyFileOverwrite f newdest
|
|
|
|
_ -> ioError $ userError $ "No idea what to do with the" ++
|
|
|
|
"given filetype: " ++ show ftype
|
|
|
|
|
2015-12-18 14:28:56 +00:00
|
|
|
|
2015-12-21 17:36:45 +00:00
|
|
|
-- |Recreate a symlink.
|
2016-05-02 17:06:53 +00:00
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `InvalidArgument` if symlink file is wrong type (file)
|
|
|
|
-- - `InvalidArgument` if symlink file is wrong type (directory)
|
|
|
|
-- - `PermissionDenied` if output directory cannot be written to
|
|
|
|
-- - `PermissionDenied` if source directory cannot be opened
|
|
|
|
-- - `AlreadyExists` if destination file already exists
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `SameFile` if source and destination are the same file (`FmIOException`)
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
|
|
|
-- Note: calls `symlink`
|
2016-05-02 17:06:53 +00:00
|
|
|
recreateSymlink :: Path Abs -- ^ the old symlink file
|
|
|
|
-> Path Abs -- ^ destination file
|
2015-12-21 17:32:53 +00:00
|
|
|
-> IO ()
|
2016-05-02 17:06:53 +00:00
|
|
|
recreateSymlink symsource newsym
|
2015-12-22 13:15:48 +00:00
|
|
|
= do
|
2016-05-08 16:48:17 +00:00
|
|
|
throwSameFile symsource newsym
|
2016-05-02 17:06:53 +00:00
|
|
|
sympoint <- readSymbolicLink (P.fromAbs symsource)
|
|
|
|
createSymbolicLink sympoint (P.fromAbs newsym)
|
2015-12-22 13:15:48 +00:00
|
|
|
|
|
|
|
|
2016-05-08 16:48:17 +00:00
|
|
|
-- |Copies the given regular file to the given destination.
|
2016-05-02 20:19:19 +00:00
|
|
|
-- Neither follows symbolic links, nor accepts them.
|
|
|
|
-- For "copying" symbolic links, use `recreateSymlink` instead.
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if source file does not exist
|
|
|
|
-- - `PermissionDenied` if output directory is not writable
|
|
|
|
-- - `PermissionDenied` if source directory can't be opened
|
|
|
|
-- - `InvalidArgument` if source file is wrong type (symlink)
|
|
|
|
-- - `InvalidArgument` if source file is wrong type (directory)
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `SameFile` if source and destination are the same file (`FmIOException`)
|
2016-05-02 18:49:08 +00:00
|
|
|
-- - `AlreadyExists` if destination already exists
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
|
|
|
-- Note: calls `sendfile`
|
2016-05-02 17:06:53 +00:00
|
|
|
copyFile :: Path Abs -- ^ source file
|
|
|
|
-> Path Abs -- ^ destination file
|
2016-04-03 20:36:29 +00:00
|
|
|
-> IO ()
|
2016-05-08 16:48:17 +00:00
|
|
|
copyFile from to = do
|
|
|
|
throwSameFile from to
|
|
|
|
_copyFile [SPDF.oNofollow]
|
|
|
|
[SPDF.oNofollow, SPDF.oExcl]
|
|
|
|
from to
|
2016-05-08 10:48:03 +00:00
|
|
|
|
|
|
|
|
2016-05-08 16:48:17 +00:00
|
|
|
-- |Like `copyFile` except it overwrites the destination if it already
|
|
|
|
-- exists.
|
2016-05-08 10:48:03 +00:00
|
|
|
-- This also works if source and destination are the same file.
|
|
|
|
--
|
2016-05-08 16:48:17 +00:00
|
|
|
-- Safety/reliability concerns:
|
|
|
|
--
|
|
|
|
-- * not atomic
|
|
|
|
-- * falls back to delete-copy method with explicit checks
|
|
|
|
--
|
2016-05-08 10:48:03 +00:00
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if source file does not exist
|
|
|
|
-- - `PermissionDenied` if output directory is not writable
|
|
|
|
-- - `PermissionDenied` if source directory can't be opened
|
|
|
|
-- - `InvalidArgument` if source file is wrong type (symlink)
|
|
|
|
-- - `InvalidArgument` if source file is wrong type (directory)
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `SameFile` if source and destination are the same file (`FmIOException`)
|
2016-05-08 10:48:03 +00:00
|
|
|
--
|
|
|
|
-- Note: calls `sendfile`
|
|
|
|
copyFileOverwrite :: Path Abs -- ^ source file
|
|
|
|
-> Path Abs -- ^ destination file
|
|
|
|
-> IO ()
|
2016-05-08 16:48:17 +00:00
|
|
|
copyFileOverwrite from to = do
|
|
|
|
throwSameFile from to
|
|
|
|
catchIOError (_copyFile [SPDF.oNofollow]
|
|
|
|
[SPDF.oNofollow, SPDF.oTrunc]
|
|
|
|
from to) $ \e ->
|
|
|
|
case ioeGetErrorType e of
|
|
|
|
-- if the destination file is not writable, we need to
|
|
|
|
-- figure out if we can still copy by deleting it first
|
|
|
|
PermissionDenied -> do
|
|
|
|
exists <- doesFileExist to
|
|
|
|
writable <- isWritable (P.dirname to)
|
|
|
|
if exists && writable
|
|
|
|
then deleteFile to >> copyFile from to
|
|
|
|
else ioError e
|
|
|
|
_ -> ioError e
|
|
|
|
|
|
|
|
|
|
|
|
_copyFile :: [SPDF.Flags]
|
|
|
|
-> [SPDF.Flags]
|
2016-05-08 10:48:03 +00:00
|
|
|
-> Path Abs -- ^ source file
|
|
|
|
-> Path Abs -- ^ destination file
|
|
|
|
-> IO ()
|
2016-05-08 16:48:17 +00:00
|
|
|
_copyFile sflags dflags from to
|
2016-05-02 17:06:53 +00:00
|
|
|
=
|
2016-04-10 02:09:29 +00:00
|
|
|
-- from sendfile(2) manpage:
|
|
|
|
-- Applications may wish to fall back to read(2)/write(2) in the case
|
|
|
|
-- where sendfile() fails with EINVAL or ENOSYS.
|
2016-05-02 17:06:53 +00:00
|
|
|
P.withAbsPath to $ \to' -> P.withAbsPath from $ \from' ->
|
2016-04-16 19:50:15 +00:00
|
|
|
catchErrno [eINVAL, eNOSYS]
|
|
|
|
(sendFileCopy from' to')
|
|
|
|
(void $ fallbackCopy from' to')
|
2016-04-10 01:58:20 +00:00
|
|
|
where
|
|
|
|
-- this is low-level stuff utilizing sendfile(2) for speed
|
|
|
|
sendFileCopy source dest =
|
2016-05-08 16:48:17 +00:00
|
|
|
bracket (SPDT.openFd source SPI.ReadOnly sflags Nothing)
|
2016-04-10 01:58:20 +00:00
|
|
|
SPI.closeFd
|
|
|
|
$ \sfd -> do
|
|
|
|
fileM <- System.Posix.Files.ByteString.fileMode
|
|
|
|
<$> getFdStatus sfd
|
2016-05-08 16:48:17 +00:00
|
|
|
bracketeer (SPDT.openFd dest SPI.WriteOnly
|
|
|
|
dflags $ Just fileM)
|
2016-05-02 17:06:53 +00:00
|
|
|
SPI.closeFd
|
|
|
|
(\fd -> SPI.closeFd fd >> deleteFile to)
|
|
|
|
$ \dfd -> sendfileFd dfd sfd EntireFile
|
2016-04-10 01:58:20 +00:00
|
|
|
-- low-level copy operation utilizing read(2)/write(2)
|
|
|
|
-- in case `sendFileCopy` fails/is unsupported
|
|
|
|
fallbackCopy source dest =
|
2016-05-08 16:48:17 +00:00
|
|
|
bracket (SPDT.openFd source SPI.ReadOnly sflags Nothing)
|
2016-04-10 01:58:20 +00:00
|
|
|
SPI.closeFd
|
|
|
|
$ \sfd -> do
|
|
|
|
fileM <- System.Posix.Files.ByteString.fileMode
|
|
|
|
<$> getFdStatus sfd
|
2016-05-08 16:48:17 +00:00
|
|
|
bracketeer (SPDT.openFd dest SPI.WriteOnly
|
|
|
|
dflags $ Just fileM)
|
2016-05-02 17:06:53 +00:00
|
|
|
SPI.closeFd
|
|
|
|
(\fd -> SPI.closeFd fd >> deleteFile to)
|
|
|
|
$ \dfd -> allocaBytes (fromIntegral bufSize) $ \buf ->
|
|
|
|
write' sfd dfd buf 0
|
2016-04-10 01:58:20 +00:00
|
|
|
where
|
2016-04-10 16:58:06 +00:00
|
|
|
bufSize :: CSize
|
|
|
|
bufSize = 8192
|
2016-04-10 01:58:20 +00:00
|
|
|
write' :: Fd -> Fd -> Ptr Word8 -> Int -> IO Int
|
|
|
|
write' sfd dfd buf totalsize = do
|
2016-04-10 16:58:06 +00:00
|
|
|
size <- SPB.fdReadBuf sfd buf bufSize
|
2016-04-10 20:04:07 +00:00
|
|
|
if size == 0
|
2016-04-10 01:58:20 +00:00
|
|
|
then return $ fromIntegral totalsize
|
|
|
|
else do rsize <- SPB.fdWriteBuf dfd buf size
|
2016-05-08 10:48:03 +00:00
|
|
|
-- TODO: switch to IOError?
|
2016-04-10 01:58:20 +00:00
|
|
|
when (rsize /= size) (throw . CopyFailed $ "wrong size!")
|
|
|
|
write' sfd dfd buf (totalsize + fromIntegral size)
|
2015-12-27 18:26:58 +00:00
|
|
|
|
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
-- |Copies anything. In case of a symlink,
|
2016-04-06 01:10:07 +00:00
|
|
|
-- it is just recreated, even if it points to a directory.
|
2016-05-02 17:06:53 +00:00
|
|
|
--
|
2016-05-02 18:36:22 +00:00
|
|
|
-- Safety/reliability concerns:
|
2016-05-02 18:49:08 +00:00
|
|
|
--
|
|
|
|
-- * examines filetypes explicitly
|
|
|
|
-- * calls `copyDirRecursive` for directories
|
2016-05-02 17:06:53 +00:00
|
|
|
easyCopy :: Path Abs
|
|
|
|
-> Path Abs
|
2015-12-22 13:15:48 +00:00
|
|
|
-> IO ()
|
2016-05-02 17:06:53 +00:00
|
|
|
easyCopy from to = do
|
|
|
|
ftype <- getFileType from
|
|
|
|
case ftype of
|
|
|
|
SymbolicLink -> recreateSymlink from to
|
|
|
|
RegularFile -> copyFile from to
|
|
|
|
Directory -> copyDirRecursive from to
|
|
|
|
_ -> ioError $ userError $ "No idea what to do with the" ++
|
|
|
|
"given filetype: " ++ show ftype
|
|
|
|
|
2015-12-23 15:08:39 +00:00
|
|
|
|
2016-05-08 16:48:17 +00:00
|
|
|
-- |Like `easyCopy` except it overwrites the destination if it already exists.
|
|
|
|
-- For directories, this overwrites contents without pruning them, so the resulting
|
|
|
|
-- directory may have more files than have been copied.
|
|
|
|
easyCopyOverwrite :: Path Abs
|
|
|
|
-> Path Abs
|
|
|
|
-> IO ()
|
|
|
|
easyCopyOverwrite from to = do
|
|
|
|
ftype <- getFileType from
|
|
|
|
case ftype of
|
|
|
|
SymbolicLink -> whenM (doesFileExist to) (deleteFile to)
|
|
|
|
>> recreateSymlink from to
|
|
|
|
RegularFile -> copyFileOverwrite from to
|
|
|
|
Directory -> copyDirRecursiveOverwrite from to
|
|
|
|
_ -> ioError $ userError $ "No idea what to do with the" ++
|
|
|
|
"given filetype: " ++ show ftype
|
|
|
|
|
|
|
|
|
2015-12-23 15:08:39 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
2015-12-17 15:25:37 +00:00
|
|
|
|
2015-12-19 15:13:48 +00:00
|
|
|
---------------------
|
|
|
|
--[ File Deletion ]--
|
|
|
|
---------------------
|
2015-12-17 15:25:37 +00:00
|
|
|
|
2015-12-19 15:13:48 +00:00
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
-- |Deletes the given file, does not follow symlinks. Raises `eISDIR`
|
2016-05-02 20:19:19 +00:00
|
|
|
-- if run on a directory. Does not follow symbolic links.
|
2016-05-02 21:10:22 +00:00
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `InappropriateType` for wrong file type (directory)
|
|
|
|
-- - `NoSuchThing` if the file does not exist
|
|
|
|
-- - `PermissionDenied` if the directory cannot be read
|
2016-05-02 17:06:53 +00:00
|
|
|
deleteFile :: Path Abs -> IO ()
|
|
|
|
deleteFile p = P.withAbsPath p removeLink
|
2015-12-22 13:15:48 +00:00
|
|
|
|
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
-- |Deletes the given directory, which must be empty, never symlinks.
|
2016-05-03 09:55:34 +00:00
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `InappropriateType` for wrong file type (symlink to directory)
|
|
|
|
-- - `InappropriateType` for wrong file type (regular file)
|
|
|
|
-- - `NoSuchThing` if directory does not exist
|
|
|
|
-- - `UnsatisfiedConstraints` if directory is not empty
|
|
|
|
-- - `PermissionDenied` if we can't open or write to parent directory
|
|
|
|
--
|
|
|
|
-- Notes: calls `rmdir`
|
2016-05-02 17:06:53 +00:00
|
|
|
deleteDir :: Path Abs -> IO ()
|
|
|
|
deleteDir p = P.withAbsPath p removeDirectory
|
2015-12-22 13:15:48 +00:00
|
|
|
|
|
|
|
|
2016-05-02 20:19:19 +00:00
|
|
|
-- |Deletes the given directory recursively. Does not follow symbolic
|
2016-05-03 09:55:34 +00:00
|
|
|
-- links. Tries `deleteDir` first before attemtping a recursive
|
|
|
|
-- deletion.
|
2016-05-02 17:06:53 +00:00
|
|
|
--
|
2016-05-02 18:36:22 +00:00
|
|
|
-- Safety/reliability concerns:
|
2016-05-02 18:49:08 +00:00
|
|
|
--
|
|
|
|
-- * not atomic
|
|
|
|
-- * examines filetypes explicitly
|
2016-05-03 09:55:34 +00:00
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `InappropriateType` for wrong file type (symlink to directory)
|
|
|
|
-- - `InappropriateType` for wrong file type (regular file)
|
|
|
|
-- - `NoSuchThing` if directory does not exist
|
|
|
|
-- - `PermissionDenied` if we can't open or write to parent directory
|
2016-05-02 17:06:53 +00:00
|
|
|
deleteDirRecursive :: Path Abs -> IO ()
|
2016-05-03 09:54:25 +00:00
|
|
|
deleteDirRecursive p =
|
|
|
|
catchErrno [eNOTEMPTY, eEXIST]
|
|
|
|
(deleteDir p)
|
|
|
|
$ do
|
|
|
|
files <- getDirsFiles p
|
|
|
|
for_ files $ \file -> do
|
|
|
|
ftype <- getFileType file
|
|
|
|
case ftype of
|
|
|
|
SymbolicLink -> deleteFile file
|
|
|
|
Directory -> deleteDirRecursive file
|
|
|
|
RegularFile -> deleteFile file
|
|
|
|
_ -> ioError $ userError $ "No idea what to do with the" ++
|
|
|
|
"given filetype: " ++ show ftype
|
|
|
|
removeDirectory . P.toFilePath $ p
|
2015-12-18 14:28:56 +00:00
|
|
|
|
|
|
|
|
2015-12-21 17:32:53 +00:00
|
|
|
-- |Deletes a file, directory or symlink, whatever it may be.
|
2015-12-23 15:10:08 +00:00
|
|
|
-- In case of directory, performs recursive deletion. In case of
|
|
|
|
-- a symlink, the symlink file is deleted.
|
2016-05-02 17:06:53 +00:00
|
|
|
--
|
2016-05-02 18:36:22 +00:00
|
|
|
-- Safety/reliability concerns:
|
2016-05-02 18:49:08 +00:00
|
|
|
--
|
|
|
|
-- * examines filetypes explicitly
|
|
|
|
-- * calls `deleteDirRecursive` for directories
|
2016-05-02 17:06:53 +00:00
|
|
|
easyDelete :: Path Abs -> IO ()
|
|
|
|
easyDelete p = do
|
|
|
|
ftype <- getFileType p
|
|
|
|
case ftype of
|
|
|
|
SymbolicLink -> deleteFile p
|
|
|
|
Directory -> deleteDirRecursive p
|
|
|
|
RegularFile -> deleteFile p
|
|
|
|
_ -> ioError $ userError $ "No idea what to do with the" ++
|
|
|
|
"given filetype: " ++ show ftype
|
2015-12-22 13:15:48 +00:00
|
|
|
|
2015-12-19 15:13:48 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
--------------------
|
|
|
|
--[ File Opening ]--
|
|
|
|
--------------------
|
2015-12-17 15:25:37 +00:00
|
|
|
|
|
|
|
|
2016-04-06 01:10:07 +00:00
|
|
|
-- |Opens a file appropriately by invoking xdg-open. The file type
|
|
|
|
-- is not checked.
|
2016-05-02 17:06:53 +00:00
|
|
|
openFile :: Path Abs
|
2016-04-04 22:56:36 +00:00
|
|
|
-> IO ProcessID
|
2016-05-02 17:06:53 +00:00
|
|
|
openFile p =
|
|
|
|
P.withAbsPath p $ \fp ->
|
2016-04-16 19:50:15 +00:00
|
|
|
SPP.forkProcess $ SPP.executeFile "xdg-open" True [fp] Nothing
|
2015-12-17 03:42:22 +00:00
|
|
|
|
|
|
|
|
|
|
|
-- |Executes a program with the given arguments.
|
2016-05-02 17:06:53 +00:00
|
|
|
executeFile :: Path Abs -- ^ program
|
2016-04-10 01:58:20 +00:00
|
|
|
-> [ByteString] -- ^ arguments
|
2016-04-04 22:56:36 +00:00
|
|
|
-> IO ProcessID
|
2016-05-02 17:06:53 +00:00
|
|
|
executeFile fp args
|
2016-04-16 19:50:15 +00:00
|
|
|
= P.withAbsPath fp $ \fpb ->
|
|
|
|
SPP.forkProcess
|
|
|
|
$ SPP.executeFile fpb True args Nothing
|
2015-12-25 21:51:45 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
---------------------
|
|
|
|
--[ File Creation ]--
|
|
|
|
---------------------
|
|
|
|
|
|
|
|
|
2016-04-06 01:10:07 +00:00
|
|
|
-- |Create an empty regular file at the given directory with the given filename.
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `PermissionDenied` if output directory cannot be written to
|
|
|
|
-- - `AlreadyExists` if destination file already exists
|
2016-05-02 17:06:53 +00:00
|
|
|
createRegularFile :: Path Abs -> IO ()
|
|
|
|
createRegularFile dest =
|
|
|
|
bracket (SPI.openFd (P.fromAbs dest) SPI.WriteOnly (Just newFilePerms)
|
|
|
|
(SPI.defaultFileFlags { exclusive = True }))
|
|
|
|
SPI.closeFd
|
|
|
|
(\_ -> return ())
|
2015-12-26 02:04:28 +00:00
|
|
|
|
|
|
|
|
2016-04-06 01:10:07 +00:00
|
|
|
-- |Create an empty directory at the given directory with the given filename.
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `PermissionDenied` if output directory cannot be written to
|
|
|
|
-- - `AlreadyExists` if destination directory already exists
|
2016-05-02 17:06:53 +00:00
|
|
|
createDir :: Path Abs -> IO ()
|
|
|
|
createDir dest = createDirectory (P.fromAbs dest) newDirPerms
|
2015-12-26 14:58:41 +00:00
|
|
|
|
|
|
|
|
2015-12-26 02:04:28 +00:00
|
|
|
|
|
|
|
|
2015-12-26 20:18:42 +00:00
|
|
|
----------------------------
|
|
|
|
--[ File Renaming/Moving ]--
|
|
|
|
----------------------------
|
2015-12-26 02:04:28 +00:00
|
|
|
|
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
-- |Rename a given file with the provided filename. Destination and source
|
|
|
|
-- must be on the same device, otherwise `eXDEV` will be raised.
|
|
|
|
--
|
2016-05-02 20:19:19 +00:00
|
|
|
-- Does not follow symbolic links, but renames the symbolic link file.
|
|
|
|
--
|
2016-05-02 18:36:22 +00:00
|
|
|
-- Safety/reliability concerns:
|
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- * has a separate set of exception handling, apart from the syscall
|
|
|
|
--
|
|
|
|
-- Throws:
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- - `NoSuchThing` if source file does not exist
|
|
|
|
-- - `PermissionDenied` if output directory cannot be written to
|
2016-05-02 20:52:10 +00:00
|
|
|
-- - `PermissionDenied` if source directory cannot be opened
|
2016-05-02 18:49:08 +00:00
|
|
|
-- - `UnsupportedOperation` if source and destination are on different devices
|
|
|
|
-- - `FileDoesExist` if destination file already exists
|
|
|
|
-- - `DirDoesExist` if destination directory already exists
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `SameFile` if destination and source are the same file (`FmIOException`)
|
2016-05-02 18:49:08 +00:00
|
|
|
--
|
|
|
|
-- Note: calls `rename` (but does not allow to rename over existing files)
|
2016-05-02 17:06:53 +00:00
|
|
|
renameFile :: Path Abs -> Path Abs -> IO ()
|
|
|
|
renameFile fromf tof = do
|
2015-12-26 02:04:28 +00:00
|
|
|
throwSameFile fromf tof
|
2016-05-02 17:06:53 +00:00
|
|
|
throwFileDoesExist tof
|
|
|
|
throwDirDoesExist tof
|
2016-03-31 13:49:35 +00:00
|
|
|
rename (P.fromAbs fromf) (P.fromAbs tof)
|
2015-12-26 14:58:41 +00:00
|
|
|
|
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
-- |Move a file. This also works across devices by copy-delete fallback.
|
|
|
|
-- And also works on directories.
|
|
|
|
--
|
2016-05-02 20:19:19 +00:00
|
|
|
-- Does not follow symbolic links, but renames the symbolic link file.
|
|
|
|
--
|
2016-05-02 18:36:22 +00:00
|
|
|
-- Safety/reliability concerns:
|
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- * copy-delete fallback is inherently non-atomic
|
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if source file does not exist
|
|
|
|
-- - `PermissionDenied` if output directory cannot be written to
|
2016-05-02 20:52:10 +00:00
|
|
|
-- - `PermissionDenied` if source directory cannot be opened
|
2016-05-02 18:49:08 +00:00
|
|
|
-- - `FileDoesExist` if destination file already exists
|
|
|
|
-- - `DirDoesExist` if destination directory already exists
|
2016-05-08 16:48:17 +00:00
|
|
|
-- - `SameFile` if destination and source are the same file (`FmIOException`)
|
2016-05-02 18:36:22 +00:00
|
|
|
--
|
2016-05-02 18:49:08 +00:00
|
|
|
-- Note: calls `rename` (but does not allow to rename over existing files)
|
2016-05-02 17:06:53 +00:00
|
|
|
moveFile :: Path Abs -- ^ file to move
|
|
|
|
-> Path Abs -- ^ destination
|
2015-12-26 20:18:42 +00:00
|
|
|
-> IO ()
|
2016-05-08 16:48:17 +00:00
|
|
|
moveFile from to = do
|
|
|
|
throwSameFile from to
|
2016-05-02 17:06:53 +00:00
|
|
|
catchErrno [eXDEV] (renameFile from to) $ do
|
|
|
|
easyCopy from to
|
2015-12-26 22:21:02 +00:00
|
|
|
easyDelete from
|
2015-12-26 20:18:42 +00:00
|
|
|
|
|
|
|
|
2016-05-08 18:14:30 +00:00
|
|
|
-- |Like `moveFile`, but overwrites the destination if it exists.
|
|
|
|
--
|
|
|
|
-- Does not follow symbolic links, but renames the symbolic link file.
|
|
|
|
--
|
|
|
|
-- Safety/reliability concerns:
|
|
|
|
--
|
|
|
|
-- * copy-delete fallback is inherently non-atomic
|
2016-05-08 21:20:00 +00:00
|
|
|
-- * checks for file types and destination file existence explicitly
|
2016-05-08 18:14:30 +00:00
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if source file does not exist
|
|
|
|
-- - `PermissionDenied` if output directory cannot be written to
|
|
|
|
-- - `PermissionDenied` if source directory cannot be opened
|
|
|
|
-- - `SameFile` if destination and source are the same file (`FmIOException`)
|
|
|
|
--
|
|
|
|
-- Note: calls `rename` (but does not allow to rename over existing files)
|
|
|
|
moveFileOverwrite :: Path Abs -- ^ file to move
|
|
|
|
-> Path Abs -- ^ destination
|
|
|
|
-> IO ()
|
|
|
|
moveFileOverwrite from to = do
|
|
|
|
throwSameFile from to
|
2016-05-08 21:20:00 +00:00
|
|
|
ft <- getFileType from
|
2016-05-08 18:14:30 +00:00
|
|
|
writable <- isWritable $ P.dirname to
|
2016-05-08 21:20:00 +00:00
|
|
|
case ft of
|
|
|
|
RegularFile -> do
|
|
|
|
exists <- doesFileExist to
|
|
|
|
when (exists && writable) (deleteFile to)
|
|
|
|
SymbolicLink -> do
|
|
|
|
exists <- doesFileExist to
|
|
|
|
when (exists && writable) (deleteFile to)
|
|
|
|
Directory -> do
|
|
|
|
exists <- doesDirectoryExist to
|
|
|
|
when (exists && writable) (deleteDir to)
|
|
|
|
_ -> ioError $ userError $ "Don't know how to handle filetype " ++
|
|
|
|
show ft
|
2016-05-08 18:14:30 +00:00
|
|
|
moveFile from to
|
|
|
|
|
2015-12-26 20:18:42 +00:00
|
|
|
|
|
|
|
|
2015-12-26 14:58:41 +00:00
|
|
|
|
|
|
|
-----------------------
|
|
|
|
--[ File Permissions]--
|
|
|
|
-----------------------
|
|
|
|
|
|
|
|
|
2016-04-06 01:10:07 +00:00
|
|
|
-- |Default permissions for a new file.
|
2015-12-26 14:58:41 +00:00
|
|
|
newFilePerms :: FileMode
|
|
|
|
newFilePerms
|
|
|
|
= ownerWriteMode
|
|
|
|
`unionFileModes` ownerReadMode
|
|
|
|
`unionFileModes` groupWriteMode
|
|
|
|
`unionFileModes` groupReadMode
|
|
|
|
`unionFileModes` otherWriteMode
|
|
|
|
`unionFileModes` otherReadMode
|
|
|
|
|
|
|
|
|
2016-04-06 01:10:07 +00:00
|
|
|
-- |Default permissions for a new directory.
|
2015-12-26 14:58:41 +00:00
|
|
|
newDirPerms :: FileMode
|
|
|
|
newDirPerms
|
|
|
|
= ownerModes
|
|
|
|
`unionFileModes` groupExecuteMode
|
|
|
|
`unionFileModes` groupReadMode
|
|
|
|
`unionFileModes` otherExecuteMode
|
|
|
|
`unionFileModes` otherReadMode
|
2016-04-06 01:10:07 +00:00
|
|
|
|
2016-05-02 17:06:53 +00:00
|
|
|
|
|
|
|
|
|
|
|
-------------------------
|
|
|
|
--[ Directory reading ]--
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
|
|
|
|
-- |Gets all filenames of the given directory. This excludes "." and "..".
|
2016-05-02 20:19:19 +00:00
|
|
|
-- This version does not follow symbolic links.
|
2016-05-02 20:52:10 +00:00
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if directory does not exist
|
|
|
|
-- - `InappropriateType` if file type is wrong (file)
|
|
|
|
-- - `InappropriateType` if file type is wrong (symlink to file)
|
|
|
|
-- - `InappropriateType` if file type is wrong (symlink to dir)
|
|
|
|
-- - `PermissionDenied` if directory cannot be opened
|
2016-05-02 17:06:53 +00:00
|
|
|
getDirsFiles :: Path Abs -- ^ dir to read
|
|
|
|
-> IO [Path Abs]
|
|
|
|
getDirsFiles p =
|
|
|
|
P.withAbsPath p $ \fp ->
|
|
|
|
bracketOnError (SPDT.openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing)
|
|
|
|
SPI.closeFd
|
|
|
|
$ \fd ->
|
|
|
|
return
|
|
|
|
. catMaybes
|
|
|
|
. fmap (\x -> (P.</>) p <$> (parseMaybe . snd $ x))
|
|
|
|
=<< getDirectoryContents' fd
|
|
|
|
where
|
|
|
|
parseMaybe :: ByteString -> Maybe (Path Fn)
|
|
|
|
parseMaybe = P.parseFn
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
---------------------------
|
|
|
|
--[ FileType operations ]--
|
|
|
|
---------------------------
|
|
|
|
|
|
|
|
|
2016-05-02 20:13:19 +00:00
|
|
|
-- |Get the file type of the file located at the given path. Does
|
|
|
|
-- not follow symbolic links.
|
|
|
|
--
|
|
|
|
-- Throws:
|
|
|
|
--
|
|
|
|
-- - `NoSuchThing` if the file does not exist
|
|
|
|
-- - `PermissionDenied` if any part of the path is not accessible
|
2016-05-02 17:06:53 +00:00
|
|
|
getFileType :: Path Abs -> IO FileType
|
|
|
|
getFileType p = do
|
|
|
|
fs <- PF.getSymbolicLinkStatus (P.fromAbs p)
|
|
|
|
decide fs
|
|
|
|
where
|
|
|
|
decide fs
|
|
|
|
| PF.isDirectory fs = return Directory
|
|
|
|
| PF.isRegularFile fs = return RegularFile
|
|
|
|
| PF.isSymbolicLink fs = return SymbolicLink
|
|
|
|
| PF.isBlockDevice fs = return BlockDevice
|
|
|
|
| PF.isCharacterDevice fs = return CharacterDevice
|
|
|
|
| PF.isNamedPipe fs = return NamedPipe
|
|
|
|
| PF.isSocket fs = return Socket
|
|
|
|
| otherwise = ioError $ userError "No filetype?!"
|
|
|
|
|