Backport changes from posix-paths PR:
* add isFileName * add hasParentDir * add hiddenFile * add our own openFd version for more control * small documentation improvements * add a getDirectoryContents' version that works on Fd * fix linting warnings * lift version constraints in benchmark Also adjust HPath.IO to work with the new API.
This commit is contained in:
parent
0fa66cd581
commit
797dcaf725
@ -29,6 +29,7 @@ library
|
|||||||
HPath.Internal,
|
HPath.Internal,
|
||||||
System.Posix.Directory.Foreign,
|
System.Posix.Directory.Foreign,
|
||||||
System.Posix.Directory.Traversals,
|
System.Posix.Directory.Traversals,
|
||||||
|
System.Posix.FD,
|
||||||
System.Posix.FilePath
|
System.Posix.FilePath
|
||||||
build-depends: base >= 4.2 && <5
|
build-depends: base >= 4.2 && <5
|
||||||
, bytestring >= 0.9.2.0
|
, bytestring >= 0.9.2.0
|
||||||
@ -111,9 +112,9 @@ benchmark bench.hs
|
|||||||
bytestring,
|
bytestring,
|
||||||
unix,
|
unix,
|
||||||
directory >= 1.1 && < 1.3,
|
directory >= 1.1 && < 1.3,
|
||||||
filepath >= 1.2 && < 1.4,
|
filepath >= 1.2 && < 1.5,
|
||||||
process >= 1.0 && < 1.3,
|
process >= 1.0 && < 1.3,
|
||||||
criterion >= 0.6 && < 0.9
|
criterion >= 0.6 && < 1.2
|
||||||
ghc-options: -O2
|
ghc-options: -O2
|
||||||
|
|
||||||
source-repository head
|
source-repository head
|
||||||
|
@ -45,9 +45,6 @@ module HPath
|
|||||||
,withAbsPath
|
,withAbsPath
|
||||||
,withRelPath
|
,withRelPath
|
||||||
,withFnPath
|
,withFnPath
|
||||||
-- * ByteString operations
|
|
||||||
,fpToString
|
|
||||||
,userStringToFP
|
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
@ -182,6 +182,10 @@ import System.Posix.Files.ByteString
|
|||||||
import qualified System.Posix.Files.ByteString as PF
|
import qualified System.Posix.Files.ByteString as PF
|
||||||
import qualified "unix" System.Posix.IO.ByteString as SPI
|
import qualified "unix" System.Posix.IO.ByteString as SPI
|
||||||
import qualified "unix-bytestring" System.Posix.IO.ByteString as SPB
|
import qualified "unix-bytestring" System.Posix.IO.ByteString as SPB
|
||||||
|
import System.Posix.FD
|
||||||
|
(
|
||||||
|
openFd
|
||||||
|
)
|
||||||
import qualified System.Posix.Directory.Traversals as SPDT
|
import qualified System.Posix.Directory.Traversals as SPDT
|
||||||
import qualified System.Posix.Directory.Foreign as SPDF
|
import qualified System.Posix.Directory.Foreign as SPDF
|
||||||
import qualified System.Posix.Process.ByteString as SPP
|
import qualified System.Posix.Process.ByteString as SPP
|
||||||
@ -415,33 +419,27 @@ _copyFile sflags dflags from to
|
|||||||
(sendFileCopy from' to')
|
(sendFileCopy from' to')
|
||||||
(void $ readWriteCopy from' to')
|
(void $ readWriteCopy from' to')
|
||||||
where
|
where
|
||||||
-- this is low-level stuff utilizing sendfile(2) for speed
|
copyWith copyAction source dest =
|
||||||
sendFileCopy source dest =
|
bracket (openFd source SPI.ReadOnly sflags Nothing)
|
||||||
bracket (SPDT.openFd source SPI.ReadOnly sflags Nothing)
|
|
||||||
SPI.closeFd
|
SPI.closeFd
|
||||||
$ \sfd -> do
|
$ \sfd -> do
|
||||||
fileM <- System.Posix.Files.ByteString.fileMode
|
fileM <- System.Posix.Files.ByteString.fileMode
|
||||||
<$> getFdStatus sfd
|
<$> getFdStatus sfd
|
||||||
bracketeer (SPDT.openFd dest SPI.WriteOnly
|
bracketeer (openFd dest SPI.WriteOnly
|
||||||
dflags $ Just fileM)
|
dflags $ Just fileM)
|
||||||
SPI.closeFd
|
SPI.closeFd
|
||||||
(\fd -> SPI.closeFd fd >> deleteFile to)
|
(\fd -> SPI.closeFd fd >> deleteFile to)
|
||||||
$ \dfd -> sendfileFd dfd sfd EntireFile (return ())
|
$ \dfd -> copyAction sfd dfd
|
||||||
|
-- this is low-level stuff utilizing sendfile(2) for speed
|
||||||
|
sendFileCopy :: ByteString -> ByteString -> IO ()
|
||||||
|
sendFileCopy = copyWith
|
||||||
|
(\sfd dfd -> sendfileFd dfd sfd EntireFile $ return ())
|
||||||
-- low-level copy operation utilizing read(2)/write(2)
|
-- low-level copy operation utilizing read(2)/write(2)
|
||||||
-- in case `sendFileCopy` fails/is unsupported
|
-- in case `sendFileCopy` fails/is unsupported
|
||||||
readWriteCopy :: ByteString -> ByteString -> IO Int
|
readWriteCopy :: ByteString -> ByteString -> IO Int
|
||||||
readWriteCopy source dest =
|
readWriteCopy = copyWith
|
||||||
bracket (SPDT.openFd source SPI.ReadOnly sflags Nothing)
|
(\sfd dfd -> allocaBytes (fromIntegral bufSize)
|
||||||
SPI.closeFd
|
$ \buf -> write' sfd dfd buf 0)
|
||||||
$ \sfd -> do
|
|
||||||
fileM <- System.Posix.Files.ByteString.fileMode
|
|
||||||
<$> getFdStatus sfd
|
|
||||||
bracketeer (SPDT.openFd dest SPI.WriteOnly
|
|
||||||
dflags $ Just fileM)
|
|
||||||
SPI.closeFd
|
|
||||||
(\fd -> SPI.closeFd fd >> deleteFile to)
|
|
||||||
$ \dfd -> allocaBytes (fromIntegral bufSize) $ \buf ->
|
|
||||||
write' sfd dfd buf 0
|
|
||||||
where
|
where
|
||||||
bufSize :: CSize
|
bufSize :: CSize
|
||||||
bufSize = 8192
|
bufSize = 8192
|
||||||
@ -781,14 +779,12 @@ newDirPerms
|
|||||||
getDirsFiles :: Path Abs -- ^ dir to read
|
getDirsFiles :: Path Abs -- ^ dir to read
|
||||||
-> IO [Path Abs]
|
-> IO [Path Abs]
|
||||||
getDirsFiles p =
|
getDirsFiles p =
|
||||||
withAbsPath p $ \fp ->
|
withAbsPath p $ \fp -> do
|
||||||
bracketOnError (SPDT.openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing)
|
fd <- openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing
|
||||||
SPI.closeFd
|
return
|
||||||
$ \fd ->
|
. catMaybes
|
||||||
return
|
. fmap (\x -> (</>) p <$> (parseMaybe . snd $ x))
|
||||||
. catMaybes
|
=<< getDirectoryContents' fd
|
||||||
. fmap (\x -> (</>) p <$> (parseMaybe . snd $ x))
|
|
||||||
=<< getDirectoryContents' fd
|
|
||||||
where
|
where
|
||||||
parseMaybe :: ByteString -> Maybe (Path Fn)
|
parseMaybe :: ByteString -> Maybe (Path Fn)
|
||||||
parseMaybe = parseFn
|
parseMaybe = parseFn
|
||||||
|
@ -66,6 +66,10 @@ import Data.ByteString
|
|||||||
(
|
(
|
||||||
ByteString
|
ByteString
|
||||||
)
|
)
|
||||||
|
import Data.ByteString.UTF8
|
||||||
|
(
|
||||||
|
toString
|
||||||
|
)
|
||||||
import Data.Data
|
import Data.Data
|
||||||
(
|
(
|
||||||
Data(..)
|
Data(..)
|
||||||
@ -114,20 +118,20 @@ data HPathIOException = FileDoesNotExist ByteString
|
|||||||
|
|
||||||
|
|
||||||
instance Show HPathIOException where
|
instance Show HPathIOException where
|
||||||
show (FileDoesNotExist fp) = "File does not exist:" ++ fpToString fp
|
show (FileDoesNotExist fp) = "File does not exist:" ++ toString fp
|
||||||
show (DirDoesNotExist fp) = "Directory does not exist: "
|
show (DirDoesNotExist fp) = "Directory does not exist: "
|
||||||
++ fpToString fp
|
++ toString fp
|
||||||
show (SameFile fp1 fp2) = fpToString fp1
|
show (SameFile fp1 fp2) = toString fp1
|
||||||
++ " and " ++ fpToString fp2
|
++ " and " ++ toString fp2
|
||||||
++ " are the same file!"
|
++ " are the same file!"
|
||||||
show (DestinationInSource fp1 fp2) = fpToString fp1
|
show (DestinationInSource fp1 fp2) = toString fp1
|
||||||
++ " is contained in "
|
++ " is contained in "
|
||||||
++ fpToString fp2
|
++ toString fp2
|
||||||
show (FileDoesExist fp) = "File does exist: " ++ fpToString fp
|
show (FileDoesExist fp) = "File does exist: " ++ toString fp
|
||||||
show (DirDoesExist fp) = "Directory does exist: " ++ fpToString fp
|
show (DirDoesExist fp) = "Directory does exist: " ++ toString fp
|
||||||
show (InvalidOperation str) = "Invalid operation: " ++ str
|
show (InvalidOperation str) = "Invalid operation: " ++ str
|
||||||
show (Can'tOpenDirectory fp) = "Can't open directory: "
|
show (Can'tOpenDirectory fp) = "Can't open directory: "
|
||||||
++ fpToString fp
|
++ toString fp
|
||||||
show (CopyFailed str) = "Copying failed: " ++ str
|
show (CopyFailed str) = "Copying failed: " ++ str
|
||||||
|
|
||||||
|
|
||||||
|
@ -1,5 +1,6 @@
|
|||||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE PackageImports #-}
|
||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
|
|
||||||
@ -17,7 +18,7 @@ module System.Posix.Directory.Traversals (
|
|||||||
, readDirEnt
|
, readDirEnt
|
||||||
, packDirStream
|
, packDirStream
|
||||||
, unpackDirStream
|
, unpackDirStream
|
||||||
, openFd
|
, fdOpendir
|
||||||
|
|
||||||
, realpath
|
, realpath
|
||||||
) where
|
) where
|
||||||
@ -36,6 +37,7 @@ import System.Posix.Directory.ByteString as PosixBS
|
|||||||
import System.Posix.Files.ByteString
|
import System.Posix.Files.ByteString
|
||||||
|
|
||||||
import System.IO.Unsafe
|
import System.IO.Unsafe
|
||||||
|
import "unix" System.Posix.IO.ByteString (closeFd)
|
||||||
import Unsafe.Coerce (unsafeCoerce)
|
import Unsafe.Coerce (unsafeCoerce)
|
||||||
import Foreign.C.Error
|
import Foreign.C.Error
|
||||||
import Foreign.C.String
|
import Foreign.C.String
|
||||||
@ -54,6 +56,8 @@ import Foreign.Storable
|
|||||||
-- Upon entering a directory, 'allDirectoryContents' will get all entries
|
-- Upon entering a directory, 'allDirectoryContents' will get all entries
|
||||||
-- strictly. However the returned list is lazy in that directories will only
|
-- strictly. However the returned list is lazy in that directories will only
|
||||||
-- be accessed on demand.
|
-- be accessed on demand.
|
||||||
|
--
|
||||||
|
-- Follows symbolic links for the input dir.
|
||||||
allDirectoryContents :: RawFilePath -> IO [RawFilePath]
|
allDirectoryContents :: RawFilePath -> IO [RawFilePath]
|
||||||
allDirectoryContents topdir = do
|
allDirectoryContents topdir = do
|
||||||
namesAndTypes <- getDirectoryContents topdir
|
namesAndTypes <- getDirectoryContents topdir
|
||||||
@ -71,6 +75,8 @@ allDirectoryContents topdir = do
|
|||||||
return (topdir : concat paths)
|
return (topdir : concat paths)
|
||||||
|
|
||||||
-- | Get all files from a directory and its subdirectories strictly.
|
-- | Get all files from a directory and its subdirectories strictly.
|
||||||
|
--
|
||||||
|
-- Follows symbolic links for the input dir.
|
||||||
allDirectoryContents' :: RawFilePath -> IO [RawFilePath]
|
allDirectoryContents' :: RawFilePath -> IO [RawFilePath]
|
||||||
allDirectoryContents' = fmap reverse . traverseDirectory (\acc fp -> return (fp:acc)) []
|
allDirectoryContents' = fmap reverse . traverseDirectory (\acc fp -> return (fp:acc)) []
|
||||||
-- this uses traverseDirectory because it's more efficient than forcing the
|
-- this uses traverseDirectory because it's more efficient than forcing the
|
||||||
@ -80,6 +86,8 @@ allDirectoryContents' = fmap reverse . traverseDirectory (\acc fp -> return (fp:
|
|||||||
-- files/subdirectories.
|
-- files/subdirectories.
|
||||||
--
|
--
|
||||||
-- This function allows for memory-efficient traversals.
|
-- This function allows for memory-efficient traversals.
|
||||||
|
--
|
||||||
|
-- Follows symbolic links for the input dir.
|
||||||
traverseDirectory :: (s -> RawFilePath -> IO s) -> s -> RawFilePath -> IO s
|
traverseDirectory :: (s -> RawFilePath -> IO s) -> s -> RawFilePath -> IO s
|
||||||
traverseDirectory act s0 topdir = toploop
|
traverseDirectory act s0 topdir = toploop
|
||||||
where
|
where
|
||||||
@ -103,17 +111,17 @@ actOnDirContents :: RawFilePath
|
|||||||
-> IO b
|
-> IO b
|
||||||
actOnDirContents pathRelToTop b f =
|
actOnDirContents pathRelToTop b f =
|
||||||
modifyIOError ((`ioeSetFileName` (BS.unpack pathRelToTop)) .
|
modifyIOError ((`ioeSetFileName` (BS.unpack pathRelToTop)) .
|
||||||
(`ioeSetLocation` "findBSTypRel")) $ do
|
(`ioeSetLocation` "findBSTypRel")) $
|
||||||
bracket
|
bracket
|
||||||
(openDirStream pathRelToTop)
|
(openDirStream pathRelToTop)
|
||||||
(Posix.closeDirStream)
|
Posix.closeDirStream
|
||||||
(\dirp -> loop dirp b)
|
(\dirp -> loop dirp b)
|
||||||
where
|
where
|
||||||
loop dirp b' = do
|
loop dirp b' = do
|
||||||
(typ,e) <- readDirEnt dirp
|
(typ,e) <- readDirEnt dirp
|
||||||
if (e == "")
|
if (e == "")
|
||||||
then return b'
|
then return b'
|
||||||
else do
|
else
|
||||||
if (e == "." || e == "..")
|
if (e == "." || e == "..")
|
||||||
then loop dirp b'
|
then loop dirp b'
|
||||||
else f typ (pathRelToTop </> e) b' >>= loop dirp
|
else f typ (pathRelToTop </> e) b' >>= loop dirp
|
||||||
@ -154,9 +162,6 @@ foreign import ccall "realpath"
|
|||||||
foreign import ccall unsafe "fdopendir"
|
foreign import ccall unsafe "fdopendir"
|
||||||
c_fdopendir :: Posix.Fd -> IO (Ptr ())
|
c_fdopendir :: Posix.Fd -> IO (Ptr ())
|
||||||
|
|
||||||
foreign import ccall unsafe "open"
|
|
||||||
c_open :: CString -> CInt -> Posix.CMode -> IO CInt
|
|
||||||
|
|
||||||
----------------------------------------------------------
|
----------------------------------------------------------
|
||||||
-- less dodgy but still lower-level
|
-- less dodgy but still lower-level
|
||||||
|
|
||||||
@ -189,81 +194,53 @@ readDirEnt (unpackDirStream -> dirp) =
|
|||||||
else throwErrno "readDirEnt"
|
else throwErrno "readDirEnt"
|
||||||
|
|
||||||
|
|
||||||
|
-- |Gets all directory contents (not recursively).
|
||||||
getDirectoryContents :: RawFilePath -> IO [(DirType, RawFilePath)]
|
getDirectoryContents :: RawFilePath -> IO [(DirType, RawFilePath)]
|
||||||
getDirectoryContents path =
|
getDirectoryContents path =
|
||||||
modifyIOError ((`ioeSetFileName` (BS.unpack path)) .
|
modifyIOError ((`ioeSetFileName` (BS.unpack path)) .
|
||||||
(`ioeSetLocation` "System.Posix.Directory.Traversals.getDirectoryContents")) $ do
|
(`ioeSetLocation` "System.Posix.Directory.Traversals.getDirectoryContents")) $
|
||||||
bracket
|
bracket
|
||||||
(PosixBS.openDirStream path)
|
(PosixBS.openDirStream path)
|
||||||
PosixBS.closeDirStream
|
PosixBS.closeDirStream
|
||||||
loop
|
_dirloop
|
||||||
where
|
|
||||||
loop dirp = do
|
|
||||||
t@(_typ,e) <- readDirEnt dirp
|
|
||||||
if BS.null e then return [] else do
|
|
||||||
es <- loop dirp
|
|
||||||
return (t:es)
|
|
||||||
|
|
||||||
|
|
||||||
|
-- |Binding to @fdopendir(3)@.
|
||||||
fdOpendir :: Posix.Fd -> IO DirStream
|
fdOpendir :: Posix.Fd -> IO DirStream
|
||||||
fdOpendir fd =
|
fdOpendir fd =
|
||||||
packDirStream <$> throwErrnoIfNull "fdOpendir" (c_fdopendir fd)
|
packDirStream <$> throwErrnoIfNull "fdOpendir" (c_fdopendir fd)
|
||||||
|
|
||||||
|
|
||||||
|
-- |Like `getDirectoryContents` except for a file descriptor.
|
||||||
|
--
|
||||||
|
-- To avoid complicated error checks, the file descriptor is
|
||||||
|
-- __always__ closed, even if `fdOpendir` fails. Usually, this
|
||||||
|
-- only happens on successful `fdOpendir` and after the directory
|
||||||
|
-- stream is closed. Also see the manpage of @fdopendir(3)@ for
|
||||||
|
-- more details.
|
||||||
getDirectoryContents' :: Posix.Fd -> IO [(DirType, RawFilePath)]
|
getDirectoryContents' :: Posix.Fd -> IO [(DirType, RawFilePath)]
|
||||||
getDirectoryContents' fd =
|
getDirectoryContents' fd = do
|
||||||
bracket
|
dirstream <- fdOpendir fd `catchIOError` \e -> do
|
||||||
(fdOpendir fd)
|
closeFd fd
|
||||||
PosixBS.closeDirStream
|
ioError e
|
||||||
loop
|
-- closeDirStream closes the filedescriptor
|
||||||
where
|
finally (_dirloop dirstream) (PosixBS.closeDirStream dirstream)
|
||||||
loop dirp = do
|
|
||||||
t@(_typ,e) <- readDirEnt dirp
|
|
||||||
if BS.null e then return [] else do
|
|
||||||
es <- loop dirp
|
|
||||||
return (t:es)
|
|
||||||
|
|
||||||
|
|
||||||
open_ :: CString
|
_dirloop :: DirStream -> IO [(DirType, RawFilePath)]
|
||||||
-> Posix.OpenMode
|
{-# INLINE _dirloop #-}
|
||||||
-> [Flags]
|
_dirloop dirp = do
|
||||||
-> Maybe Posix.FileMode
|
t@(_typ,e) <- readDirEnt dirp
|
||||||
-> IO Posix.Fd
|
if BS.null e then return [] else do
|
||||||
open_ str how optional_flags maybe_mode = do
|
es <- _dirloop dirp
|
||||||
fd <- c_open str all_flags mode_w
|
return (t:es)
|
||||||
return (Posix.Fd fd)
|
|
||||||
where
|
|
||||||
all_flags = unionFlags $ optional_flags ++ [open_mode] ++ creat
|
|
||||||
|
|
||||||
|
|
||||||
(creat, mode_w) = case maybe_mode of
|
|
||||||
Nothing -> ([],0)
|
|
||||||
Just x -> ([oCreat], x)
|
|
||||||
|
|
||||||
open_mode = case how of
|
|
||||||
Posix.ReadOnly -> oRdonly
|
|
||||||
Posix.WriteOnly -> oWronly
|
|
||||||
Posix.ReadWrite -> oRdwr
|
|
||||||
|
|
||||||
|
|
||||||
-- |Open and optionally create this file. See 'System.Posix.Files'
|
|
||||||
-- for information on how to use the 'FileMode' type.
|
|
||||||
openFd :: RawFilePath
|
|
||||||
-> Posix.OpenMode
|
|
||||||
-> [Flags]
|
|
||||||
-> Maybe Posix.FileMode
|
|
||||||
-> IO Posix.Fd
|
|
||||||
openFd name how optional_flags maybe_mode =
|
|
||||||
withFilePath name $ \str ->
|
|
||||||
throwErrnoPathIfMinus1Retry "openFd" name $
|
|
||||||
open_ str how optional_flags maybe_mode
|
|
||||||
|
|
||||||
|
|
||||||
-- | return the canonicalized absolute pathname
|
-- | return the canonicalized absolute pathname
|
||||||
--
|
--
|
||||||
-- like canonicalizePath, but uses realpath(3)
|
-- like canonicalizePath, but uses @realpath(3)@
|
||||||
realpath :: RawFilePath -> IO RawFilePath
|
realpath :: RawFilePath -> IO RawFilePath
|
||||||
realpath inp = do
|
realpath inp =
|
||||||
allocaBytes pathMax $ \tmp -> do
|
allocaBytes pathMax $ \tmp -> do
|
||||||
void $ BS.useAsCString inp $ \cstr -> throwErrnoIfNull "realpath" $ c_realpath cstr tmp
|
void $ BS.useAsCString inp $ \cstr -> throwErrnoIfNull "realpath" $ c_realpath cstr tmp
|
||||||
BS.packCString tmp
|
BS.packCString tmp
|
||||||
|
67
src/System/Posix/FD.hs
Normal file
67
src/System/Posix/FD.hs
Normal file
@ -0,0 +1,67 @@
|
|||||||
|
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
|
||||||
|
{-# OPTIONS_GHC -Wall #-}
|
||||||
|
|
||||||
|
-- |Provides an alternative for `System.Posix.IO.ByteString.openFd`
|
||||||
|
-- which gives us more control on what status flags to pass to the
|
||||||
|
-- low-level `open(2)` call, in contrast to the unix package.
|
||||||
|
module System.Posix.FD (
|
||||||
|
openFd
|
||||||
|
, fooBar
|
||||||
|
) where
|
||||||
|
|
||||||
|
|
||||||
|
import Foreign.C.String
|
||||||
|
import Foreign.C.Types
|
||||||
|
import System.Posix.Directory.Foreign
|
||||||
|
import qualified System.Posix as Posix
|
||||||
|
import System.Posix.ByteString.FilePath
|
||||||
|
|
||||||
|
|
||||||
|
foreign import ccall unsafe "open"
|
||||||
|
c_open :: CString -> CInt -> Posix.CMode -> IO CInt
|
||||||
|
|
||||||
|
|
||||||
|
open_ :: CString
|
||||||
|
-> Posix.OpenMode
|
||||||
|
-> [Flags]
|
||||||
|
-> Maybe Posix.FileMode
|
||||||
|
-> IO Posix.Fd
|
||||||
|
open_ str how optional_flags maybe_mode = do
|
||||||
|
fd <- c_open str all_flags mode_w
|
||||||
|
return (Posix.Fd fd)
|
||||||
|
where
|
||||||
|
all_flags = unionFlags $ optional_flags ++ [open_mode] ++ creat
|
||||||
|
|
||||||
|
|
||||||
|
(creat, mode_w) = case maybe_mode of
|
||||||
|
Nothing -> ([],0)
|
||||||
|
Just x -> ([oCreat], x)
|
||||||
|
|
||||||
|
open_mode = case how of
|
||||||
|
Posix.ReadOnly -> oRdonly
|
||||||
|
Posix.WriteOnly -> oWronly
|
||||||
|
Posix.ReadWrite -> oRdwr
|
||||||
|
|
||||||
|
|
||||||
|
-- |Open and optionally create this file. See 'System.Posix.Files'
|
||||||
|
-- for information on how to use the 'FileMode' type.
|
||||||
|
--
|
||||||
|
-- Note that passing `Just x` as the 4th argument triggers the
|
||||||
|
-- `oCreat` status flag, which must be set when you pass in `oExcl`
|
||||||
|
-- to the status flags. Also see the manpage for `open(2)`.
|
||||||
|
openFd :: RawFilePath
|
||||||
|
-> Posix.OpenMode
|
||||||
|
-> [Flags] -- ^ status flags of open(2)
|
||||||
|
-> Maybe Posix.FileMode -- ^ Just x => creates the file with the given modes, Nothing => the file must exist.
|
||||||
|
-> IO Posix.Fd
|
||||||
|
openFd name how optional_flags maybe_mode =
|
||||||
|
withFilePath name $ \str ->
|
||||||
|
throwErrnoPathIfMinus1Retry "openFd" name $
|
||||||
|
open_ str how optional_flags maybe_mode
|
||||||
|
|
||||||
|
|
||||||
|
fooBar :: String -> String
|
||||||
|
fooBar = undefined
|
@ -1,21 +1,10 @@
|
|||||||
-- |
|
|
||||||
-- Module : System.Posix.FilePath
|
|
||||||
-- Copyright : © 2016 Julian Ospald
|
|
||||||
-- License : BSD3
|
|
||||||
--
|
|
||||||
-- Maintainer : Julian Ospald <hasufell@posteo.de>
|
|
||||||
-- Stability : experimental
|
|
||||||
-- Portability : portable
|
|
||||||
--
|
|
||||||
-- The equivalent of "System.FilePath" on raw (byte string) file paths.
|
|
||||||
--
|
|
||||||
-- Not all functions of "System.FilePath" are implemented yet. Feel free to contribute!
|
|
||||||
|
|
||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
|
||||||
{-# OPTIONS_GHC -Wall #-}
|
{-# OPTIONS_GHC -Wall #-}
|
||||||
|
|
||||||
|
-- | The equivalent of "System.FilePath" on raw (byte string) file paths.
|
||||||
|
--
|
||||||
|
-- Not all functions of "System.FilePath" are implemented yet. Feel free to contribute!
|
||||||
module System.Posix.FilePath (
|
module System.Posix.FilePath (
|
||||||
|
|
||||||
-- * Separators
|
-- * Separators
|
||||||
@ -72,16 +61,11 @@ module System.Posix.FilePath (
|
|||||||
, equalFilePath
|
, equalFilePath
|
||||||
, hiddenFile
|
, hiddenFile
|
||||||
|
|
||||||
-- * Type conversion
|
|
||||||
, fpToString
|
|
||||||
, userStringToFP
|
|
||||||
|
|
||||||
, module System.Posix.ByteString.FilePath
|
, module System.Posix.ByteString.FilePath
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import Data.ByteString.UTF8 (fromString, toString)
|
|
||||||
import System.Posix.ByteString.FilePath
|
import System.Posix.ByteString.FilePath
|
||||||
|
|
||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust)
|
||||||
@ -94,7 +78,6 @@ import Control.Arrow (second)
|
|||||||
-- >>> import Test.QuickCheck
|
-- >>> import Test.QuickCheck
|
||||||
-- >>> import Control.Applicative
|
-- >>> import Control.Applicative
|
||||||
-- >>> import qualified Data.ByteString as BS
|
-- >>> import qualified Data.ByteString as BS
|
||||||
-- >>> import Data.ByteString (ByteString)
|
|
||||||
-- >>> instance Arbitrary ByteString where arbitrary = BS.pack <$> arbitrary
|
-- >>> instance Arbitrary ByteString where arbitrary = BS.pack <$> arbitrary
|
||||||
-- >>> instance CoArbitrary ByteString where coarbitrary = coarbitrary . BS.unpack
|
-- >>> instance CoArbitrary ByteString where coarbitrary = coarbitrary . BS.unpack
|
||||||
--
|
--
|
||||||
@ -441,7 +424,6 @@ normalise filepath =
|
|||||||
dropDots :: [ByteString] -> [ByteString]
|
dropDots :: [ByteString] -> [ByteString]
|
||||||
dropDots = filter (BS.singleton _period /=)
|
dropDots = filter (BS.singleton _period /=)
|
||||||
|
|
||||||
|
|
||||||
------------------------
|
------------------------
|
||||||
-- trailing path separators
|
-- trailing path separators
|
||||||
|
|
||||||
@ -524,7 +506,8 @@ isValid filepath
|
|||||||
| _nul `BS.elem` filepath = False
|
| _nul `BS.elem` filepath = False
|
||||||
| otherwise = True
|
| otherwise = True
|
||||||
|
|
||||||
-- | Is the given filename a valid filename?
|
-- | Is the given path a valid filename? This includes
|
||||||
|
-- "." and "..".
|
||||||
--
|
--
|
||||||
-- >>> isFileName "lal"
|
-- >>> isFileName "lal"
|
||||||
-- True
|
-- True
|
||||||
@ -538,13 +521,13 @@ isValid filepath
|
|||||||
-- False
|
-- False
|
||||||
-- >>> isFileName "/random_ path:*"
|
-- >>> isFileName "/random_ path:*"
|
||||||
-- False
|
-- False
|
||||||
isFileName :: ByteString -> Bool
|
isFileName :: RawFilePath -> Bool
|
||||||
isFileName filepath =
|
isFileName filepath =
|
||||||
not (BS.singleton pathSeparator `BS.isInfixOf` filepath) &&
|
not (BS.singleton pathSeparator `BS.isInfixOf` filepath) &&
|
||||||
not (BS.null filepath) &&
|
not (BS.null filepath) &&
|
||||||
not (_nul `BS.elem` filepath)
|
not (_nul `BS.elem` filepath)
|
||||||
|
|
||||||
-- | Helper function: check if the filepath has any parent directories in it.
|
-- | Check if the filepath has any parent directories in it.
|
||||||
--
|
--
|
||||||
-- >>> hasParentDir "/.."
|
-- >>> hasParentDir "/.."
|
||||||
-- True
|
-- True
|
||||||
@ -560,19 +543,18 @@ isFileName filepath =
|
|||||||
-- False
|
-- False
|
||||||
-- >>> hasParentDir ".."
|
-- >>> hasParentDir ".."
|
||||||
-- False
|
-- False
|
||||||
hasParentDir :: ByteString -> Bool
|
hasParentDir :: RawFilePath -> Bool
|
||||||
hasParentDir filepath =
|
hasParentDir filepath =
|
||||||
((pathSeparator `BS.cons` pathDoubleDot)
|
(pathSeparator `BS.cons` pathDoubleDot)
|
||||||
`BS.isSuffixOf` filepath
|
`BS.isSuffixOf` filepath
|
||||||
) ||
|
||
|
||||||
((BS.singleton pathSeparator
|
(BS.singleton pathSeparator
|
||||||
`BS.append` pathDoubleDot
|
`BS.append` pathDoubleDot
|
||||||
`BS.append` BS.singleton pathSeparator
|
`BS.append` BS.singleton pathSeparator)
|
||||||
) `BS.isInfixOf` filepath
|
`BS.isInfixOf` filepath
|
||||||
) ||
|
||
|
||||||
((pathDoubleDot `BS.append` BS.singleton pathSeparator
|
(pathDoubleDot `BS.append` BS.singleton pathSeparator)
|
||||||
) `BS.isPrefixOf` filepath
|
`BS.isPrefixOf` filepath
|
||||||
)
|
|
||||||
where
|
where
|
||||||
pathDoubleDot = BS.pack [_period, _period]
|
pathDoubleDot = BS.pack [_period, _period]
|
||||||
|
|
||||||
@ -605,32 +587,26 @@ equalFilePath p1 p2 = f p1 == f p2
|
|||||||
-- True
|
-- True
|
||||||
-- >>> hiddenFile "..foo.bar"
|
-- >>> hiddenFile "..foo.bar"
|
||||||
-- True
|
-- True
|
||||||
|
-- >>> hiddenFile "some/path/.bar"
|
||||||
|
-- True
|
||||||
-- >>> hiddenFile "..."
|
-- >>> hiddenFile "..."
|
||||||
-- True
|
-- True
|
||||||
-- >>> hiddenFile "dod"
|
|
||||||
-- False
|
|
||||||
-- >>> hiddenFile "dod.bar"
|
-- >>> hiddenFile "dod.bar"
|
||||||
-- False
|
-- False
|
||||||
|
-- >>> hiddenFile "."
|
||||||
|
-- False
|
||||||
|
-- >>> hiddenFile ".."
|
||||||
|
-- False
|
||||||
|
-- >>> hiddenFile ""
|
||||||
|
-- False
|
||||||
hiddenFile :: RawFilePath -> Bool
|
hiddenFile :: RawFilePath -> Bool
|
||||||
hiddenFile fp
|
hiddenFile fp
|
||||||
| fp == BS.pack [_period, _period] = False
|
| fn == BS.pack [_period, _period] = False
|
||||||
| fp == BS.pack [_period] = False
|
| fn == BS.pack [_period] = False
|
||||||
| otherwise = BS.pack [extSeparator]
|
| otherwise = BS.pack [extSeparator]
|
||||||
`BS.isPrefixOf` fp
|
`BS.isPrefixOf` fn
|
||||||
|
where
|
||||||
------------------------
|
fn = takeFileName fp
|
||||||
-- conversion
|
|
||||||
|
|
||||||
-- |Uses UTF-8 decoding to convert the bytestring into a String.
|
|
||||||
fpToString :: ByteString -> String
|
|
||||||
fpToString = toString
|
|
||||||
|
|
||||||
|
|
||||||
-- |Uses UTF-8 encoding to convert a user provided String into
|
|
||||||
-- a ByteString, which represents a filepath.
|
|
||||||
userStringToFP :: String -> ByteString
|
|
||||||
userStringToFP = fromString
|
|
||||||
|
|
||||||
|
|
||||||
------------------------
|
------------------------
|
||||||
-- internal stuff
|
-- internal stuff
|
||||||
@ -638,7 +614,7 @@ userStringToFP = fromString
|
|||||||
-- Just split the input FileName without adding/normalizing or changing
|
-- Just split the input FileName without adding/normalizing or changing
|
||||||
-- anything.
|
-- anything.
|
||||||
splitFileNameRaw :: RawFilePath -> (RawFilePath, RawFilePath)
|
splitFileNameRaw :: RawFilePath -> (RawFilePath, RawFilePath)
|
||||||
splitFileNameRaw x = BS.breakEnd isPathSeparator x
|
splitFileNameRaw = BS.breakEnd isPathSeparator
|
||||||
|
|
||||||
-- | Combine two paths, assuming rhs is NOT absolute.
|
-- | Combine two paths, assuming rhs is NOT absolute.
|
||||||
combineRaw :: RawFilePath -> RawFilePath -> RawFilePath
|
combineRaw :: RawFilePath -> RawFilePath -> RawFilePath
|
||||||
|
Loading…
Reference in New Issue
Block a user