HFuse-0.1: HFuse is a binding for the Linux FUSE librarySource codeContentsIndex
System.Posix.HFuse
PortabilityGHC 6.8
Stabilityexperimental
Maintainerjeremy.bobbio@etu.upmc.fr
Contents
Using FUSE
Operations datatypes
FUSE Context
File modes
Description

HFuse is a binding for the FUSE (Filesystem in USErspace) library.

See http://fuse.sourceforge.net/

This library allow new filesystem implementation as simple user-land programs.

The binding tries to follow as much as possible current Haskell POSIX interface in System.Posix.Files and System.Posix.Directory.

FUSE uses POSIX thread, thus Haskell implementation needs to be linked against a threaded runtime system (eg. using the threaded GHC option).

Synopsis
module Foreign.C.Error
data FuseOperations = FuseOperations {
fuseGetFileStat :: FilePath -> IO (Either Errno FileStat)
fuseReadSymbolicLink :: FilePath -> IO (Either Errno FilePath)
fuseGetDirectoryContents :: FilePath -> IO (Either Errno [(FilePath, EntryType)])
fuseCreateDevice :: FilePath -> EntryType -> FileMode -> DeviceID -> IO Errno
fuseCreateDirectory :: FilePath -> FileMode -> IO Errno
fuseRemoveLink :: FilePath -> IO Errno
fuseRemoveDirectory :: FilePath -> IO Errno
fuseCreateSymbolicLink :: FilePath -> FilePath -> IO Errno
fuseRename :: FilePath -> FilePath -> IO Errno
fuseCreateLink :: FilePath -> FilePath -> IO Errno
fuseSetFileMode :: FilePath -> FileMode -> IO Errno
fuseSetOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO Errno
fuseSetFileSize :: FilePath -> FileOffset -> IO Errno
fuseSetFileTimes :: FilePath -> EpochTime -> EpochTime -> IO Errno
fuseOpen :: FilePath -> OpenMode -> OpenFileFlags -> IO Errno
fuseRead :: FilePath -> ByteCount -> FileOffset -> IO (Either Errno (String, ByteCount))
fuseWrite :: FilePath -> String -> FileOffset -> IO (Either Errno ByteCount)
fuseGetFileSystemStats :: String -> IO (Either Errno FileSystemStats)
fuseFlush :: FilePath -> IO Errno
fuseRelease :: FilePath -> Int -> IO ()
fuseSynchronizeFile :: FilePath -> SyncType -> IO Errno
fuseOpenDirectory :: FilePath -> IO Errno
fuseReleaseDirectory :: FilePath -> IO Errno
fuseSynchronizeDirectory :: FilePath -> SyncType -> IO Errno
fuseInit :: IO ()
fuseDestroy :: IO ()
}
defaultFuseOps :: FuseOperations
fuseMain :: FuseOperations -> (Exception -> IO Errno) -> IO ()
defaultExceptionHandler :: Exception -> IO Errno
data FileStat = FileStat {
statEntryType :: EntryType
statFileMode :: FileMode
statLinkCount :: LinkCount
statFileOwner :: UserID
statFileGroup :: GroupID
statSpecialDeviceID :: DeviceID
statFileSize :: FileOffset
statBlocks :: Integer
statAccessTime :: EpochTime
statModificationTime :: EpochTime
statStatusChangeTime :: EpochTime
}
data EntryType
= Unknown
| NamedPipe
| CharacterSpecial
| Directory
| BlockSpecial
| RegularFile
| SymbolicLink
| Socket
data FileSystemStats = FileSystemStats {
fsStatBlockSize :: Integer
fsStatBlockCount :: Integer
fsStatBlocksFree :: Integer
fsStatBlocksAvailable :: Integer
fsStatFileCount :: Integer
fsStatFilesFree :: Integer
fsStatMaxNameLength :: Integer
}
data SyncType
= FullSync
| DataSync
getFuseContext :: IO FuseContext
data FuseContext
entryTypeToFileMode :: EntryType -> FileMode
OpenMode (ReadOnly, WriteOnly, ReadWrite)
OpenFileFlags (OpenFileFlags, append, exclusive, noctty, nonBlock, trunc)
intersectFileModes
unionFileModes
Using FUSE

FuseOperations contains a field for each filesystem operations that can be called by FUSE. Think like if you were implementing a file system inside the Linux kernel.

Each actions must return a POSIX error code, also called Errno reflecting operation relult. For actions not using Either, you should return eOK in case of success.

Read and writes are done with Haskell String type. Even if this representation is known to have drawbacks, the binding try to be coherent with current Haskell libraries.

module Foreign.C.Error
data FuseOperations Source

This record, given to fuseMain, binds each required file system operations.

Each field is named against System.Posix names. Matching Linux system calls are also given as a reference.

  • fuseGetFileStat implements System.Posix.Files.getSymbolicLinkStatus operation (POSIX lstat(2)).
  • fuseReadSymbolicLink implements System.Posix.Files.readSymbolicLink operation (POSIX readlink(2)). The returned FilePath might be truncated depending on caller buffer size.
  • fuseGetDirectoryContents implements System.Directory.getDirectoryContents (POSIX readddir(2)).
  • fuseCreateDevice implements System.Posix.Files.createDevice (POSIX mknod(2)). This function will also be called for regular file creation.
  • fuseCreateDirectory implements System.Posix.Directory.createDirectory (POSIX mkdir(2)).
  • fuseRemoveLink implements System.Posix.Files.removeLink (POSIX unlink(2)).
  • fuseRemoveDirectory implements System.Posix.Directory.removeDirectory (POSIX rmdir(2)).
  • fuseCreateSymbolicLink implements System.Posix.Files.createSymbolicLink (POSIX symlink(2)).
  • fuseRename implements System.Posix.Files.rename (POSIX rename(2)).
  • fuseCreateLink implements System.Posix.Files.createLink (POSIX link(2)).
  • fuseSetFileMode implements System.Posix.Files.setFileMode (POSIX chmod(2)).
  • fuseSetOwnerAndGroup implements System.Posix.Files.setOwnerAndGroup (POSIX chown(2)).
  • fuseSetFileSize implements System.Posix.Files.setFileSize (POSIX truncate(2)).
  • fuseSetFileTimes implements System.Posix.Files.setFileTimes (POSIX utime(2)).
  • fuseOpen implements System.Posix.Files.openFd (POSIX open(2)), but this does not actually returns a file handle but eOK if the operation is permitted with the given flags. No creation, exclusive access or truncating flags will be passed.
  • fuseRead implements Unix98 pread(2). It differs from System.Posix.Files.fdRead by the explicit FileOffset argument.
  • fuseWrite implements Unix98 pwrite(2). It differs from System.Posix.Files.fdWrite by the explicit FileOffset argument.
  • fuseGetFileSystemStats implements statfs(2).
  • fuseFlush is 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.
  • fuseRelease is 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.
  • fuseSynchronizeFile implements fsync(2).
Constructors
FuseOperations
fuseGetFileStat :: FilePath -> IO (Either Errno FileStat)
fuseReadSymbolicLink :: FilePath -> IO (Either Errno FilePath)
fuseGetDirectoryContents :: FilePath -> IO (Either Errno [(FilePath, EntryType)])
fuseCreateDevice :: FilePath -> EntryType -> FileMode -> DeviceID -> IO Errno
fuseCreateDirectory :: FilePath -> FileMode -> IO Errno
fuseRemoveLink :: FilePath -> IO Errno
fuseRemoveDirectory :: FilePath -> IO Errno
fuseCreateSymbolicLink :: FilePath -> FilePath -> IO Errno
fuseRename :: FilePath -> FilePath -> IO Errno
fuseCreateLink :: FilePath -> FilePath -> IO Errno
fuseSetFileMode :: FilePath -> FileMode -> IO Errno
fuseSetOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO Errno
fuseSetFileSize :: FilePath -> FileOffset -> IO Errno
fuseSetFileTimes :: FilePath -> EpochTime -> EpochTime -> IO Errno
fuseOpen :: FilePath -> OpenMode -> OpenFileFlags -> IO Errno
fuseRead :: FilePath -> ByteCount -> FileOffset -> IO (Either Errno (String, ByteCount))
fuseWrite :: FilePath -> String -> FileOffset -> IO (Either Errno ByteCount)
fuseGetFileSystemStats :: String -> IO (Either Errno FileSystemStats)
fuseFlush :: FilePath -> IO Errno
fuseRelease :: FilePath -> Int -> IO ()
fuseSynchronizeFile :: FilePath -> SyncType -> IO Errno
fuseOpenDirectory :: FilePath -> IO Errno
fuseReleaseDirectory :: FilePath -> IO Errno
fuseSynchronizeDirectory :: FilePath -> SyncType -> IO Errno
fuseInit :: IO ()
fuseDestroy :: IO ()
defaultFuseOps :: FuseOperationsSource
Empty / default versions of the FUSE operations.
fuseMain :: FuseOperations -> (Exception -> IO Errno) -> 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.

This function does the following:

  • parses command line options (-d, -s and -h) ;
  • passes all options after -- to the fusermount program ;
  • mounts the filesystem by calling fusermount ;
  • installs signal handlers for System.Posix.Signals.keyboardSignal, System.Posix.Signals.lostConnection, System.Posix.Signals.softwareTermination and System.Posix.Signals.openEndedPipe ;
  • registers an exit handler to unmount the filesystem on program exit ;
  • registers the operations ;
  • calls FUSE event loop.
defaultExceptionHandler :: Exception -> IO ErrnoSource
Default exception handler. Print the exception on error output and returns eFAULT.
Operations datatypes
data FileStat Source
Used by fuseGetFileStat.
Constructors
FileStat
statEntryType :: EntryType
statFileMode :: FileMode
statLinkCount :: LinkCount
statFileOwner :: UserID
statFileGroup :: GroupID
statSpecialDeviceID :: DeviceID
statFileSize :: FileOffset
statBlocks :: Integer
statAccessTime :: EpochTime
statModificationTime :: EpochTime
statStatusChangeTime :: EpochTime
data EntryType Source
Used by fuseGetDirectoryContents implementation to specify the type of a directory entry.
Constructors
UnknownUnknown entry type
NamedPipe
CharacterSpecial
Directory
BlockSpecial
RegularFile
SymbolicLink
Socket
data FileSystemStats Source
Type used by the fuseGetFileSystemStats.
Constructors
FileSystemStats
fsStatBlockSize :: IntegerOptimal transfer block size. FUSE default is 512.
fsStatBlockCount :: IntegerTotal data blocks in file system.
fsStatBlocksFree :: IntegerFree blocks in file system.
fsStatBlocksAvailable :: IntegerFree blocks available to non-superusers.
fsStatFileCount :: IntegerTotal file nodes in file system.
fsStatFilesFree :: IntegerFree file nodes in file system.
fsStatMaxNameLength :: IntegerMaximum length of filenames. FUSE default is 255.
data SyncType Source
Used by fuseSynchronizeFile.
Constructors
FullSyncSynchronize all in-core parts of a file to disk: file content and metadata.
DataSyncSynchronize only the file content.
show/hide Instances
FUSE Context
getFuseContext :: IO FuseContextSource
Returns the context of the program doing the current FUSE call.
data FuseContext Source
Returned by getFuseContext.
File modes
entryTypeToFileMode :: EntryType -> FileModeSource
Converts an EntryType into the corresponding POSIX FileMode.
OpenMode (ReadOnly, WriteOnly, ReadWrite)
OpenFileFlags (OpenFileFlags, append, exclusive, noctty, nonBlock, trunc)
intersectFileModes
unionFileModes
Produced by Haddock version 2.4.2