{-# LINE 1 "System/Posix/Directory/PosixPath.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE NondecreasingIndentation #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Directory.PosixPath-- Copyright : (c) The University of Glasgow 2002-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : non-portable (requires POSIX)---- PosixPath based POSIX directory support--------------------------------------------------------------------------------- hack copied from System.Posix.Files{-# LINE 24 "System/Posix/Directory/PosixPath.hsc" #-}moduleSystem.Posix.Directory.PosixPath(-- * Creating and removing directoriescreateDirectory ,removeDirectory ,-- * Reading directoriesCommon.DirStream ,openDirStream ,readDirStream ,readDirStreamMaybe ,Common.rewindDirStream ,Common.closeDirStream ,Common.DirStreamOffset ,{-# LINE 38 "System/Posix/Directory/PosixPath.hsc" #-}Common.tellDirStream,{-# LINE 40 "System/Posix/Directory/PosixPath.hsc" #-}{-# LINE 41 "System/Posix/Directory/PosixPath.hsc" #-}Common.seekDirStream,{-# LINE 43 "System/Posix/Directory/PosixPath.hsc" #-}-- * The working directorygetWorkingDirectory ,changeWorkingDirectory ,Common.changeWorkingDirectoryFd ,)whereimportControl.Monad((>=>))importData.MaybeimportSystem.Posix.TypesimportForeignimportForeign.CimportSystem.OsPath.PosiximportqualifiedSystem.Posix.Directory.Common asCommonimportSystem.Posix.PosixPath.FilePath -- | @createDirectory dir mode@ calls @mkdir@ to-- create a new directory, @dir@, with permissions based on-- @mode@.createDirectory ::PosixPath->FileMode->IO()createDirectory :: PosixPath -> FileMode -> IO ()
createDirectory PosixPath
name FileMode
mode =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"createDirectory"PosixPath
name (CString -> FileMode -> IO CInt
c_mkdir CString
s FileMode
mode )-- POSIX doesn't allow mkdir() to return EINTR, but it does on-- OS X (#5184), so we need the Retry variant here.foreignimportccallunsafe"mkdir"c_mkdir ::CString->CMode->IOCInt-- | @openDirStream dir@ calls @opendir@ to obtain a-- directory stream for @dir@.openDirStream ::PosixPath->IOCommon.DirStream openDirStream :: PosixPath -> IO DirStream
openDirStream PosixPath
name =PosixPath -> (CString -> IO DirStream) -> IO DirStream
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO DirStream) -> IO DirStream)
-> (CString -> IO DirStream) -> IO DirStream
forall a b. (a -> b) -> a -> b
$\CString
s ->doPtr CDir
dirp <-String -> PosixPath -> IO (Ptr CDir) -> IO (Ptr CDir)
forall a. String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry String
"openDirStream"PosixPath
name (IO (Ptr CDir) -> IO (Ptr CDir)) -> IO (Ptr CDir) -> IO (Ptr CDir)
forall a b. (a -> b) -> a -> b
$CString -> IO (Ptr CDir)
c_opendir CString
s DirStream -> IO DirStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(Ptr CDir -> DirStream
Common.DirStream Ptr CDir
dirp )foreignimportcapiunsafe"HsUnix.h opendir"c_opendir ::CString->IO(PtrCommon.CDir )-- | @readDirStream dp@ calls @readdir@ to obtain the-- next directory entry (@struct dirent@) for the open directory-- stream @dp@, and returns the @d_name@ member of that-- structure.---- Note that this function returns an empty filepath if the end of the-- directory stream is reached. For a safer alternative use-- 'readDirStreamMaybe'.readDirStream ::Common.DirStream ->IOPosixPathreadDirStream :: DirStream -> IO PosixPath
readDirStream =(Maybe PosixPath -> PosixPath)
-> IO (Maybe PosixPath) -> IO PosixPath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap(PosixPath -> Maybe PosixPath -> PosixPath
forall a. a -> Maybe a -> a
fromMaybePosixPath
forall a. Monoid a => a
mempty)(IO (Maybe PosixPath) -> IO PosixPath)
-> (DirStream -> IO (Maybe PosixPath)) -> DirStream -> IO PosixPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.DirStream -> IO (Maybe PosixPath)
readDirStreamMaybe -- | @readDirStreamMaybe dp@ calls @readdir@ to obtain the-- next directory entry (@struct dirent@) for the open directory-- stream @dp@. It returns the @d_name@ member of that-- structure wrapped in a @Just d_name@ if an entry was read and @Nothing@ if-- the end of the directory stream was reached.readDirStreamMaybe ::Common.DirStream ->IO(MaybePosixPath)readDirStreamMaybe :: DirStream -> IO (Maybe PosixPath)
readDirStreamMaybe =(DirEnt -> IO PosixPath) -> DirStream -> IO (Maybe PosixPath)
forall a. (DirEnt -> IO a) -> DirStream -> IO (Maybe a)
Common.readDirStreamWith (DirEnt -> IO CString
Common.dirEntName (DirEnt -> IO CString)
-> (CString -> IO PosixPath) -> DirEnt -> IO PosixPath
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>CString -> IO PosixPath
peekFilePath )-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name-- of the current working directory.getWorkingDirectory ::IOPosixPathgetWorkingDirectory :: IO PosixPath
getWorkingDirectory =Int -> IO PosixPath
go (Int
4096){-# LINE 109 "System/Posix/Directory/PosixPath.hsc" #-}wherego :: Int -> IO PosixPath
go Int
bytes =doMaybe PosixPath
r <-Int -> (CString -> IO (Maybe PosixPath)) -> IO (Maybe PosixPath)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytesInt
bytes ((CString -> IO (Maybe PosixPath)) -> IO (Maybe PosixPath))
-> (CString -> IO (Maybe PosixPath)) -> IO (Maybe PosixPath)
forall a b. (a -> b) -> a -> b
$\CString
buf ->doCString
buf' <-CString -> CSize -> IO CString
c_getcwd CString
buf (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
bytes )ifCString
buf' CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
/=CString
forall a. Ptr a
nullPtrthendoPosixPath
s <-CString -> IO PosixPath
peekFilePath CString
buf Maybe PosixPath -> IO (Maybe PosixPath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(PosixPath -> Maybe PosixPath
forall a. a -> Maybe a
JustPosixPath
s )elsedoErrno
errno <-IO Errno
getErrnoifErrno
errno Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
==Errno
eRANGE-- we use Nothing to indicate that we should-- try again with a bigger bufferthenMaybe PosixPath -> IO (Maybe PosixPath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnMaybe PosixPath
forall a. Maybe a
NothingelseString -> IO (Maybe PosixPath)
forall a. String -> IO a
throwErrnoString
"getWorkingDirectory"IO PosixPath
-> (PosixPath -> IO PosixPath) -> Maybe PosixPath -> IO PosixPath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe(Int -> IO PosixPath
go (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
bytes ))PosixPath -> IO PosixPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnMaybe PosixPath
r foreignimportccallunsafe"getcwd"c_getcwd ::PtrCChar->CSize->IO(PtrCChar)-- | @changeWorkingDirectory dir@ calls @chdir@ to change-- the current working directory to @dir@.changeWorkingDirectory ::PosixPath->IO()changeWorkingDirectory :: PosixPath -> IO ()
changeWorkingDirectory PosixPath
path =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"changeWorkingDirectory"PosixPath
path (CString -> IO CInt
c_chdir CString
s )foreignimportccallunsafe"chdir"c_chdir ::CString->IOCIntremoveDirectory ::PosixPath->IO()removeDirectory :: PosixPath -> IO ()
removeDirectory PosixPath
path =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"removeDirectory"PosixPath
path (CString -> IO CInt
c_rmdir CString
s )foreignimportccallunsafe"rmdir"c_rmdir ::CString->IOCInt

AltStyle によって変換されたページ (->オリジナル) /