| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
System.LibFuse3
Description
A Haskell binding to libfuse-3.x.
Synopsis
- data FuseOperations fh dh = FuseOperations {
- fuseGetattr :: Maybe (FilePath -> Maybe fh -> IO (Either Errno FileStat))
- fuseReadlink :: Maybe (FilePath -> IO (Either Errno FilePath))
- fuseMknod :: Maybe (FilePath -> FileMode -> DeviceID -> IO Errno)
- fuseMkdir :: Maybe (FilePath -> FileMode -> IO Errno)
- fuseUnlink :: Maybe (FilePath -> IO Errno)
- fuseRmdir :: Maybe (FilePath -> IO Errno)
- fuseSymlink :: Maybe (FilePath -> FilePath -> IO Errno)
- fuseRename :: Maybe (FilePath -> FilePath -> IO Errno)
- fuseLink :: Maybe (FilePath -> FilePath -> IO Errno)
- fuseChmod :: Maybe (FilePath -> Maybe fh -> FileMode -> IO Errno)
- fuseChown :: Maybe (FilePath -> Maybe fh -> UserID -> GroupID -> IO Errno)
- fuseTruncate :: Maybe (FilePath -> Maybe fh -> FileOffset -> IO Errno)
- fuseOpen :: Maybe (FilePath -> OpenMode -> OpenFileFlags -> IO (Either Errno fh))
- fuseRead :: Maybe (FilePath -> fh -> ByteCount -> FileOffset -> IO (Either Errno ByteString))
- fuseWrite :: Maybe (FilePath -> fh -> ByteString -> FileOffset -> IO (Either Errno CInt))
- fuseStatfs :: Maybe (String -> IO (Either Errno FileSystemStats))
- fuseFlush :: Maybe (FilePath -> fh -> IO Errno)
- fuseRelease :: Maybe (FilePath -> fh -> IO ())
- fuseFsync :: Maybe (FilePath -> fh -> SyncType -> IO Errno)
- fuseSetxattr :: Maybe (FilePath -> String -> ByteString -> SetxattrFlag -> IO Errno)
- fuseGetxattr :: Maybe (FilePath -> String -> IO (Either Errno ByteString))
- fuseListxattr :: Maybe (FilePath -> IO (Either Errno [String]))
- fuseRemovexattr :: Maybe (FilePath -> String -> IO Errno)
- fuseOpendir :: Maybe (FilePath -> IO (Either Errno dh))
- fuseReaddir :: Maybe (FilePath -> dh -> IO (Either Errno [(String, Maybe FileStat)]))
- fuseReleasedir :: Maybe (FilePath -> dh -> IO Errno)
- fuseFsyncdir :: Maybe (FilePath -> dh -> SyncType -> IO Errno)
- fuseInit :: Maybe (FuseConfig -> IO FuseConfig)
- fuseDestroy :: Maybe (IO ())
- fuseAccess :: Maybe (FilePath -> AccessMode -> IO Errno)
- fuseCreate :: Maybe (FilePath -> OpenMode -> FileMode -> OpenFileFlags -> IO (Either Errno fh))
- fuseUtimens :: Maybe (FilePath -> Maybe fh -> TimeSpec -> TimeSpec -> IO Errno)
- fuseFallocate :: Maybe (FilePath -> fh -> CInt -> FileOffset -> FileOffset -> IO Errno)
- fuseCopyFileRange :: Maybe (FilePath -> fh -> FileOffset -> FilePath -> fh -> FileOffset -> ByteCount -> CInt -> IO (Either Errno CSsize))
- fuseLseek :: Maybe (FilePath -> fh -> FileOffset -> SeekMode -> IO (Either Errno FileOffset))
- defaultFuseOperations :: FuseOperations fh dh
- data FuseConfig
- data AccessMode
- access :: FilePath -> AccessMode -> IO ()
- accessErrno :: FilePath -> AccessMode -> IO Errno
- data EntryType
- entryTypeToFileMode :: EntryType -> FileMode
- fileModeToEntryType :: FileMode -> EntryType
- data SyncType
- data FileStat = FileStat {
- fileID :: FileID
- fileMode :: FileMode
- linkCount :: LinkCount
- fileOwner :: UserID
- fileGroup :: GroupID
- specialDeviceID :: DeviceID
- fileSize :: FileOffset
- blockCount :: CBlkSize
- accessTimeHiRes :: TimeSpec
- modificationTimeHiRes :: TimeSpec
- statusChangeTimeHiRes :: TimeSpec
- defaultFileStat :: FileStat
- getFileStat :: FilePath -> IO FileStat
- getFileStatFd :: Fd -> IO FileStat
- data FileSystemStats
- getFileSystemStats :: FilePath -> IO FileSystemStats
- getFileSystemStatsFd :: Fd -> IO FileSystemStats
- data SetxattrFlag
- module System.LibFuse3.Utils
- fuseMain :: Exception e => FuseOperations fh dh -> ExceptionHandler e -> IO ()
- type ExceptionHandler e = e -> IO Errno
- defaultExceptionHandler :: ExceptionHandler SomeException
Documentation
data FuseOperations fh dh Source #
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.
Constructors
| FuseOperations | |
Fields
| |
defaultFuseOperations :: FuseOperations fh dh Source #
An empty set of operations whose fields are Nothing.
data FuseConfig Source #
Configures the filesystem. Passed to fuseInit.
See the module System.LibFuse3.FuseConfig for its fields.
Instances
| Show FuseConfig Source # | |
Defined in System.LibFuse3.FuseConfig Methods showsPrec :: Int -> FuseConfig -> ShowS # show :: FuseConfig -> String # showList :: [FuseConfig] -> ShowS # | |
| Eq FuseConfig Source # | |
Defined in System.LibFuse3.FuseConfig | |
data AccessMode Source #
The query type of access. Passed to fuseAccess.
Constructors
| FileOK | File existence ( |
| PermOK Bool Bool Bool | Reading, writing and executing permissions ( |
Instances
| Show AccessMode Source # | |
Defined in System.LibFuse3.Internal Methods showsPrec :: Int -> AccessMode -> ShowS # show :: AccessMode -> String # showList :: [AccessMode] -> ShowS # | |
| Eq AccessMode Source # | |
Defined in System.LibFuse3.Internal | |
access :: FilePath -> AccessMode -> IO () Source #
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.
accessErrno :: FilePath -> AccessMode -> IO Errno Source #
The Unix type of a node in the filesystem.
Constructors
| Unknown | Unknown entry type |
| NamedPipe | |
| CharacterSpecial | |
| Directory | |
| BlockSpecial | |
| RegularFile | |
| SymbolicLink | |
| Socket |
Passed to fuseFsync and fuseFsyncdir.
Constructors
| FullSync | Synchronize both file content and metadata. |
| DataSync | Synchronize only the file content. |
A file status a.k.a. metadata.
The differences from FileStatus are:
- Is a record type with a
Storableinstance. - Has an extra field
blockCount. Provides an exact representation (
TimeSpec) of the time fields without converting toPOSIXTime.- This assumes that the
struct stathasst_atim,st_mtimandst_ctimfields. On Linux this requires Linux >= 2.6.
- This assumes that the
Ptr FileStat can be cast to Ptr and vice versa.CStat
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.
Constructors
| FileStat | |
Fields
| |
Instances
| Storable FileStat Source # | Targets |
Defined in System.LibFuse3.FileStat | |
| Show FileStat Source # | |
| Eq FileStat Source # | |
defaultFileStat :: FileStat Source #
The default value of FileStat.
The Haskell Equivalent of zero-setting C code { struct stat st; memset(&st, 0, sizeof(struct stat)); }.
data FileSystemStats Source #
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.
Instances
| Storable FileSystemStats Source # | |
Defined in System.LibFuse3.FileSystemStats Methods sizeOf :: FileSystemStats -> Int # alignment :: FileSystemStats -> Int # peekElemOff :: Ptr FileSystemStats -> Int -> IO FileSystemStats # pokeElemOff :: Ptr FileSystemStats -> Int -> FileSystemStats -> IO () # peekByteOff :: Ptr b -> Int -> IO FileSystemStats # pokeByteOff :: Ptr b -> Int -> FileSystemStats -> IO () # peek :: Ptr FileSystemStats -> IO FileSystemStats # poke :: Ptr FileSystemStats -> FileSystemStats -> IO () # | |
| Show FileSystemStats Source # | |
Defined in System.LibFuse3.FileSystemStats Methods showsPrec :: Int -> FileSystemStats -> ShowS # show :: FileSystemStats -> String # showList :: [FileSystemStats] -> ShowS # | |
| Eq FileSystemStats Source # | |
Defined in System.LibFuse3.FileSystemStats Methods (==) :: FileSystemStats -> FileSystemStats -> Bool # (/=) :: FileSystemStats -> FileSystemStats -> Bool # | |
Arguments
| :: FilePath | A path of any file within the filesystem |
| -> IO FileSystemStats |
Gets filesystem statistics.
Calls statvfs.
getFileSystemStatsFd :: Fd -> IO FileSystemStats Source #
Gets filesystem statistics.
Calls fstatvfs.
data SetxattrFlag Source #
Passed to fuseSetxattr.
Constructors
| SetxattrDefault | Create a new attribute if it does not exist, or replace the value if it already exists ( |
| SetxattrCreate | Perform a pure create, which fails if the named attribute exists already ( |
| SetxattrReplace | Perform a pure replace operation, which fails if the named attribute does not already exist ( |
Instances
| Show SetxattrFlag Source # | |
Defined in System.LibFuse3.Internal Methods showsPrec :: Int -> SetxattrFlag -> ShowS # show :: SetxattrFlag -> String # showList :: [SetxattrFlag] -> ShowS # | |
| Eq SetxattrFlag Source # | |
Defined in System.LibFuse3.Internal | |
module System.LibFuse3.Utils
fuseMain :: Exception e => FuseOperations fh dh -> ExceptionHandler e -> IO () Source #
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.
type ExceptionHandler e = e -> IO Errno Source #
An exception handler which converts Haskell exceptions from FuseOperations methods to Errno.
defaultExceptionHandler :: ExceptionHandler SomeException Source #
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.