-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A Haskell binding for libfuse-3.x -- -- Bindings for libfuse, the FUSE userspace reference implementation, of -- version 3.x. Compatible with Linux. @package libfuse3 @version 0.2.0.1 -- | struct stat in Haskell. module System.LibFuse3.FileStat -- | A file status a.k.a. metadata. -- -- The differences from FileStatus are: -- -- -- -- Ptr FileStat can be cast to Ptr CStat and -- vice versa. -- -- Use defaultFileStat and modify its fields you are interested -- in. -- -- The st_ino field is ignored unless the use_ino mount -- option is given. -- -- The st_dev and st_blksize fields are ignored by -- libfuse, so not provided. data FileStat FileStat :: FileID -> FileMode -> LinkCount -> UserID -> GroupID -> DeviceID -> FileOffset -> CBlkCnt -> TimeSpec -> TimeSpec -> TimeSpec -> FileStat -- | Inode number. st_ino [fileID] :: FileStat -> FileID -- | File type and mode. st_mode [fileMode] :: FileStat -> FileMode -- | Number of hard links. st_nlink [linkCount] :: FileStat -> LinkCount -- | User ID of owner. st_uid [fileOwner] :: FileStat -> UserID -- | Group ID of owner. st_gid [fileGroup] :: FileStat -> GroupID -- | Device ID (if special file). st_rdev [specialDeviceID] :: FileStat -> DeviceID -- | Total size, in bytes. st_size [fileSize] :: FileStat -> FileOffset -- | Number of 512B blocks allocated. st_blocks [blockCount] :: FileStat -> CBlkCnt -- | Time of last access. st_atim [accessTimeHiRes] :: FileStat -> TimeSpec -- | Time of last modification. st_mtim [modificationTimeHiRes] :: FileStat -> TimeSpec -- | Time of last status change. st_ctim [statusChangeTimeHiRes] :: FileStat -> TimeSpec -- | The default value of FileStat. -- -- The Haskell Equivalent of zero-setting C code { struct stat st; -- memset(&st, 0, sizeof(struct stat)); }. defaultFileStat :: FileStat -- | Reads a file status of a given file. -- -- Calls lstat. getFileStat :: FilePath -> IO FileStat -- | Reads a file status of a given file. -- -- Calls fstat. getFileStatFd :: Fd -> IO FileStat instance GHC.Show.Show System.LibFuse3.FileStat.FileStat instance GHC.Classes.Eq System.LibFuse3.FileStat.FileStat instance Foreign.Storable.Storable System.LibFuse3.FileStat.FileStat -- | struct statvfs in Haskell. module System.LibFuse3.FileSystemStats -- | Passed to fuseStatfs. -- -- The Storable instance targets C struct statvfs. -- -- f_favail, f_fsid and f_flag fields are -- ignored by libfuse, and their corresponding fields are not defined. data FileSystemStats FileSystemStats :: CULong -> CULong -> CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt -> CFsFilCnt -> CFsFilCnt -> CULong -> FileSystemStats -- | Filesystem block size. f_bsize [blockSize] :: FileSystemStats -> CULong -- | Fragment size. f_frsize [fragmentSize] :: FileSystemStats -> CULong -- | Size of the filesystem in f_frsize units. f_blocks [blockCount] :: FileSystemStats -> CFsBlkCnt -- | Number of free blocks. f_bfree [blocksFree] :: FileSystemStats -> CFsBlkCnt -- | Number of free blocks for unprivileged users. f_bavail [blocksAvailable] :: FileSystemStats -> CFsBlkCnt -- | Number of inodes (file nodes). f_files [fileCount] :: FileSystemStats -> CFsFilCnt -- | Number of free inodes. f_ffree [filesFree] :: FileSystemStats -> CFsFilCnt -- | Maximum filename length. f_namemax [maxNameLength] :: FileSystemStats -> CULong -- | Gets filesystem statistics. -- -- Calls statvfs. getFileSystemStats :: FilePath -> IO FileSystemStats -- | Gets filesystem statistics. -- -- Calls fstatvfs. getFileSystemStatsFd :: Fd -> IO FileSystemStats c_fstatvfs :: Fd -> Ptr FileSystemStats -> IO CInt c_statvfs :: CString -> Ptr FileSystemStats -> IO CInt instance GHC.Show.Show System.LibFuse3.FileSystemStats.FileSystemStats instance GHC.Classes.Eq System.LibFuse3.FileSystemStats.FileSystemStats instance Foreign.Storable.Storable System.LibFuse3.FileSystemStats.FileSystemStats -- | C land. -- -- This is an internal module. It is exposed to allow fine-tuning and -- workarounds but its API is not stable. module System.LibFuse3.Internal.C -- |
--   struct fuse_args
--   
data FuseArgs -- |
--   struct fuse_buf
--   
data FuseBuf -- |
--   struct fuse_bufvec
--   
data FuseBufvec -- |
--   struct fuse_cmdline_opts
--   
data FuseCmdlineOpts -- | The direct, storable representation of struct fuse_config. -- -- Not to be confused with the high-level FuseConfig. data FuseConfig FuseConfig :: CInt -> CUInt -> CInt -> CUInt -> CInt -> CUInt -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CDouble -> CInt -> FuseConfig -- |
--   set_gid
--   
[setGid] :: FuseConfig -> CInt -- |
--   gid
--   
[gid] :: FuseConfig -> CUInt -- |
--   set_uid
--   
[setUid] :: FuseConfig -> CInt -- |
--   uid
--   
[uid] :: FuseConfig -> CUInt -- |
--   set_mode
--   
[setMode] :: FuseConfig -> CInt -- |
--   umask
--   
[umask] :: FuseConfig -> CUInt -- |
--   entry_timeout
--   
[entryTimeout] :: FuseConfig -> CDouble -- |
--   negative_timeout
--   
[negativeTimeout] :: FuseConfig -> CDouble -- |
--   attr_timeout
--   
[attrTimeout] :: FuseConfig -> CDouble -- |
--   intr
--   
[intr] :: FuseConfig -> CInt -- |
--   intr_signal
--   
[intrSignal] :: FuseConfig -> CInt -- |
--   remember
--   
[remember] :: FuseConfig -> CInt -- |
--   hard_remove
--   
[hardRemove] :: FuseConfig -> CInt -- |
--   use_ino
--   
[useIno] :: FuseConfig -> CInt -- |
--   readdir_ino
--   
[readdirIno] :: FuseConfig -> CInt -- |
--   direct_io
--   
[directIo] :: FuseConfig -> CInt -- |
--   kernel_cache
--   
[kernelCache] :: FuseConfig -> CInt -- |
--   auto_cache
--   
[autoCache] :: FuseConfig -> CInt -- |
--   ac_attr_timeout_set
--   
[acAttrTimeoutSet] :: FuseConfig -> CInt -- |
--   ac_attr_timeout
--   
[acAttrTimeout] :: FuseConfig -> CDouble -- |
--   nullpath_ok
--   
[nullpathOk] :: FuseConfig -> CInt -- |
--   struct fuse_conn_info
--   
data FuseConnInfo -- |
--   struct fuse_file_info
--   
data FuseFileInfo -- |
--   typedef fuse_fill_dir_t
--   
type FuseFillDir = Ptr FuseFillDirBuf -> CString -> Ptr FileStat -> COff -> FuseFillDirFlags -> IO CInt -- | Ptr FuseFillDirBuf = void *, used in FuseFillDir. data FuseFillDirBuf -- |
--   enum fuse_fill_dir_flags
--   
type FuseFillDirFlags = Word32 -- | The direct, storable representation of struct -- fuse_operations. -- -- All operations are optional. NULL indicates undefined operation. You -- may modify some of the fields to fine-tune the behavior. -- -- Not to be confused with Haskell-friendly FuseOperations. Also -- not to be confused with libfuse's low-level API struct -- fuse_lowlevel_ops. data FuseOperations FuseOperations :: FunPtr CGetattr -> FunPtr CReadlink -> FunPtr CMknod -> FunPtr CMkdir -> FunPtr CUnlink -> FunPtr CRmdir -> FunPtr CSymlink -> FunPtr CRename -> FunPtr CLink -> FunPtr CChmod -> FunPtr CChown -> FunPtr CTruncate -> FunPtr COpen -> FunPtr CRead -> FunPtr CWrite -> FunPtr CStatfs -> FunPtr CFlush -> FunPtr CRelease -> FunPtr CFsync -> FunPtr CSetxattr -> FunPtr CGetxattr -> FunPtr CListxattr -> FunPtr CRemovexattr -> FunPtr COpendir -> FunPtr CReaddir -> FunPtr CReleasedir -> FunPtr CFsyncdir -> FunPtr CInit -> FunPtr CDestroy -> FunPtr CAccess -> FunPtr CCreate -> FunPtr CLock -> FunPtr CUtimens -> FunPtr CBmap -> FunPtr CIoctl -> FunPtr CPoll -> FunPtr CWriteBuf -> FunPtr CReadBuf -> FunPtr CFlock -> FunPtr CFallocate -> FunPtr CCopyFileRange -> FunPtr CLseek -> FuseOperations [fuseGetattr] :: FuseOperations -> FunPtr CGetattr [fuseReadlink] :: FuseOperations -> FunPtr CReadlink [fuseMknod] :: FuseOperations -> FunPtr CMknod [fuseMkdir] :: FuseOperations -> FunPtr CMkdir [fuseUnlink] :: FuseOperations -> FunPtr CUnlink [fuseRmdir] :: FuseOperations -> FunPtr CRmdir [fuseSymlink] :: FuseOperations -> FunPtr CSymlink [fuseRename] :: FuseOperations -> FunPtr CRename [fuseLink] :: FuseOperations -> FunPtr CLink [fuseChmod] :: FuseOperations -> FunPtr CChmod [fuseChown] :: FuseOperations -> FunPtr CChown [fuseTruncate] :: FuseOperations -> FunPtr CTruncate [fuseOpen] :: FuseOperations -> FunPtr COpen [fuseRead] :: FuseOperations -> FunPtr CRead [fuseWrite] :: FuseOperations -> FunPtr CWrite [fuseStatfs] :: FuseOperations -> FunPtr CStatfs [fuseFlush] :: FuseOperations -> FunPtr CFlush [fuseRelease] :: FuseOperations -> FunPtr CRelease [fuseFsync] :: FuseOperations -> FunPtr CFsync [fuseSetxattr] :: FuseOperations -> FunPtr CSetxattr [fuseGetxattr] :: FuseOperations -> FunPtr CGetxattr [fuseListxattr] :: FuseOperations -> FunPtr CListxattr [fuseRemovexattr] :: FuseOperations -> FunPtr CRemovexattr [fuseOpendir] :: FuseOperations -> FunPtr COpendir [fuseReaddir] :: FuseOperations -> FunPtr CReaddir [fuseReleasedir] :: FuseOperations -> FunPtr CReleasedir [fuseFsyncdir] :: FuseOperations -> FunPtr CFsyncdir [fuseInit] :: FuseOperations -> FunPtr CInit [fuseDestroy] :: FuseOperations -> FunPtr CDestroy [fuseAccess] :: FuseOperations -> FunPtr CAccess [fuseCreate] :: FuseOperations -> FunPtr CCreate [fuseLock] :: FuseOperations -> FunPtr CLock [fuseUtimens] :: FuseOperations -> FunPtr CUtimens [fuseBmap] :: FuseOperations -> FunPtr CBmap [fuseIoctl] :: FuseOperations -> FunPtr CIoctl [fusePoll] :: FuseOperations -> FunPtr CPoll [fuseWriteBuf] :: FuseOperations -> FunPtr CWriteBuf [fuseReadBuf] :: FuseOperations -> FunPtr CReadBuf [fuseFlock] :: FuseOperations -> FunPtr CFlock [fuseFallocate] :: FuseOperations -> FunPtr CFallocate [fuseCopyFileRange] :: FuseOperations -> FunPtr CCopyFileRange [fuseLseek] :: FuseOperations -> FunPtr CLseek -- | An empty set of operations whose fields are nullFunPtr. defaultFuseOperations :: FuseOperations -- | Merges two FuseOperations in a left-biased manner. mergeLFuseOperations :: FuseOperations -> FuseOperations -> FuseOperations -- |
--   struct fuse_pollhandle
--   
data FusePollhandle -- |
--   enum fuse_readdir_flags
--   
type FuseReaddirFlags = Word32 -- |
--   struct fuse_session
--   
data FuseSession -- |
--   struct fuse
--   
data StructFuse fuse_cmdline_help :: IO () fuse_destroy :: Ptr StructFuse -> IO () fuse_get_session :: Ptr StructFuse -> IO (Ptr FuseSession) fuse_lib_help :: Ptr FuseArgs -> IO () fuse_loop_mt_31 :: Ptr StructFuse -> CInt -> IO Int fuse_lowlevel_help :: IO () fuse_lowlevel_version :: IO () fuse_mount :: Ptr StructFuse -> CString -> IO CInt fuse_new :: Ptr FuseArgs -> Ptr FuseOperations -> CSize -> Ptr a -> IO (Ptr StructFuse) fuse_opt_free_args :: Ptr FuseArgs -> IO () fuse_parse_cmdline :: Ptr FuseArgs -> Ptr FuseCmdlineOpts -> IO CInt fuse_pkgversion :: IO CString fuse_session_exit :: Ptr FuseSession -> IO () fuse_unmount :: Ptr StructFuse -> IO () type CGetattr = CString -> Ptr FileStat -> Ptr FuseFileInfo -> IO CInt mkGetattr :: CGetattr -> IO (FunPtr CGetattr) type CReadlink = CString -> CString -> CSize -> IO CInt mkReadlink :: CReadlink -> IO (FunPtr CReadlink) type CMknod = CString -> CMode -> CDev -> IO CInt mkMknod :: CMknod -> IO (FunPtr CMknod) type CMkdir = CString -> CMode -> IO CInt mkMkdir :: CMkdir -> IO (FunPtr CMkdir) type CUnlink = CString -> IO CInt mkUnlink :: CUnlink -> IO (FunPtr CUnlink) type CRmdir = CString -> IO CInt mkRmdir :: CRmdir -> IO (FunPtr CRmdir) type CSymlink = CString -> CString -> IO CInt mkSymlink :: CSymlink -> IO (FunPtr CSymlink) type CRename = CString -> CString -> CUInt -> IO CInt mkRename :: CRename -> IO (FunPtr CRename) type CLink = CString -> CString -> IO CInt mkLink :: CLink -> IO (FunPtr CLink) type CChmod = CString -> CMode -> Ptr FuseFileInfo -> IO CInt mkChmod :: CChmod -> IO (FunPtr CChmod) type CChown = CString -> CUid -> CGid -> Ptr FuseFileInfo -> IO CInt mkChown :: CChown -> IO (FunPtr CChown) type CTruncate = CString -> COff -> Ptr FuseFileInfo -> IO CInt mkTruncate :: CTruncate -> IO (FunPtr CTruncate) type COpen = CString -> Ptr FuseFileInfo -> IO CInt mkOpen :: COpen -> IO (FunPtr COpen) type CRead = CString -> CString -> CSize -> COff -> Ptr FuseFileInfo -> IO CInt mkRead :: CRead -> IO (FunPtr CRead) type CWrite = CString -> CString -> CSize -> COff -> Ptr FuseFileInfo -> IO CInt mkWrite :: CWrite -> IO (FunPtr CWrite) type CStatfs = CString -> Ptr FileSystemStats -> IO CInt mkStatfs :: CStatfs -> IO (FunPtr CStatfs) type CFlush = CString -> Ptr FuseFileInfo -> IO CInt mkFlush :: CFlush -> IO (FunPtr CFlush) type CRelease = CString -> Ptr FuseFileInfo -> IO CInt mkRelease :: CRelease -> IO (FunPtr CRelease) type CFsync = CString -> CInt -> Ptr FuseFileInfo -> IO CInt mkFsync :: CFsync -> IO (FunPtr CFsync) type CSetxattr = CString -> CString -> CString -> CSize -> CInt -> IO CInt mkSetxattr :: CSetxattr -> IO (FunPtr CSetxattr) type CGetxattr = CString -> CString -> CString -> CSize -> IO CInt mkGetxattr :: CGetxattr -> IO (FunPtr CGetxattr) type CListxattr = CString -> CString -> CSize -> IO CInt mkListxattr :: CListxattr -> IO (FunPtr CListxattr) type CRemovexattr = CString -> CString -> IO CInt mkRemovexattr :: CRemovexattr -> IO (FunPtr CRemovexattr) type COpendir = CString -> Ptr FuseFileInfo -> IO CInt mkOpendir :: COpendir -> IO (FunPtr COpendir) type CReaddir = CString -> Ptr FuseFillDirBuf -> FunPtr FuseFillDir -> COff -> Ptr FuseFileInfo -> FuseReaddirFlags -> IO CInt mkReaddir :: CReaddir -> IO (FunPtr CReaddir) type CReleasedir = CString -> Ptr FuseFileInfo -> IO CInt mkReleasedir :: CReleasedir -> IO (FunPtr CReleasedir) type CFsyncdir = CString -> CInt -> Ptr FuseFileInfo -> IO CInt mkFsyncdir :: CFsyncdir -> IO (FunPtr CFsyncdir) type CInit = Ptr FuseConnInfo -> Ptr FuseConfig -> IO (Ptr ()) mkInit :: CInit -> IO (FunPtr CInit) type CDestroy = Ptr () -> IO () mkDestroy :: CDestroy -> IO (FunPtr CDestroy) type CAccess = CString -> CInt -> IO CInt mkAccess :: CAccess -> IO (FunPtr CAccess) type CCreate = CString -> CMode -> Ptr FuseFileInfo -> IO CInt mkCreate :: CCreate -> IO (FunPtr CCreate) type CLock = CString -> Ptr FuseFileInfo -> CInt -> Ptr CFLock mkLock :: CLock -> IO (FunPtr CLock) type CUtimens = CString -> Ptr TimeSpec -> Ptr FuseFileInfo -> IO CInt mkUtimens :: CUtimens -> IO (FunPtr CUtimens) type CBmap = CString -> CSize -> Ptr Word64 -> IO CInt mkBmap :: CBmap -> IO (FunPtr CBmap) type CIoctl = CString -> CUInt -> Ptr () -> Ptr FuseFileInfo -> CUInt -> Ptr () -> IO CInt mkIoctl :: CIoctl -> IO (FunPtr CIoctl) type CPoll = CString -> Ptr FuseFileInfo -> Ptr FusePollhandle -> Ptr CUInt -> IO CInt mkPoll :: CPoll -> IO (FunPtr CPoll) type CWriteBuf = CString -> Ptr FuseBufvec -> COff -> Ptr FuseFileInfo -> IO CInt mkWriteBuf :: CWriteBuf -> IO (FunPtr CWriteBuf) type CReadBuf = CString -> Ptr (Ptr FuseBufvec) -> CSize -> COff -> Ptr FuseFileInfo -> IO CInt mkReadBuf :: CReadBuf -> IO (FunPtr CReadBuf) type CFlock = CString -> Ptr FuseFileInfo -> CInt -> IO CInt mkFlock :: CFlock -> IO (FunPtr CFlock) type CFallocate = CString -> CInt -> COff -> COff -> Ptr FuseFileInfo -> IO CInt mkFallocate :: CFallocate -> IO (FunPtr CFallocate) type CCopyFileRange = CString -> Ptr FuseFileInfo -> COff -> CString -> Ptr FuseFileInfo -> COff -> CSize -> CInt -> IO CSsize mkCopyFileRange :: CCopyFileRange -> IO (FunPtr CCopyFileRange) type CLseek = CString -> COff -> CInt -> Ptr FuseFileInfo -> IO COff mkLseek :: CLseek -> IO (FunPtr CLseek) instance GHC.Show.Show System.LibFuse3.Internal.C.FuseConfig instance GHC.Classes.Eq System.LibFuse3.Internal.C.FuseConfig instance Foreign.Storable.Storable System.LibFuse3.Internal.C.FuseOperations instance Foreign.Storable.Storable System.LibFuse3.Internal.C.FuseConfig -- | The Haskell-friendly interface of struct fuse_config. module System.LibFuse3.FuseConfig -- | Configures the filesystem. Passed to fuseInit. -- -- See the module System.LibFuse3.FuseConfig for its fields. data FuseConfig FuseConfig :: Bool -> GroupID -> Bool -> UserID -> Bool -> FileMode -> Double -> Double -> Double -> Bool -> Signal -> Int -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Double -> Bool -> FuseConfig -- |
--   set_gid
--   
[setGid] :: FuseConfig -> Bool -- |
--   gid
--   
[gid] :: FuseConfig -> GroupID -- |
--   set_uid
--   
[setUid] :: FuseConfig -> Bool -- |
--   uid
--   
[uid] :: FuseConfig -> UserID -- |
--   set_mode
--   
[setMode] :: FuseConfig -> Bool -- |
--   umask
--   
[umask] :: FuseConfig -> FileMode -- |
--   entry_timeout
--   
[entryTimeout] :: FuseConfig -> Double -- |
--   negative_timeout
--   
[negativeTimeout] :: FuseConfig -> Double -- |
--   attr_timeout
--   
[attrTimeout] :: FuseConfig -> Double -- |
--   intr
--   
[intr] :: FuseConfig -> Bool -- |
--   intr_signal
--   
[intrSignal] :: FuseConfig -> Signal -- |
--   remember
--   
[remember] :: FuseConfig -> Int -- |
--   hard_remove
--   
[hardRemove] :: FuseConfig -> Bool -- |
--   use_ino
--   
[useIno] :: FuseConfig -> Bool -- |
--   readdir_ino
--   
[readdirIno] :: FuseConfig -> Bool -- |
--   direct_io
--   
[directIo] :: FuseConfig -> Bool -- |
--   kernel_cache
--   
[kernelCache] :: FuseConfig -> Bool -- |
--   auto_cache
--   
[autoCache] :: FuseConfig -> Bool -- |
--   ac_attr_timeout_set
--   
[acAttrTimeoutSet] :: FuseConfig -> Bool -- |
--   ac_attr_timeout
--   
[acAttrTimeout] :: FuseConfig -> Double -- |
--   nullpath_ok
--   
[nullpathOk] :: FuseConfig -> Bool -- | Converts to the Storable counterpart. toCFuseConfig :: FuseConfig -> FuseConfig -- | Converts from the Storable counterpart. fromCFuseConfig :: FuseConfig -> FuseConfig instance GHC.Show.Show System.LibFuse3.FuseConfig.FuseConfig instance GHC.Classes.Eq System.LibFuse3.FuseConfig.FuseConfig -- | Utils related to ResourceT -- -- This is an internal module. It is exposed to allow fine-tuning and -- workarounds but its API is not stable. module System.LibFuse3.Internal.Resource -- | Forks a new process and transfers the resources to it. -- -- The parent process exitImmediately. daemonizeResourceT :: ResourceT IO a -> ResourceT IO b -- | callocBytes with free associated as a cleanup action. resCallocBytes :: Int -> ResourceT IO (ReleaseKey, Ptr a) -- | mallocBytes with free associated as a cleanup action. resMallocBytes :: Int -> ResourceT IO (ReleaseKey, Ptr a) -- | new with free associated as a cleanup action. resNew :: Storable a => a -> ResourceT IO (ReleaseKey, Ptr a) -- | newCString with free associated as a cleanup action. resNewCString :: String -> ResourceT IO (ReleaseKey, CString) -- | newFilePath with free associated as a cleanup action. resNewFilePath :: FilePath -> ResourceT IO (ReleaseKey, CString) -- | newArray with free associated as a cleanup action. resNewArray :: Storable a => [a] -> ResourceT IO (ReleaseKey, Ptr a) -- | Miscellaneous utilities provided for convenience. -- -- These can be used for general purpose and are not directly related to -- FUSE. module System.LibFuse3.Utils -- | testBitSet bits mask is True iff all bits in -- mask are set in bits. -- --
--   testBitSet bits mask ≡ bits .&. mask == mask
--   
testBitSet :: Bits a => a -> a -> Bool -- | Unwraps the newtype Errno. unErrno :: Errno -> CInt -- | Attempts to extract an Errno from an IOError assuming it -- is constructed with errnoToIOError (typically via -- throwErrno). ioErrorToErrno :: IOError -> Maybe Errno -- | Like throwErrno but takes an Errno as a parameter -- instead of reading from getErrno. -- -- This is an inverse of tryErrno: -- --
--   tryErrno (throwErrnoOf _ e) ≡ pure (Left e)
--   
throwErrnoOf :: String -> Errno -> IO a -- | Catches an exception constructed with errnoToIOError and -- extracts Errno from it. tryErrno :: IO a -> IO (Either Errno a) -- | Like tryErrno but discards the result of the original action. -- -- If no exceptions, returns eOK. tryErrno_ :: IO a -> IO Errno -- | Like tryErrno but also catches non-Errno errors to return -- eIO. tryErrno' :: IO a -> IO (Either Errno a) -- | Like tryErrno_ but also catches non-Errno errors to return -- eIO. tryErrno_' :: IO a -> IO Errno -- | Reads from a file descriptor at a given offset. -- -- Fewer bytes may be read than requested. On error, throws an -- IOError corresponding to the errno. pread :: Fd -> ByteCount -> FileOffset -> IO ByteString -- | Writes to a file descriptor at a given offset. -- -- Returns the number of bytes written. Fewer bytes may be written than -- requested. On error, throws an IOError corresponding to the -- errno. pwrite :: Fd -> ByteString -> FileOffset -> IO CSsize -- | A foreign import of pread(2) c_pread :: CInt -> Ptr a -> CSize -> COff -> IO CSsize -- | A foreign import of pwrite(2) c_pwrite :: CInt -> Ptr a -> CSize -> COff -> IO CSsize -- | Marshals a Haskell string into a NUL terminated C string in a -- locale-dependent way. -- -- Does withCStringLen and copies it into the destination buffer. -- -- The Haskell string should not contain NUL characters. -- -- If the destination buffer is not long enough to hold the source -- string, it is truncated and a NUL byte is inserted at the end of the -- buffer. pokeCStringLen0 :: CStringLen -> String -> IO () -- | Converts a TimeSpec to a POSIXTime. -- -- This is the same conversion as the unix package does (as of -- writing). timeSpecToPOSIXTime :: TimeSpec -> POSIXTime -- | The core stuff -- -- This is an internal module. It is exposed to allow fine-tuning and -- workarounds but its API is not stable. module System.LibFuse3.Internal -- | The Unix type of a node in the filesystem. data EntryType -- | Unknown entry type Unknown :: EntryType NamedPipe :: EntryType CharacterSpecial :: EntryType Directory :: EntryType BlockSpecial :: EntryType RegularFile :: EntryType SymbolicLink :: EntryType Socket :: EntryType -- | Converts an EntryType into the corresponding POSIX -- FileMode. entryTypeToFileMode :: EntryType -> FileMode -- | Decodes EntryType from a FileMode. fileModeToEntryType :: FileMode -> EntryType -- | Passed to fuseFsync and fuseFsyncdir. data SyncType -- | Synchronize both file content and metadata. FullSync :: SyncType -- | Synchronize only the file content. DataSync :: SyncType -- | The query type of access. Passed to fuseAccess. data AccessMode -- | File existence (F_OK) FileOK :: AccessMode -- | Reading, writing and executing permissions (R_OK, -- W_OK and X_OK, resp.) PermOK :: Bool -> Bool -> Bool -> AccessMode -- | Passed to fuseSetxattr. data SetxattrFlag -- | Create a new attribute if it does not exist, or replace the value if -- it already exists (0) SetxattrDefault :: SetxattrFlag -- | Perform a pure create, which fails if the named attribute exists -- already (XATTR_CREATE) SetxattrCreate :: SetxattrFlag -- | Perform a pure replace operation, which fails if the named attribute -- does not already exist (XATTR_REPLACE) SetxattrReplace :: SetxattrFlag -- | Tests if access permissions to the file is granted or the file exists. -- -- Calls access. Compared to fileAccess and -- fileExist, this function doesn't translate the errno and just -- returns () to indicate success, or throws an error to -- indicate failure. access :: FilePath -> AccessMode -> IO () -- | Same as access but returns the Errno instead of throwing -- an exception. -- -- Returns eOK on success. accessErrno :: FilePath -> AccessMode -> IO Errno -- | The file system operations. -- -- All operations are optional. Each field is named against struct -- fuse_operations in fuse.h. -- -- fh is the file handle type returned by fuseOpen, and -- subsequently passed to all other file operations. -- -- dh is the directory handle type returned by -- fuseOpendir, and subsequently passed to fuseReaddir and -- fuseReleasedir. data FuseOperations fh dh FuseOperations :: Maybe (FilePath -> Maybe fh -> IO (Either Errno FileStat)) -> Maybe (FilePath -> IO (Either Errno FilePath)) -> Maybe (FilePath -> FileMode -> DeviceID -> IO Errno) -> Maybe (FilePath -> FileMode -> IO Errno) -> Maybe (FilePath -> IO Errno) -> Maybe (FilePath -> IO Errno) -> Maybe (FilePath -> FilePath -> IO Errno) -> Maybe (FilePath -> FilePath -> IO Errno) -> Maybe (FilePath -> FilePath -> IO Errno) -> Maybe (FilePath -> Maybe fh -> FileMode -> IO Errno) -> Maybe (FilePath -> Maybe fh -> UserID -> GroupID -> IO Errno) -> Maybe (FilePath -> Maybe fh -> FileOffset -> IO Errno) -> Maybe (FilePath -> OpenMode -> OpenFileFlags -> IO (Either Errno fh)) -> Maybe (FilePath -> fh -> ByteCount -> FileOffset -> IO (Either Errno ByteString)) -> Maybe (FilePath -> fh -> ByteString -> FileOffset -> IO (Either Errno CInt)) -> Maybe (String -> IO (Either Errno FileSystemStats)) -> Maybe (FilePath -> fh -> IO Errno) -> Maybe (FilePath -> fh -> IO ()) -> Maybe (FilePath -> fh -> SyncType -> IO Errno) -> Maybe (FilePath -> String -> ByteString -> SetxattrFlag -> IO Errno) -> Maybe (FilePath -> String -> IO (Either Errno ByteString)) -> Maybe (FilePath -> IO (Either Errno [String])) -> Maybe (FilePath -> String -> IO Errno) -> Maybe (FilePath -> IO (Either Errno dh)) -> Maybe (FilePath -> dh -> IO (Either Errno [(String, Maybe FileStat)])) -> Maybe (FilePath -> dh -> IO Errno) -> Maybe (FilePath -> dh -> SyncType -> IO Errno) -> Maybe (FuseConfig -> IO FuseConfig) -> Maybe (IO ()) -> Maybe (FilePath -> AccessMode -> IO Errno) -> Maybe (FilePath -> OpenMode -> FileMode -> OpenFileFlags -> IO (Either Errno fh)) -> Maybe (FilePath -> Maybe fh -> TimeSpec -> TimeSpec -> IO Errno) -> Maybe (FilePath -> fh -> CInt -> FileOffset -> FileOffset -> IO Errno) -> Maybe (FilePath -> fh -> FileOffset -> FilePath -> fh -> FileOffset -> ByteCount -> CInt -> IO (Either Errno CSsize)) -> Maybe (FilePath -> fh -> FileOffset -> SeekMode -> IO (Either Errno FileOffset)) -> FuseOperations fh dh -- | Implements getSymbolicLinkStatus operation (POSIX -- lstat(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. [fuseGetattr] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> IO (Either Errno FileStat)) -- | Implements readSymbolicLink operation (POSIX -- readlink(2)). -- -- This function should not append a terminating NUL byte. The returned -- FilePath might be truncated depending on caller buffer size. [fuseReadlink] :: FuseOperations fh dh -> Maybe (FilePath -> IO (Either Errno FilePath)) -- | Implements createDevice (POSIX mknod(2)). -- -- This function will also be called for regular file creation if -- fuseCreate is not defined. -- -- fileModeToEntryType is handy to pattern match on the request -- type of the node. [fuseMknod] :: FuseOperations fh dh -> Maybe (FilePath -> FileMode -> DeviceID -> IO Errno) -- | Implements createDirectory (POSIX mkdir(2)). [fuseMkdir] :: FuseOperations fh dh -> Maybe (FilePath -> FileMode -> IO Errno) -- | Implements removeLink (POSIX unlink(2)). [fuseUnlink] :: FuseOperations fh dh -> Maybe (FilePath -> IO Errno) -- | Implements removeDirectory (POSIX rmdir(2)). [fuseRmdir] :: FuseOperations fh dh -> Maybe (FilePath -> IO Errno) -- | Implements createSymbolicLink (POSIX symlink(2)). [fuseSymlink] :: FuseOperations fh dh -> Maybe (FilePath -> FilePath -> IO Errno) -- | Implements rename (POSIX rename(2)). [fuseRename] :: FuseOperations fh dh -> Maybe (FilePath -> FilePath -> IO Errno) -- | Implements createLink (POSIX link(2)). [fuseLink] :: FuseOperations fh dh -> Maybe (FilePath -> FilePath -> IO Errno) -- | Implements setFileMode (POSIX chmod(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. [fuseChmod] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> FileMode -> IO Errno) -- | Implements setOwnerAndGroup (POSIX chown(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. -- -- Unless FUSE_CAP_HANDLE_KILLPRIV is disabled, this method is -- expected to reset the setuid and setgid bits. [fuseChown] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> UserID -> GroupID -> IO Errno) -- | Implements setFileSize (POSIX truncate(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. -- -- Unless FUSE_CAP_HANDLE_KILLPRIV is disabled, this method is -- expected to reset the setuid and setgid bits. [fuseTruncate] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> FileOffset -> IO Errno) -- | Implements openFd (POSIX open(2)). On success, returns -- Right of a filehandle-like value that will be passed to future -- file operations; on failure, returns Left of the appropriate -- Errno. -- -- -- -- TODO allow this method to set fuse_file_info.direct_io and -- fuse_file_info.keep_cache [fuseOpen] :: FuseOperations fh dh -> Maybe (FilePath -> OpenMode -> OpenFileFlags -> IO (Either Errno fh)) -- | Implements Unix98 pread(2). -- -- It differs from fdRead by the explicit FileOffset -- argument. [fuseRead] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> ByteCount -> FileOffset -> IO (Either Errno ByteString)) -- | Implements Unix98 pwrite(2). -- -- It differs from fdWrite by the explicit FileOffset -- argument. -- -- Unless FUSE_CAP_HANDLE_KILLPRIV is disabled, this method is -- expected to reset the setuid and setgid bits. [fuseWrite] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> ByteString -> FileOffset -> IO (Either Errno CInt)) -- | Implements statfs(2). [fuseStatfs] :: FuseOperations fh dh -> Maybe (String -> IO (Either Errno FileSystemStats)) -- | Called when close(2) has been called on an open file. -- -- Note: this does not mean that the file is released. This function may -- be called more than once for each open(2). The return value -- is passed on to the close(2) system call. [fuseFlush] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> IO Errno) -- | Called when an open file has all file descriptors closed and all -- memory mappings unmapped. -- -- For every open call there will be exactly one -- release call with the same flags. It is possible to have a -- file opened more than once, in which case only the last release will -- mean that no more reads or writes will happen on the file. [fuseRelease] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> IO ()) -- | Implements fsync(2). [fuseFsync] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> SyncType -> IO Errno) -- | Implements setxattr(2). -- -- The parameters are: path, name, value and flags. [fuseSetxattr] :: FuseOperations fh dh -> Maybe (FilePath -> String -> ByteString -> SetxattrFlag -> IO Errno) -- | Implements getxattr(2). -- -- The parameters are path and name. [fuseGetxattr] :: FuseOperations fh dh -> Maybe (FilePath -> String -> IO (Either Errno ByteString)) -- | Implements listxattr(2). [fuseListxattr] :: FuseOperations fh dh -> Maybe (FilePath -> IO (Either Errno [String])) -- | Implements removexattr(2). [fuseRemovexattr] :: FuseOperations fh dh -> Maybe (FilePath -> String -> IO Errno) -- | Implements opendir(3). -- -- This method should check if the open operation is permitted for this -- directory. [fuseOpendir] :: FuseOperations fh dh -> Maybe (FilePath -> IO (Either Errno dh)) -- | Implements readdir(3). -- -- The entire contents of the directory should be returned as a list of -- tuples (corresponding to the first mode of operation documented in -- fuse.h). -- -- The returned list should contain entries of "." and "..". -- -- Each element of the list is a pair of the name and the stat. The name -- should not include the path to it. The implementation may return -- Nothing as the stat; in this case fuseGetattr is -- called instead. [fuseReaddir] :: FuseOperations fh dh -> Maybe (FilePath -> dh -> IO (Either Errno [(String, Maybe FileStat)])) -- | Implements closedir(3). [fuseReleasedir] :: FuseOperations fh dh -> Maybe (FilePath -> dh -> IO Errno) -- | Synchronize the directory's contents; analogous to fuseFsync. [fuseFsyncdir] :: FuseOperations fh dh -> Maybe (FilePath -> dh -> SyncType -> IO Errno) -- | Initializes the filesystem. This is called before all other -- operations. -- -- The filesystem may modify FuseConfig to configure the API. [fuseInit] :: FuseOperations fh dh -> Maybe (FuseConfig -> IO FuseConfig) -- | Called on filesystem exit to allow cleanup. [fuseDestroy] :: FuseOperations fh dh -> Maybe (IO ()) -- | Implements fileAccess and 'System.Posix.Files.fileExist (POSIX -- access(2)). -- -- Checks file access permissions as requested by an AccessMode. -- -- If the default_permissions mount option is given, this method -- is not called. This method is also not called under Linux kernel -- versions 2.4.x -- -- TODO add notes about default_permissions to other relevant -- handlers [fuseAccess] :: FuseOperations fh dh -> Maybe (FilePath -> AccessMode -> IO Errno) -- | Implements openFd (POSIX open(2)). Creates and opens a -- regular file. -- -- If this is not implemented, fuseMknod and fuseOpen -- methods will be called instead. -- -- See fuseOpen for notes on the flags. [fuseCreate] :: FuseOperations fh dh -> Maybe (FilePath -> OpenMode -> FileMode -> OpenFileFlags -> IO (Either Errno fh)) -- | Implements utimensat(2). -- -- Changes the access and modification times of a file with nanosecond -- resolution. -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. [fuseUtimens] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> TimeSpec -> TimeSpec -> IO Errno) -- | Implements fileAllocate (posix_fallocate(3)). -- Allocates space for an open file. [fuseFallocate] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> CInt -> FileOffset -> FileOffset -> IO Errno) -- | Implements copy_file_range(2). [fuseCopyFileRange] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> FileOffset -> FilePath -> fh -> FileOffset -> ByteCount -> CInt -> IO (Either Errno CSsize)) -- | Implements fdSeek lseek(3). -- -- Note: This is silently ignored if libfuse doesn't support -- lseek operation (requires libfuse-3.8.0). [fuseLseek] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> FileOffset -> SeekMode -> IO (Either Errno FileOffset)) -- | An empty set of operations whose fields are Nothing. defaultFuseOperations :: FuseOperations fh dh -- | Merges two FuseOperations in a left-biased manner. mergeLFuseOperations :: FuseOperations fh dh -> FuseOperations fh dh -> FuseOperations fh dh -- | Allocates a fuse_operations struct and pokes -- FuseOperations into it. -- -- Each field of FuseOperations is converted into a C function -- pointer and is assigned to a corresponding field of struct -- fuse_operations. -- -- The created FuseOperations has the following invariants: -- -- resCFuseOperations :: forall fh dh e. Exception e => FuseOperations fh dh -> ExceptionHandler e -> ResourceT IO (Ptr FuseOperations) -- | Allocates a fuse_args struct to hold commandline arguments. resFuseArgs :: String -> [String] -> ResourceT IO (Ptr FuseArgs) -- | Calls fuse_parse_cmdline to parse the part of the commandline -- arguments that we care about. -- -- fuse_parse_cmdline will modify the FuseArgs struct -- passed in to remove those arguments; the FuseArgs struct -- containing remaining arguments must be passed to -- fuse_mount/fuse_new. -- -- The multithreaded runtime will be used regardless of the threading -- flag! See the comment in fuse_session_exit for why. fuseParseCommandLine :: Ptr FuseArgs -> IO (Either ExitCode FuseMainArgs) -- | Parses the commandline arguments and exit if the args are bad or -- certain informational flag(s) are specified. See -- fuseParseCommandLine. fuseParseCommandLineOrExit :: Ptr FuseArgs -> IO FuseMainArgs -- | Haskell version of fuse_daemonize. -- -- During the fork, transfers all of the resources in ResourceT -- (and its cleanup actions) to the forked process. -- -- Mimics daemon()'s use of _exit() instead of -- exit(); we depend on this in fuseMainReal, because -- otherwise we'll unmount the filesystem when the foreground process -- exits. fuseDaemonize :: ResourceT IO a -> ResourceT IO b -- | withSignalHandlers handler io installs signal handlers while -- io is executed. withSignalHandlers :: IO () -> IO a -> IO a -- | The parts of fuse_parse_cmdline we are interested in. Passed -- to fuseMainReal. -- --
--   (foreground, mountpoint, clone_fd)
--   
-- -- So far, we don't interpret the value of clone_fd at all so -- its type is CInt. type FuseMainArgs = (Bool, String, CInt) -- | Mounts the filesystem, forks (if requested), and then starts fuse. fuseMainReal :: Ptr StructFuse -> FuseMainArgs -> ResourceT IO a -- | Parses the commandline arguments and runs fuse. fuseRun :: Exception e => String -> [String] -> FuseOperations fh dh -> ExceptionHandler e -> IO a -- | Main function of FUSE. -- -- This is all that has to be called from the main function. On -- top of the FuseOperations record with filesystem -- implementation, you must give an exception handler converting Haskell -- exceptions to Errno. fuseMain :: Exception e => FuseOperations fh dh -> ExceptionHandler e -> IO () -- | An exception handler which converts Haskell exceptions from -- FuseOperations methods to Errno. type ExceptionHandler e = e -> IO Errno -- | Catches any exception, logs it to stderr, and returns eIO. -- -- Suitable as a default exception handler. -- -- NOTE 1 This differs from the one in the HFuse package -- which returns eFAULT. -- -- NOTE 2 If the filesystem is daemonized (as default), the -- exceptions will not be logged because stderr is redirected to -- /dev/null. defaultExceptionHandler :: ExceptionHandler SomeException -- | Gets a file handle from FuseFileInfo which is embedded with -- newFH. -- -- If either the Ptr FuseFileInfo itself or its -- fh field is NULL, returns Nothing. getFH :: Ptr FuseFileInfo -> IO (Maybe fh) -- | Gets a file handle from FuseFileInfo. -- --
--   getFHJust = fmap fromJust . getFH
--   
-- -- This means you must make sure that getFH returns Just -- or you'll get a Haskell exception. However, it's deliberately -- made lazy so that calling getFHJust itself won't throw but -- trying to use the returned value will. -- -- This function is implemented this way in order to take care of rare(?) -- cases in which fuseRead/fuseReaddir is implemented but -- not fuseOpen/fuseOpendir resp. In such a case, -- newFH would not be called but only getFH would be. -- Without some protection, we would be dereferencing a non-initialized -- StablePtr, which is undefined behavior. Throwing a -- Haskell exception in a pure code is much better than UB. See the -- comment in the source of getFH if you are interested in more -- explanation. getFHJust :: Ptr FuseFileInfo -> IO fh -- | Embeds a file handle into FuseFileInfo. It should be freed with -- delFH when no longer required. newFH :: Ptr FuseFileInfo -> fh -> IO () -- | Frees a file handle in FuseFileInfo which is embedded with -- newFH. delFH :: Ptr FuseFileInfo -> IO () -- | Materializes the callback of readdir to marshal -- fuseReaddir. peekFuseFillDir :: FunPtr FuseFillDir -> FuseFillDir instance GHC.Show.Show System.LibFuse3.Internal.EntryType instance GHC.Classes.Eq System.LibFuse3.Internal.EntryType instance GHC.Show.Show System.LibFuse3.Internal.SyncType instance GHC.Classes.Eq System.LibFuse3.Internal.SyncType instance GHC.Show.Show System.LibFuse3.Internal.AccessMode instance GHC.Classes.Eq System.LibFuse3.Internal.AccessMode instance GHC.Show.Show System.LibFuse3.Internal.SetxattrFlag instance GHC.Classes.Eq System.LibFuse3.Internal.SetxattrFlag -- | A Haskell binding to libfuse-3.x. module System.LibFuse3 -- | The file system operations. -- -- All operations are optional. Each field is named against struct -- fuse_operations in fuse.h. -- -- fh is the file handle type returned by fuseOpen, and -- subsequently passed to all other file operations. -- -- dh is the directory handle type returned by -- fuseOpendir, and subsequently passed to fuseReaddir and -- fuseReleasedir. data FuseOperations fh dh FuseOperations :: Maybe (FilePath -> Maybe fh -> IO (Either Errno FileStat)) -> Maybe (FilePath -> IO (Either Errno FilePath)) -> Maybe (FilePath -> FileMode -> DeviceID -> IO Errno) -> Maybe (FilePath -> FileMode -> IO Errno) -> Maybe (FilePath -> IO Errno) -> Maybe (FilePath -> IO Errno) -> Maybe (FilePath -> FilePath -> IO Errno) -> Maybe (FilePath -> FilePath -> IO Errno) -> Maybe (FilePath -> FilePath -> IO Errno) -> Maybe (FilePath -> Maybe fh -> FileMode -> IO Errno) -> Maybe (FilePath -> Maybe fh -> UserID -> GroupID -> IO Errno) -> Maybe (FilePath -> Maybe fh -> FileOffset -> IO Errno) -> Maybe (FilePath -> OpenMode -> OpenFileFlags -> IO (Either Errno fh)) -> Maybe (FilePath -> fh -> ByteCount -> FileOffset -> IO (Either Errno ByteString)) -> Maybe (FilePath -> fh -> ByteString -> FileOffset -> IO (Either Errno CInt)) -> Maybe (String -> IO (Either Errno FileSystemStats)) -> Maybe (FilePath -> fh -> IO Errno) -> Maybe (FilePath -> fh -> IO ()) -> Maybe (FilePath -> fh -> SyncType -> IO Errno) -> Maybe (FilePath -> String -> ByteString -> SetxattrFlag -> IO Errno) -> Maybe (FilePath -> String -> IO (Either Errno ByteString)) -> Maybe (FilePath -> IO (Either Errno [String])) -> Maybe (FilePath -> String -> IO Errno) -> Maybe (FilePath -> IO (Either Errno dh)) -> Maybe (FilePath -> dh -> IO (Either Errno [(String, Maybe FileStat)])) -> Maybe (FilePath -> dh -> IO Errno) -> Maybe (FilePath -> dh -> SyncType -> IO Errno) -> Maybe (FuseConfig -> IO FuseConfig) -> Maybe (IO ()) -> Maybe (FilePath -> AccessMode -> IO Errno) -> Maybe (FilePath -> OpenMode -> FileMode -> OpenFileFlags -> IO (Either Errno fh)) -> Maybe (FilePath -> Maybe fh -> TimeSpec -> TimeSpec -> IO Errno) -> Maybe (FilePath -> fh -> CInt -> FileOffset -> FileOffset -> IO Errno) -> Maybe (FilePath -> fh -> FileOffset -> FilePath -> fh -> FileOffset -> ByteCount -> CInt -> IO (Either Errno CSsize)) -> Maybe (FilePath -> fh -> FileOffset -> SeekMode -> IO (Either Errno FileOffset)) -> FuseOperations fh dh -- | Implements getSymbolicLinkStatus operation (POSIX -- lstat(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. [fuseGetattr] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> IO (Either Errno FileStat)) -- | Implements readSymbolicLink operation (POSIX -- readlink(2)). -- -- This function should not append a terminating NUL byte. The returned -- FilePath might be truncated depending on caller buffer size. [fuseReadlink] :: FuseOperations fh dh -> Maybe (FilePath -> IO (Either Errno FilePath)) -- | Implements createDevice (POSIX mknod(2)). -- -- This function will also be called for regular file creation if -- fuseCreate is not defined. -- -- fileModeToEntryType is handy to pattern match on the request -- type of the node. [fuseMknod] :: FuseOperations fh dh -> Maybe (FilePath -> FileMode -> DeviceID -> IO Errno) -- | Implements createDirectory (POSIX mkdir(2)). [fuseMkdir] :: FuseOperations fh dh -> Maybe (FilePath -> FileMode -> IO Errno) -- | Implements removeLink (POSIX unlink(2)). [fuseUnlink] :: FuseOperations fh dh -> Maybe (FilePath -> IO Errno) -- | Implements removeDirectory (POSIX rmdir(2)). [fuseRmdir] :: FuseOperations fh dh -> Maybe (FilePath -> IO Errno) -- | Implements createSymbolicLink (POSIX symlink(2)). [fuseSymlink] :: FuseOperations fh dh -> Maybe (FilePath -> FilePath -> IO Errno) -- | Implements rename (POSIX rename(2)). [fuseRename] :: FuseOperations fh dh -> Maybe (FilePath -> FilePath -> IO Errno) -- | Implements createLink (POSIX link(2)). [fuseLink] :: FuseOperations fh dh -> Maybe (FilePath -> FilePath -> IO Errno) -- | Implements setFileMode (POSIX chmod(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. [fuseChmod] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> FileMode -> IO Errno) -- | Implements setOwnerAndGroup (POSIX chown(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. -- -- Unless FUSE_CAP_HANDLE_KILLPRIV is disabled, this method is -- expected to reset the setuid and setgid bits. [fuseChown] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> UserID -> GroupID -> IO Errno) -- | Implements setFileSize (POSIX truncate(2)). -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. -- -- Unless FUSE_CAP_HANDLE_KILLPRIV is disabled, this method is -- expected to reset the setuid and setgid bits. [fuseTruncate] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> FileOffset -> IO Errno) -- | Implements openFd (POSIX open(2)). On success, returns -- Right of a filehandle-like value that will be passed to future -- file operations; on failure, returns Left of the appropriate -- Errno. -- -- -- -- TODO allow this method to set fuse_file_info.direct_io and -- fuse_file_info.keep_cache [fuseOpen] :: FuseOperations fh dh -> Maybe (FilePath -> OpenMode -> OpenFileFlags -> IO (Either Errno fh)) -- | Implements Unix98 pread(2). -- -- It differs from fdRead by the explicit FileOffset -- argument. [fuseRead] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> ByteCount -> FileOffset -> IO (Either Errno ByteString)) -- | Implements Unix98 pwrite(2). -- -- It differs from fdWrite by the explicit FileOffset -- argument. -- -- Unless FUSE_CAP_HANDLE_KILLPRIV is disabled, this method is -- expected to reset the setuid and setgid bits. [fuseWrite] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> ByteString -> FileOffset -> IO (Either Errno CInt)) -- | Implements statfs(2). [fuseStatfs] :: FuseOperations fh dh -> Maybe (String -> IO (Either Errno FileSystemStats)) -- | Called when close(2) has been called on an open file. -- -- Note: this does not mean that the file is released. This function may -- be called more than once for each open(2). The return value -- is passed on to the close(2) system call. [fuseFlush] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> IO Errno) -- | Called when an open file has all file descriptors closed and all -- memory mappings unmapped. -- -- For every open call there will be exactly one -- release call with the same flags. It is possible to have a -- file opened more than once, in which case only the last release will -- mean that no more reads or writes will happen on the file. [fuseRelease] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> IO ()) -- | Implements fsync(2). [fuseFsync] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> SyncType -> IO Errno) -- | Implements setxattr(2). -- -- The parameters are: path, name, value and flags. [fuseSetxattr] :: FuseOperations fh dh -> Maybe (FilePath -> String -> ByteString -> SetxattrFlag -> IO Errno) -- | Implements getxattr(2). -- -- The parameters are path and name. [fuseGetxattr] :: FuseOperations fh dh -> Maybe (FilePath -> String -> IO (Either Errno ByteString)) -- | Implements listxattr(2). [fuseListxattr] :: FuseOperations fh dh -> Maybe (FilePath -> IO (Either Errno [String])) -- | Implements removexattr(2). [fuseRemovexattr] :: FuseOperations fh dh -> Maybe (FilePath -> String -> IO Errno) -- | Implements opendir(3). -- -- This method should check if the open operation is permitted for this -- directory. [fuseOpendir] :: FuseOperations fh dh -> Maybe (FilePath -> IO (Either Errno dh)) -- | Implements readdir(3). -- -- The entire contents of the directory should be returned as a list of -- tuples (corresponding to the first mode of operation documented in -- fuse.h). -- -- The returned list should contain entries of "." and "..". -- -- Each element of the list is a pair of the name and the stat. The name -- should not include the path to it. The implementation may return -- Nothing as the stat; in this case fuseGetattr is -- called instead. [fuseReaddir] :: FuseOperations fh dh -> Maybe (FilePath -> dh -> IO (Either Errno [(String, Maybe FileStat)])) -- | Implements closedir(3). [fuseReleasedir] :: FuseOperations fh dh -> Maybe (FilePath -> dh -> IO Errno) -- | Synchronize the directory's contents; analogous to fuseFsync. [fuseFsyncdir] :: FuseOperations fh dh -> Maybe (FilePath -> dh -> SyncType -> IO Errno) -- | Initializes the filesystem. This is called before all other -- operations. -- -- The filesystem may modify FuseConfig to configure the API. [fuseInit] :: FuseOperations fh dh -> Maybe (FuseConfig -> IO FuseConfig) -- | Called on filesystem exit to allow cleanup. [fuseDestroy] :: FuseOperations fh dh -> Maybe (IO ()) -- | Implements fileAccess and 'System.Posix.Files.fileExist (POSIX -- access(2)). -- -- Checks file access permissions as requested by an AccessMode. -- -- If the default_permissions mount option is given, this method -- is not called. This method is also not called under Linux kernel -- versions 2.4.x -- -- TODO add notes about default_permissions to other relevant -- handlers [fuseAccess] :: FuseOperations fh dh -> Maybe (FilePath -> AccessMode -> IO Errno) -- | Implements openFd (POSIX open(2)). Creates and opens a -- regular file. -- -- If this is not implemented, fuseMknod and fuseOpen -- methods will be called instead. -- -- See fuseOpen for notes on the flags. [fuseCreate] :: FuseOperations fh dh -> Maybe (FilePath -> OpenMode -> FileMode -> OpenFileFlags -> IO (Either Errno fh)) -- | Implements utimensat(2). -- -- Changes the access and modification times of a file with nanosecond -- resolution. -- -- fh will always be Nothing if the file is not -- currently open, but may also be Nothing even if it is open. [fuseUtimens] :: FuseOperations fh dh -> Maybe (FilePath -> Maybe fh -> TimeSpec -> TimeSpec -> IO Errno) -- | Implements fileAllocate (posix_fallocate(3)). -- Allocates space for an open file. [fuseFallocate] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> CInt -> FileOffset -> FileOffset -> IO Errno) -- | Implements copy_file_range(2). [fuseCopyFileRange] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> FileOffset -> FilePath -> fh -> FileOffset -> ByteCount -> CInt -> IO (Either Errno CSsize)) -- | Implements fdSeek lseek(3). -- -- Note: This is silently ignored if libfuse doesn't support -- lseek operation (requires libfuse-3.8.0). [fuseLseek] :: FuseOperations fh dh -> Maybe (FilePath -> fh -> FileOffset -> SeekMode -> IO (Either Errno FileOffset)) -- | An empty set of operations whose fields are Nothing. defaultFuseOperations :: FuseOperations fh dh -- | Configures the filesystem. Passed to fuseInit. -- -- See the module System.LibFuse3.FuseConfig for its fields. data FuseConfig -- | The query type of access. Passed to fuseAccess. data AccessMode -- | File existence (F_OK) FileOK :: AccessMode -- | Reading, writing and executing permissions (R_OK, -- W_OK and X_OK, resp.) PermOK :: Bool -> Bool -> Bool -> AccessMode -- | Tests if access permissions to the file is granted or the file exists. -- -- Calls access. Compared to fileAccess and -- fileExist, this function doesn't translate the errno and just -- returns () to indicate success, or throws an error to -- indicate failure. access :: FilePath -> AccessMode -> IO () -- | Same as access but returns the Errno instead of throwing -- an exception. -- -- Returns eOK on success. accessErrno :: FilePath -> AccessMode -> IO Errno -- | The Unix type of a node in the filesystem. data EntryType -- | Unknown entry type Unknown :: EntryType NamedPipe :: EntryType CharacterSpecial :: EntryType Directory :: EntryType BlockSpecial :: EntryType RegularFile :: EntryType SymbolicLink :: EntryType Socket :: EntryType -- | Converts an EntryType into the corresponding POSIX -- FileMode. entryTypeToFileMode :: EntryType -> FileMode -- | Decodes EntryType from a FileMode. fileModeToEntryType :: FileMode -> EntryType -- | Passed to fuseFsync and fuseFsyncdir. data SyncType -- | Synchronize both file content and metadata. FullSync :: SyncType -- | Synchronize only the file content. DataSync :: SyncType -- | A file status a.k.a. metadata. -- -- The differences from FileStatus are: -- -- -- -- Ptr FileStat can be cast to Ptr CStat and -- vice versa. -- -- Use defaultFileStat and modify its fields you are interested -- in. -- -- The st_ino field is ignored unless the use_ino mount -- option is given. -- -- The st_dev and st_blksize fields are ignored by -- libfuse, so not provided. data FileStat FileStat :: FileID -> FileMode -> LinkCount -> UserID -> GroupID -> DeviceID -> FileOffset -> CBlkCnt -> TimeSpec -> TimeSpec -> TimeSpec -> FileStat -- | Inode number. st_ino [fileID] :: FileStat -> FileID -- | File type and mode. st_mode [fileMode] :: FileStat -> FileMode -- | Number of hard links. st_nlink [linkCount] :: FileStat -> LinkCount -- | User ID of owner. st_uid [fileOwner] :: FileStat -> UserID -- | Group ID of owner. st_gid [fileGroup] :: FileStat -> GroupID -- | Device ID (if special file). st_rdev [specialDeviceID] :: FileStat -> DeviceID -- | Total size, in bytes. st_size [fileSize] :: FileStat -> FileOffset -- | Number of 512B blocks allocated. st_blocks [blockCount] :: FileStat -> CBlkCnt -- | Time of last access. st_atim [accessTimeHiRes] :: FileStat -> TimeSpec -- | Time of last modification. st_mtim [modificationTimeHiRes] :: FileStat -> TimeSpec -- | Time of last status change. st_ctim [statusChangeTimeHiRes] :: FileStat -> TimeSpec -- | The default value of FileStat. -- -- The Haskell Equivalent of zero-setting C code { struct stat st; -- memset(&st, 0, sizeof(struct stat)); }. defaultFileStat :: FileStat -- | Reads a file status of a given file. -- -- Calls lstat. getFileStat :: FilePath -> IO FileStat -- | Reads a file status of a given file. -- -- Calls fstat. getFileStatFd :: Fd -> IO FileStat -- | Passed to fuseStatfs. -- -- The Storable instance targets C struct statvfs. -- -- f_favail, f_fsid and f_flag fields are -- ignored by libfuse, and their corresponding fields are not defined. data FileSystemStats -- | Gets filesystem statistics. -- -- Calls statvfs. getFileSystemStats :: FilePath -> IO FileSystemStats -- | Gets filesystem statistics. -- -- Calls fstatvfs. getFileSystemStatsFd :: Fd -> IO FileSystemStats -- | Passed to fuseSetxattr. data SetxattrFlag -- | Create a new attribute if it does not exist, or replace the value if -- it already exists (0) SetxattrDefault :: SetxattrFlag -- | Perform a pure create, which fails if the named attribute exists -- already (XATTR_CREATE) SetxattrCreate :: SetxattrFlag -- | Perform a pure replace operation, which fails if the named attribute -- does not already exist (XATTR_REPLACE) SetxattrReplace :: SetxattrFlag -- | Main function of FUSE. -- -- This is all that has to be called from the main function. On -- top of the FuseOperations record with filesystem -- implementation, you must give an exception handler converting Haskell -- exceptions to Errno. fuseMain :: Exception e => FuseOperations fh dh -> ExceptionHandler e -> IO () -- | An exception handler which converts Haskell exceptions from -- FuseOperations methods to Errno. type ExceptionHandler e = e -> IO Errno -- | Catches any exception, logs it to stderr, and returns eIO. -- -- Suitable as a default exception handler. -- -- NOTE 1 This differs from the one in the HFuse package -- which returns eFAULT. -- -- NOTE 2 If the filesystem is daemonized (as default), the -- exceptions will not be logged because stderr is redirected to -- /dev/null. defaultExceptionHandler :: ExceptionHandler SomeException