{-# LINE 1 "System/Posix/Directory/ByteString.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE NondecreasingIndentation #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Directory.ByteString-- 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)---- String-based POSIX directory support--------------------------------------------------------------------------------- hack copied from System.Posix.Files{-# LINE 25 "System/Posix/Directory/ByteString.hsc" #-}moduleSystem.Posix.Directory.ByteString(-- * Creating and removing directoriescreateDirectory ,removeDirectory ,-- * Reading directoriesDirStream ,openDirStream ,readDirStream ,readDirStreamMaybe ,rewindDirStream ,closeDirStream ,DirStreamOffset ,{-# LINE 39 "System/Posix/Directory/ByteString.hsc" #-}tellDirStream,{-# LINE 41 "System/Posix/Directory/ByteString.hsc" #-}{-# LINE 42 "System/Posix/Directory/ByteString.hsc" #-}seekDirStream,{-# LINE 44 "System/Posix/Directory/ByteString.hsc" #-}-- * The working directorygetWorkingDirectory ,changeWorkingDirectory ,changeWorkingDirectoryFd ,)whereimportControl.Monad((>=>))importData.MaybeimportSystem.Posix.TypesimportForeignimportForeign.CimportData.ByteString.Char8asBCimportSystem.Posix.Directory.Common importSystem.Posix.ByteString.FilePath -- | @createDirectory dir mode@ calls @mkdir@ to-- create a new directory, @dir@, with permissions based on-- @mode@.createDirectory ::RawFilePath ->FileMode->IO()createDirectory :: RawFilePath -> FileMode -> IO ()
createDirectory RawFilePath
name FileMode
mode =RawFilePath -> (CString -> IO ()) -> IO ()
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> RawFilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"createDirectory"RawFilePath
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 ::RawFilePath ->IODirStream openDirStream :: RawFilePath -> IO DirStream
openDirStream RawFilePath
name =RawFilePath -> (CString -> IO DirStream) -> IO DirStream
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
name ((CString -> IO DirStream) -> IO DirStream)
-> (CString -> IO DirStream) -> IO DirStream
forall a b. (a -> b) -> a -> b
$\CString
s ->doPtr CDir
dirp <-String -> RawFilePath -> IO (Ptr CDir) -> IO (Ptr CDir)
forall a. String -> RawFilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry String
"openDirStream"RawFilePath
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
DirStream Ptr CDir
dirp )foreignimportcapiunsafe"HsUnix.h opendir"c_opendir ::CString->IO(PtrCDir )-- | @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 ::DirStream ->IORawFilePath readDirStream :: DirStream -> IO RawFilePath
readDirStream =(Maybe RawFilePath -> RawFilePath)
-> IO (Maybe RawFilePath) -> IO RawFilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap(RawFilePath -> Maybe RawFilePath -> RawFilePath
forall a. a -> Maybe a -> a
fromMaybeRawFilePath
BC.empty)(IO (Maybe RawFilePath) -> IO RawFilePath)
-> (DirStream -> IO (Maybe RawFilePath))
-> DirStream
-> IO RawFilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.DirStream -> IO (Maybe RawFilePath)
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 ::DirStream ->IO(MaybeRawFilePath )readDirStreamMaybe :: DirStream -> IO (Maybe RawFilePath)
readDirStreamMaybe =(DirEnt -> IO RawFilePath) -> DirStream -> IO (Maybe RawFilePath)
forall a. (DirEnt -> IO a) -> DirStream -> IO (Maybe a)
readDirStreamWith (DirEnt -> IO CString
dirEntName (DirEnt -> IO CString)
-> (CString -> IO RawFilePath) -> DirEnt -> IO RawFilePath
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>CString -> IO RawFilePath
peekFilePath )-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name-- of the current working directory.getWorkingDirectory ::IORawFilePath getWorkingDirectory :: IO RawFilePath
getWorkingDirectory =Int -> IO RawFilePath
go (Int
4096){-# LINE 110 "System/Posix/Directory/ByteString.hsc" #-}wherego :: Int -> IO RawFilePath
go Int
bytes =doMaybe RawFilePath
r <-Int
-> (CString -> IO (Maybe RawFilePath)) -> IO (Maybe RawFilePath)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytesInt
bytes ((CString -> IO (Maybe RawFilePath)) -> IO (Maybe RawFilePath))
-> (CString -> IO (Maybe RawFilePath)) -> IO (Maybe RawFilePath)
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
nullPtrthendoRawFilePath
s <-CString -> IO RawFilePath
peekFilePath CString
buf Maybe RawFilePath -> IO (Maybe RawFilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(RawFilePath -> Maybe RawFilePath
forall a. a -> Maybe a
JustRawFilePath
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 RawFilePath -> IO (Maybe RawFilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnMaybe RawFilePath
forall a. Maybe a
NothingelseString -> IO (Maybe RawFilePath)
forall a. String -> IO a
throwErrnoString
"getWorkingDirectory"IO RawFilePath
-> (RawFilePath -> IO RawFilePath)
-> Maybe RawFilePath
-> IO RawFilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe(Int -> IO RawFilePath
go (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
bytes ))RawFilePath -> IO RawFilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnMaybe RawFilePath
r foreignimportccallunsafe"getcwd"c_getcwd ::PtrCChar->CSize->IO(PtrCChar)-- | @changeWorkingDirectory dir@ calls @chdir@ to change-- the current working directory to @dir@.changeWorkingDirectory ::RawFilePath ->IO()changeWorkingDirectory :: RawFilePath -> IO ()
changeWorkingDirectory RawFilePath
path =RawFilePath -> (CString -> IO ()) -> IO ()
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> RawFilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"changeWorkingDirectory"RawFilePath
path (CString -> IO CInt
c_chdir CString
s )foreignimportccallunsafe"chdir"c_chdir ::CString->IOCIntremoveDirectory ::RawFilePath ->IO()removeDirectory :: RawFilePath -> IO ()
removeDirectory RawFilePath
path =RawFilePath -> (CString -> IO ()) -> IO ()
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> RawFilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"removeDirectory"RawFilePath
path (CString -> IO CInt
c_rmdir CString
s )foreignimportccallunsafe"rmdir"c_rmdir ::CString->IOCInt

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