{-# LINE 1 "System/Posix/Directory/Common.hsc" #-}{-# LANGUAGE CPP, Safe, CApiFFI, MultiWayIf, PatternSynonyms #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Directory.Common-- 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)---- POSIX directory support-------------------------------------------------------------------------------
#include "HsUnixConfig.h"
moduleSystem.Posix.Directory.Common(DirStream(..),CDir,CDirent,DirStreamOffset(..),DirStreamWithPath(..),fromDirStreamWithPath,toDirStreamWithPath,DirEnt(..),dirEntName,dirEntType ,DirType(DirType,UnknownType,NamedPipeType,CharacterDeviceType,DirectoryType,BlockDeviceType,RegularFileType,SymbolicLinkType,SocketType,WhiteoutType),isUnknownType,isNamedPipeType,isCharacterDeviceType,isDirectoryType,isBlockDeviceType,isRegularFileType ,isSymbolicLinkType,isSocketType,isWhiteoutType,getRealDirType ,unsafeOpenDirStreamFd,readDirStreamWith,readDirStreamWithPtr,rewindDirStream,closeDirStream,{-# LINE 61 "System/Posix/Directory/Common.hsc" #-}seekDirStream,{-# LINE 63 "System/Posix/Directory/Common.hsc" #-}{-# LINE 64 "System/Posix/Directory/Common.hsc" #-}tellDirStream,{-# LINE 66 "System/Posix/Directory/Common.hsc" #-}changeWorkingDirectoryFd,)whereimportControl.Exception(mask_)importControl.Monad(void,when)importSystem.Posix.TypesimportForeignhiding(void)importForeign.C{-# LINE 79 "System/Posix/Directory/Common.hsc" #-}importSystem.Posix.Files.CommonnewtypeDirStream=DirStream(PtrCDir)-- | @since 2.8.6.0newtypeDirStreamWithPatha=DirStreamWithPath(a,PtrCDir)-- | Convert a 'DirStreamWithPath' to a 'DirStream'.-- Note that the underlying pointer is shared by both values, hence any-- modification to the resulting 'DirStream' will also modify the original-- 'DirStreamWithPath'.---- @since 2.8.6.0fromDirStreamWithPath::DirStreamWithPatha->DirStreamfromDirStreamWithPath(DirStreamWithPath(_,ptr))=DirStreamptr-- | Construct a 'DirStreamWithPath' from a 'DirStream'.-- Note that the underlying pointer is shared by both values, hence any-- modification to the pointer of the resulting 'DirStreamWithPath' will also-- modify the original 'DirStream'.---- @since 2.8.6.0toDirStreamWithPath::a->DirStream->DirStreamWithPathatoDirStreamWithPathpath(DirStreamptr)=DirStreamWithPath(path,ptr)-- | @since 2.8.6.0newtypeDirEnt=DirEnt(PtrCDirent)-- We provide a hand-written instance here since GeneralizedNewtypeDeriving and-- DerivingVia are not allowed in Safe Haskell.instanceStorableDirEntwheresizeOf_=sizeOf(undefined::PtrCDirent){-# INLINEsizeOf#-}alignment_=alignment(undefined::PtrCDirent){-# INLINEalignment#-}peekptr=DirEnt<$>peek(castPtrptr){-# INLINEpeek#-}pokeptr(DirEntdEnt)=poke(castPtrptr)dEnt{-# INLINEpoke#-}data{-# CTYPE"DIR"#-}CDirdata{-# CTYPE"struct dirent"#-}CDirent-- | The value of the @d_type@ field of a @dirent@ struct.-- Note that the possible values of that type depend on the filesystem that is-- queried. From @readdir(3)@:---- > Currently, only some filesystems (among them: Btrfs, ext2, ext3, and ext4)-- > have full support for returning the file type in d_type. All applications-- > must properly handle a return of DT_UNKNOWN.---- For example, JFS is a filesystem that does not support @d_type@;-- See https://github.com/haskell/ghcup-hs/issues/766---- Furthermore, @dirent@ or the constants represented by the associated pattern-- synonyms of this type may not be provided by the underlying platform. In that-- case none of those patterns will match and the application must handle that-- case accordingly.---- @since 2.8.6.0newtypeDirType=DirTypeCCharderiving(Eq,Ord,Show)-- | The 'DirType' refers to an entry of unknown type.patternUnknownType::DirTypepatternUnknownType=DirType(CONST_DT_UNKNOWN)-- | The 'DirType' refers to an entry that is a named pipe.patternNamedPipeType::DirTypepatternNamedPipeType=DirType(CONST_DT_FIFO)-- | The 'DirType' refers to an entry that is a character device.patternCharacterDeviceType::DirTypepatternCharacterDeviceType=DirType(CONST_DT_CHR)-- | The 'DirType' refers to an entry that is a directory.patternDirectoryType::DirTypepatternDirectoryType=DirType(CONST_DT_DIR)-- | The 'DirType' refers to an entry that is a block device.patternBlockDeviceType::DirTypepatternBlockDeviceType=DirType(CONST_DT_BLK)-- | The 'DirType' refers to an entry that is a regular file.patternRegularFileType::DirTypepatternRegularFileType=DirType(CONST_DT_REG)-- | The 'DirType' refers to an entry that is a symbolic link.patternSymbolicLinkType::DirTypepatternSymbolicLinkType=DirType(CONST_DT_LNK)-- | The 'DirType' refers to an entry that is a socket.patternSocketType::DirTypepatternSocketType=DirType(CONST_DT_SOCK)-- | The 'DirType' refers to an entry that is a whiteout.patternWhiteoutType::DirTypepatternWhiteoutType=DirType(CONST_DT_WHT)-- | Checks if this 'DirType' refers to an entry of unknown type.---- @since 2.8.6.0isUnknownType::DirType->Bool-- | Checks if this 'DirType' refers to a block device entry.---- @since 2.8.6.0isBlockDeviceType::DirType->Bool-- | Checks if this 'DirType' refers to a character device entry.---- @since 2.8.6.0isCharacterDeviceType::DirType->Bool-- | Checks if this 'DirType' refers to a named pipe entry.---- @since 2.8.6.0isNamedPipeType::DirType->Bool-- | Checks if this 'DirType' refers to a regular file entry.---- @since 2.8.6.0isRegularFileType::DirType->Bool-- | Checks if this 'DirType' refers to a directory entry.---- @since 2.8.6.0isDirectoryType::DirType->Bool-- | Checks if this 'DirType' refers to a symbolic link entry.---- @since 2.8.6.0isSymbolicLinkType::DirType->Bool-- | Checks if this 'DirType' refers to a socket entry.---- @since 2.8.6.0isSocketType::DirType->Bool-- | Checks if this 'DirType' refers to a whiteout entry.---- @since 2.8.6.0isWhiteoutType::DirType->BoolisUnknownTypedtype=dtype==UnknownTypeisBlockDeviceTypedtype=dtype==BlockDeviceTypeisCharacterDeviceTypedtype=dtype==CharacterDeviceTypeisNamedPipeTypedtype=dtype==NamedPipeTypeisRegularFileTypedtype=dtype==RegularFileTypeisDirectoryTypedtype=dtype==DirectoryTypeisSymbolicLinkTypedtype=dtype==SymbolicLinkTypeisSocketTypedtype=dtype==SocketTypeisWhiteoutTypedtype=dtype==WhiteoutType-- | @since 2.8.6.0getRealDirType::IOFileStatus->DirType->IODirTypegetRealDirType_BlockDeviceType=returnBlockDeviceTypegetRealDirType_CharacterDeviceType=returnCharacterDeviceTypegetRealDirType_NamedPipeType=returnNamedPipeTypegetRealDirType_RegularFileType=returnRegularFileTypegetRealDirType_DirectoryType=returnDirectoryTypegetRealDirType_SymbolicLinkType=returnSymbolicLinkTypegetRealDirType_SocketType=returnSocketTypegetRealDirType_WhiteoutType=returnWhiteoutTypegetRealDirTypegetFileStatus_=dostat<-getFileStatusreturn$if|isRegularFilestat->RegularFileType|isDirectorystat->DirectoryType|isSymbolicLinkstat->SymbolicLinkType|isBlockDevicestat->BlockDeviceType|isCharacterDevicestat->CharacterDeviceType|isNamedPipestat->NamedPipeType|isSocketstat->SocketType|otherwise->UnknownType-- | Call @fdopendir@ to obtain a directory stream for @fd@. @fd@ must not be-- otherwise used after this.---- On success, it is owned by the returned 'DirStream', which should be closed-- via 'closeDirStream' when no longer needed. On error, the file descriptor-- is automatically closed and then an exception is thrown. There is no code-- path in which the file descriptor remains open and yet not owned by a-- returned 'DirStream'.---- The input file descriptor must not have been used with @threadWaitRead@ or-- @threadWaitWrite@.---- @since 2.8.6.0unsafeOpenDirStreamFd::Fd->IODirStreamunsafeOpenDirStreamFd(Fdfd)=mask_$doptr<-c_fdopendirfdwhen(ptr==nullPtr)$doerrno<-getErrnovoid$c_closefdioError(errnoToIOError"openDirStreamFd"errnoNothingNothing)return$DirStreamptr-- We need c_close here, because 'closeFd' throws exceptions on error,-- but we want to silently close the (presumably directory) descriptor.foreignimportccallunsafe"HsUnix.h close"c_close::CInt->IOCInt-- NOTE: It is /critical/ to use "capi" and "dirent.h" here, because system-- headers on e.g. macOS alias this function, and linking directly to the-- "fdopendir" symbol in libc leads to a crash!--foreignimportcapiunsafe"dirent.h fdopendir"c_fdopendir::CInt->IO(PtrCDir)-- | @readDirStreamWith f dp@ calls @readdir@ to obtain the next directory entry-- (@struct dirent@) for the open directory stream @dp@. If an entry is read,-- it passes the pointer to that structure to the provided function @f@ for-- processing. It returns the result of that function call wrapped in a @Just@-- if an entry was read and @Nothing@ if the end of the directory stream was-- reached.---- __NOTE:__ The lifetime of the pointer wrapped in the `DirEnt` is limited to-- invocation of the callback and it will be freed automatically after. Do not-- pass it to the outside world!---- @since 2.8.6.0readDirStreamWith::(DirEnt->IOa)->DirStream->IO(Maybea)readDirStreamWithfdstream=alloca(\ptr_dEnt->readDirStreamWithPtrptr_dEntfdstream)-- | A version of 'readDirStreamWith' that takes a pre-allocated pointer in-- addition to the other arguments. This pointer is used to store the pointer-- to the next directory entry, if there is any. This function is intended for-- use cases where you need to read a lot of directory entries and want to-- reuse the pointer for each of them. Using for example 'readDirStream' or-- 'readDirStreamWith' in this scenario would allocate a new pointer for each-- call of these functions.---- __NOTE__: You are responsible for releasing the pointer after you are done.---- @since 2.8.6.0readDirStreamWithPtr::PtrDirEnt->(DirEnt->IOa)->DirStream->IO(Maybea)readDirStreamWithPtrptr_dEntfdstream@(DirStreamdirp)=doresetErrnor<-c_readdirdirp(castPtrptr_dEnt)if(r==0)thendodEnt@(DirEntdEntPtr)<-peekptr_dEntif(dEntPtr==nullPtr)thenreturnNothingelsedores<-fdEntc_freeDirEntdEntPtrreturn(Justres)elsedoerrno<-getErrnoif(errno==eINTR)thenreadDirStreamWithPtrptr_dEntfdstreamelsedolet(Errnoeo)=errnoif(eo==0)thenreturnNothingelsethrowErrno"readDirStream"-- | @since 2.8.6.0dirEntName::DirEnt->IOCStringdirEntName(DirEntdEntPtr)=d_namedEntPtrforeignimportccallunsafe"__hscore_d_name"d_name::PtrCDirent->IOCString-- | @since 2.8.6.0dirEntType::DirEnt->IODirTypedirEntType(DirEntdEntPtr)=DirType<$>d_typedEntPtrforeignimportccallunsafe"__hscore_d_type"d_type::PtrCDirent->IOCChar-- traversing directoriesforeignimportccallunsafe"__hscore_readdir"c_readdir::PtrCDir->Ptr(PtrCDirent)->IOCIntforeignimportccallunsafe"__hscore_free_dirent"c_freeDirEnt::PtrCDirent->IO()-- | @rewindDirStream dp@ calls @rewinddir@ to reposition-- the directory stream @dp@ at the beginning of the directory.rewindDirStream::DirStream->IO()rewindDirStream(DirStreamdirp)=c_rewinddirdirpforeignimportccallunsafe"rewinddir"c_rewinddir::PtrCDir->IO()-- | @closeDirStream dp@ calls @closedir@ to close-- the directory stream @dp@.closeDirStream::DirStream->IO()closeDirStream(DirStreamdirp)=dothrowErrnoIfMinus1Retry_"closeDirStream"(c_closedirdirp)foreignimportccallunsafe"closedir"c_closedir::PtrCDir->IOCIntnewtypeDirStreamOffset=DirStreamOffsetCOff{-# LINE 375 "System/Posix/Directory/Common.hsc" #-}seekDirStream::DirStream->DirStreamOffset->IO()seekDirStream(DirStreamdirp)(DirStreamOffsetoff)=c_seekdirdirp(fromIntegraloff)-- TODO: check for CLong/COff overflowforeignimportccallunsafe"seekdir"c_seekdir::PtrCDir->CLong->IO(){-# LINE 382 "System/Posix/Directory/Common.hsc" #-}{-# LINE 384 "System/Posix/Directory/Common.hsc" #-}tellDirStream::DirStream->IODirStreamOffsettellDirStream(DirStreamdirp)=dooff<-c_telldirdirpreturn(DirStreamOffset(fromIntegraloff))-- TODO: check for overflowforeignimportccallunsafe"telldir"c_telldir::PtrCDir->IOCLong{-# LINE 392 "System/Posix/Directory/Common.hsc" #-}{-# LINE 394 "System/Posix/Directory/Common.hsc" #-}changeWorkingDirectoryFd::Fd->IO()changeWorkingDirectoryFd(Fdfd)=throwErrnoIfMinus1Retry_"changeWorkingDirectoryFd"(c_fchdirfd)foreignimportccallunsafe"fchdir"c_fchdir::CInt->IOCInt{-# LINE 409 "System/Posix/Directory/Common.hsc" #-}

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