halfs-0.2: Haskell File SystemSource codeContentsIndex
Halfs
PortabilityGHC
Stabilityalpha
MaintainerIsaac Jones <ijones@galois.com>
Contents
Write-related functions
Read-related functions
Meta-data functions
Creating new filesystems
Mounting filesystems
Evaluating the FSRead and FSWrite moands
fsck
Types (most are re-exported from elsewhere)
Types to make abstract (FIX)
testing
Description
High-level interface to Halfs, the Haskell Filesystem.
Synopsis
unlink :: FilePath -> FSWrite ()
rmdir :: FilePath -> FSWrite ()
rename :: FilePath -> FilePath -> FSWrite ()
mkdir :: FilePath -> FSWrite ()
addChildWrite :: Directory -> Inode -> String -> FSWrite Inode
openWrite :: FilePath -> FSWrite FileHandle
openAppend :: FilePath -> FSWrite FileHandle
write :: FileHandle -> Buffer -> INInt -> INInt -> FSWrite INInt
writeString :: FileHandle -> String -> FSWrite INInt
closeWrite :: FileHandle -> FSWrite ()
openFileAtPathWrite :: FileMode -> FilePath -> FileType -> Bool -> FSWrite FileHandle
stat :: FilePath -> FSRead RdStat
fstat :: FileHandle -> FSRead RdStat
openRead :: FilePath -> FSRead FileHandle
read :: FileHandle -> Buffer -> INInt -> INInt -> FSRead INInt
closeRead :: FileHandle -> FSRead ()
seek :: FileHandle -> INLong -> FSRead ()
openFileAtPathRead :: FilePath -> FSRead FileHandle
fsStats :: FSRoot -> IO FileSystemStats
getDirectoryContents :: FilePath -> FSRead [FilePath]
isDirectory :: FilePath -> FSRead Bool
getDirectoryDetails :: FilePath -> FSRead [(String, Inode)]
newFS :: DeviceLocation -> INInt -> IO ()
withNewFSWrite :: String -> INInt -> FSWrite a -> IO a
mountFS :: Maybe StateHandle -> DeviceLocation -> Bool -> Int -> IO FSRoot
unmountFS :: FSRoot -> IO ()
unmountWriteFS :: FSWrite ()
mountFSMV :: Maybe StateHandle -> DeviceLocation -> Maybe (MVar ()) -> Bool -> Int -> IO StateHandle
withFSRead :: DeviceLocation -> FSRead a -> IO a
withFSWrite :: DeviceLocation -> FSWrite a -> IO a
evalFSWriteIOMV :: FSWrite a -> StateHandle -> IO a
evalFSReadIOMV :: FSRead a -> StateHandle -> IO a
fsck :: DeviceLocation -> IO ()
fsckWrite :: FSWrite ()
syncPeriodicallyWrite :: MVar () -> Bool -> FSWrite ()
readReadRef :: ReadRef a -> FSRead a
data FSWrite a
data FSRead a
newtype TimeT = TimeT CLong
type SizeT = INLong
type FileHandle = IORef FileHandle
data FileMode
= ReadMode
| WriteMode
| AppendMode
data Buffer
type DeviceLocation = String
data InodeMetadata = InodeMetadata {
magic1 :: INInt
num_bytes :: INLong
uid :: INInt
gid :: INInt
mode :: FileType
inode_num :: INInt
flags :: INInt
hard_links :: INInt
create_time :: INLong
last_modified_time :: INLong
level :: INInt
}
data Inode = Inode {
metaData :: InodeMetadata
blockPtrs :: INPointers
}
data StateHandle = StateHandle {
stateFineMVar :: MVar FSRoot
stateCoarseMVar :: Maybe (MVar ())
}
data RdStat
= RdDirectory {
modTime :: TimeT
}
| RdFile {
modTime :: TimeT
size :: SizeT
}
data FileSystemStats = FileSystemStats {
blockSize :: Integer
blockCount :: Integer
blocksFree :: Integer
blocksAvailable :: Integer
fileCount :: Integer
filesFree :: Integer
maxNameLength :: Integer
}
data FSStatus
= FsUnmounted
| FsReadOnly
| FsReadWrite
makeFiles :: Int -> FilePath -> String -> FSWrite ()
unitTests :: Bool -> UnitTests
Write-related functions
unlink :: FilePath -> FSWrite ()Source
Delete this file. Currently can be used to delete a directory, but that should probably be FIXED.
rmdir :: FilePath -> FSWrite ()Source
Unlink this directory. Should only be called on empty directories. Does not descent into sub-directories. Should fail if given a file or if the directory is non-empty (but currently doesn't: FIX).
renameSource
:: FilePathFrom
-> FilePathTo
-> FSWrite ()
Rename this file. Rename the file named as From to the file named as To. Can throw an exception if From doesn't exist.
mkdir :: FilePath -> FSWrite ()Source
Create an empty directory at this path. Throws an error if something already exists at this path.
addChildWriteSource
:: Directoryto add to directory
-> Inodenew child's inode
-> StringName of child to create inside directory.
-> FSWrite Inode
Like Direcotry.addChild, but in the FSWrite monad, and syncs this directory.
openWrite :: FilePath -> FSWrite FileHandleSource
Open the given file for writing. If a file exists at this location, it gets overwritten. FIX: Test
openAppend :: FilePath -> FSWrite FileHandleSource
Open the given file for appending. If a file already exists at this location, it gets opened for writing, and the file pointer is pointing to the end. FIX: Test, what does it do if no such file exists.
writeSource
:: FileHandle
-> BufferBuffer to write from
-> INIntOffset into above buffer FIX: should we allow current loc
-> INIntHow many to write
-> FSWrite INInt
Write from the given buffer into the file.
writeString :: FileHandle -> String -> FSWrite INIntSource
Helpfer function for writing a string to a file.
closeWrite :: FileHandle -> FSWrite ()Source
Close a file that's open for writing.
openFileAtPathWrite :: FileMode -> FilePath -> FileType -> Bool -> FSWrite FileHandleSource
Much like getDirectoryAtPath, builds a handle out of this filepath. May throw IO Error! FIX: annotate w/ errors thrown. FIX: throw errors for incorrect mode.
Read-related functions
stat :: FilePath -> FSRead RdStatSource
Get basic information about the file at this path.
fstat :: FileHandle -> FSRead RdStatSource
Get basic information about this file handle.
openRead :: FilePath -> FSRead FileHandleSource
Open this file for reading. FIX: test.
readSource
:: FileHandle
-> BufferBuffer to read into
-> INIntOffset into above buffer
-> INIntHow many to read
-> FSRead INInt
Read from this file handle into this buffer.
closeRead :: FileHandle -> FSRead ()Source
Close a filehandle that's open for reading.
seekSource
:: FileHandle
-> INLongWhat byte offset to move the filehandle to. Must be > 0 and < the number of bytes in the file.
-> FSRead ()
Move this filehandle to given position.
openFileAtPathRead :: FilePath -> FSRead FileHandleSource
Meta-data functions
fsStats :: FSRoot -> IO FileSystemStatsSource
getDirectoryContents :: FilePath -> FSRead [FilePath]Source
Get the contents of a directory.
isDirectory :: FilePath -> FSRead BoolSource
Does this filepath refer to a directory?
getDirectoryDetails :: FilePath -> FSRead [(String, Inode)]Source
Caller may want to filter out . and ..
Creating new filesystems
newFSSource
:: DeviceLocation
-> INIntdesired length of the new filesystem in blocks
-> IO ()
Creates a new filesystem with a real-life root inode! Out of thin air, create a buffer block for this device, 0, and write root inode to our new cache.
withNewFSWriteSource
::
=> String
-> INInt
-> FSWrite aOperations to perform
-> IO a
Create a new file system and perform the given operations. Unmounting is up to the caller. See newFS for parameter details.
Mounting filesystems
mountFSSource
:: Maybe StateHandleif Just, use the raw device inside
-> DeviceLocationLocation of device
-> BoolRead only?
-> Intbuffer block cache size
-> IO FSRoot
Basic low-level mount operation. Usually used via wrappers such as withFSWrite and withFSRead. See also newFS.
unmountFS :: FSRoot -> IO ()Source
Syncs the device and closes its handle. You should stop using it after that. Must represent an open device!
unmountWriteFS :: FSWrite ()Source
Just like unmountFS but in the FSWrite monad.
mountFSMVSource
:: Maybe StateHandle
-> DeviceLocation
-> Maybe (MVar ())the outermost-blocker, if desirable. causes a synchronization thread to be spawned
-> Bool
-> Intcache size
-> IO StateHandle
See mountFS for most documentation.
withFSReadSource
::
=> DeviceLocationLocation of device
-> FSRead aOperations to perform
-> IO a
Mount the given file system for reading and perform these operations.
withFSWriteSource
::
=> DeviceLocationLocation of device
-> FSWrite aOperations to perform
-> IO a
Mount the given file system for writing and perform these operations. FIX: Maybe add MVar () for blocking on.
Evaluating the FSRead and FSWrite moands
evalFSWriteIOMV :: FSWrite a -> StateHandle -> IO aSource
evalFSReadIOMV :: FSRead a -> StateHandle -> IO aSource
fsck
fsck :: DeviceLocation -> IO ()Source
Check the filesystem for errors. Exits with an error code and message if any are found. Outputs lots of low-level data to the terminal.
fsckWrite :: FSWrite ()Source
See fsck.
syncPeriodicallyWriteSource
:: MVar ()High-level blocker. This function blocks on this mvar.
-> Bool
-> FSWrite ()
Periodically sync the filesystem. Usually forked off in its own thread. For READS: Flush caches on read-only filesystem (so they'll be re-populated). For WRITES: write out the filesystem data. FIX: remove readOnly; that's in the fsroot. FIX: add exception handler (since it does a take)
readReadRef :: ReadRef a -> FSRead aSource
Types (most are re-exported from elsewhere)
data FSWrite a Source
show/hide Instances
data FSRead a Source
show/hide Instances
newtype TimeT Source
Constructors
TimeT CLong
show/hide Instances
type SizeT = INLongSource
type FileHandle = IORef FileHandleSource
data FileMode Source
Constructors
ReadMode
WriteMode
AppendMode
show/hide Instances
data Buffer Source
type DeviceLocation = StringSource
The location of a device might be a path to the device on a Linux filesystem.
data InodeMetadata Source
Constructors
InodeMetadata
magic1 :: INInt
num_bytes :: INLong
uid :: INInt
gid :: INInt
mode :: FileTypefile or dir
inode_num :: INInt
flags :: INInt
hard_links :: INIntpersistent references
create_time :: INLong
last_modified_time :: INLong
level :: INInt
show/hide Instances
data Inode Source
Constructors
Inode
metaData :: InodeMetadata
blockPtrs :: INPointers
show/hide Instances
Types to make abstract (FIX)
data StateHandle Source
Read-write state
Constructors
StateHandle
stateFineMVar :: MVar FSRoot
stateCoarseMVar :: Maybe (MVar ())
show/hide Instances
data RdStat Source
This seems to be the kind of Stat information needed by the TSE front end.
Constructors
RdDirectory
modTime :: TimeT
RdFile
modTime :: TimeT
size :: SizeT
show/hide Instances
data FileSystemStats Source
Constructors
FileSystemStats
blockSize :: IntegerOptimal transfer block size in bytes.
blockCount :: IntegerTotal data blocks in file system.
blocksFree :: IntegerFree blocks in file system.
blocksAvailable :: IntegerFree blocks available to non-superusers.
fileCount :: IntegerTotal file nodes in file system.
filesFree :: IntegerFree file nodes in file system.
maxNameLength :: IntegerMaximum length of filenames. FUSE default is 255.
data FSStatus Source
Constructors
FsUnmounted
FsReadOnly
FsReadWrite
show/hide Instances
testing
makeFilesSource
:: IntNumber of files
-> FilePathWhere to put them
-> String
-> FSWrite ()
for testing. Create some files in the given directory
unitTests :: Bool -> UnitTestsSource
Produced by Haddock version 2.4.2