HFuse-0.2.4.5: HFuse is a binding for the Linux FUSE library.

Copyright(c) Jérémy Bobbio, Taru Karttunen
LicenseBSD-style
MaintainerMontez Fitzpatrick
Stabilityexperimental
PortabilityGHC 6.4-7.8.2
Safe HaskellNone
LanguageHaskell2010

System.Fuse

Contents

Description

A binding for the FUSE (Filesystem in USErspace) library (http://fuse.sourceforge.net/), which allows filesystems to be implemented as userspace processes.

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

FUSE uses POSIX threads, so any Haskell application using this library must be linked against a threaded runtime system (eg. using the threaded GHC option).

Synopsis

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 result. For actions not using Either, you should return eOK in case of success.

Read and writes are done with Haskell ByteString type.

data FuseOperations fh Source

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

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

fh is the file handle type returned by fuseOpen and subsequently passed to all other file operations.

Constructors

FuseOperations 

Fields

fuseGetFileStat :: FilePath -> IO (Either Errno FileStat)

Implements getSymbolicLinkStatus operation (POSIX lstat(2)).

fuseReadSymbolicLink :: FilePath -> IO (Either Errno FilePath)

Implements readSymbolicLink operation (POSIX readlink(2)). The returned FilePath might be truncated depending on caller buffer size.

fuseCreateDevice :: FilePath -> EntryType -> FileMode -> DeviceID -> IO Errno

Implements createDevice (POSIX mknod(2)). This function will also be called for regular file creation.

fuseCreateDirectory :: FilePath -> FileMode -> IO Errno

Implements createDirectory (POSIX mkdir(2)).

fuseRemoveLink :: FilePath -> IO Errno

Implements removeLink (POSIX unlink(2)).

fuseRemoveDirectory :: FilePath -> IO Errno

Implements removeDirectory (POSIX rmdir(2)).

fuseCreateSymbolicLink :: FilePath -> FilePath -> IO Errno

Implements createSymbolicLink (POSIX symlink(2)).

fuseRename :: FilePath -> FilePath -> IO Errno

Implements rename (POSIX rename(2)).

fuseCreateLink :: FilePath -> FilePath -> IO Errno

Implements createLink (POSIX link(2)).

fuseSetFileMode :: FilePath -> FileMode -> IO Errno

Implements setFileMode (POSIX chmod(2)).

fuseSetOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO Errno

Implements setOwnerAndGroup (POSIX chown(2)).

fuseSetFileSize :: FilePath -> FileOffset -> IO Errno

Implements setFileSize (POSIX truncate(2)).

fuseSetFileTimes :: FilePath -> EpochTime -> EpochTime -> IO Errno

Implements setFileTimes (POSIX utime(2)).

fuseOpen :: FilePath -> OpenMode -> OpenFileFlags -> IO (Either Errno fh)

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.

No creation, exclusive access or truncating flags will be passed. This should check that the operation is permitted for the given flags.

fuseRead :: FilePath -> fh -> ByteCount -> FileOffset -> IO (Either Errno ByteString)

Implements Unix98 pread(2). It differs from fdRead by the explicit FileOffset argument. The fuse.h documentation stipulates that this "should return exactly the number of bytes requested except on EOF or error, otherwise the rest of the data will be substituted with zeroes."

fuseWrite :: FilePath -> fh -> ByteString -> FileOffset -> IO (Either Errno ByteCount)

Implements Unix98 pwrite(2). It differs from fdWrite by the explicit FileOffset argument.

fuseGetFileSystemStats :: String -> IO (Either Errno FileSystemStats)

Implements statfs(2).

fuseFlush :: FilePath -> fh -> IO Errno

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 :: FilePath -> fh -> IO ()

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 :: FilePath -> SyncType -> IO Errno

Implements fsync(2).

fuseOpenDirectory :: FilePath -> IO Errno

Implements opendir(3). This method should check if the open operation is permitted for this directory.

fuseReadDirectory :: FilePath -> IO (Either Errno [(FilePath, FileStat)])

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).

fuseReleaseDirectory :: FilePath -> IO Errno

Implements closedir(3).

fuseSynchronizeDirectory :: FilePath -> SyncType -> IO Errno

Synchronize the directory's contents; analogous to fuseSynchronizeFile.

fuseAccess :: FilePath -> Int -> IO Errno

Check file access permissions; this will be called for the access() system call. 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

fuseInit :: IO ()

Initializes the filesystem. This is called before all other operations.

fuseDestroy :: IO ()

Called on filesystem exit to allow cleanup.

defaultFuseOps :: FuseOperations fh Source

Empty / default versions of the FUSE operations.

fuseMain :: Exception e => FuseOperations fh -> (e -> 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 keyboardSignal, lostConnection, softwareTermination and openEndedPipe ;
  • registers an exit handler to unmount the filesystem on program exit ;
  • registers the operations ;
  • calls FUSE event loop.

fuseRun :: String -> [String] -> Exception e => FuseOperations fh -> (e -> IO Errno) -> IO () Source

defaultExceptionHandler :: SomeException -> IO Errno Source

Default exception handler. Print the exception on error output and returns eFAULT.

Operations datatypes

data FileStat Source

Used by fuseGetFileStat. Corresponds to struct stat from stat.h; st_dev, st_ino and st_blksize are omitted, since (from the libfuse documentation): "the st_dev and st_blksize fields are ignored. The st_ino field is ignored except if the use_ino mount option is given."

TODO: at some point the inode field will probably be needed.

Instances

data EntryType Source

The Unix type of a node in the filesystem.

Instances

data FileSystemStats Source

Type used by the fuseGetFileSystemStats.

Constructors

FileSystemStats 

Fields

fsStatBlockSize :: Integer

Optimal transfer block size. FUSE default is 512.

fsStatBlockCount :: Integer

Total data blocks in file system.

fsStatBlocksFree :: Integer

Free blocks in file system.

fsStatBlocksAvailable :: Integer

Free blocks available to non-superusers.

fsStatFileCount :: Integer

Total file nodes in file system.

fsStatFilesFree :: Integer

Free file nodes in file system.

fsStatMaxNameLength :: Integer

Maximum length of filenames. FUSE default is 255.

data SyncType Source

Constructors

FullSync

Synchronize all in-core parts of a file to disk: file content and metadata.

DataSync

Synchronize only the file content.

Instances

FUSE Context

getFuseContext :: IO FuseContext Source

Returns the context of the program doing the current FUSE call.

File modes

entryTypeToFileMode :: EntryType -> FileMode Source

Converts an EntryType into the corresponding POSIX FileMode.

data OpenMode :: *

Constructors

ReadOnly 
WriteOnly 
ReadWrite 

data OpenFileFlags :: *

Correspond to some of the int flags from C's fcntl.h.

Constructors

OpenFileFlags 

Fields

append :: Bool

O_APPEND

exclusive :: Bool

O_EXCL

noctty :: Bool

O_NOCTTY

nonBlock :: Bool

O_NONBLOCK

trunc :: Bool

O_TRUNC

intersectFileModes :: FileMode -> FileMode -> FileMode

Combines two file modes into one that only contains modes that appear in both.

unionFileModes :: FileMode -> FileMode -> FileMode

Combines the two file modes into one that contains modes that appear in either.