Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
An abstract view over the filesystem.
Synopsis
- data HasFS m h = HasFS {
- dumpState :: m String
- hOpen :: HasCallStack => FsPath -> OpenMode -> m (Handle h)
- hClose :: HasCallStack => Handle h -> m ()
- hIsOpen :: HasCallStack => Handle h -> m Bool
- hSeek :: HasCallStack => Handle h -> SeekMode -> Int64 -> m ()
- hGetSome :: HasCallStack => Handle h -> Word64 -> m ByteString
- hGetSomeAt :: HasCallStack => Handle h -> Word64 -> AbsOffset -> m ByteString
- hPutSome :: HasCallStack => Handle h -> ByteString -> m Word64
- hTruncate :: HasCallStack => Handle h -> Word64 -> m ()
- hGetSize :: HasCallStack => Handle h -> m Word64
- createDirectory :: HasCallStack => FsPath -> m ()
- createDirectoryIfMissing :: HasCallStack => Bool -> FsPath -> m ()
- listDirectory :: HasCallStack => FsPath -> m (Set String)
- doesDirectoryExist :: HasCallStack => FsPath -> m Bool
- doesFileExist :: HasCallStack => FsPath -> m Bool
- removeDirectoryRecursive :: HasCallStack => FsPath -> m ()
- removeFile :: HasCallStack => FsPath -> m ()
- renameFile :: HasCallStack => FsPath -> FsPath -> m ()
- mkFsErrorPath :: FsPath -> FsErrorPath
- unsafeToFilePath :: FsPath -> m FilePath
- hGetBufSome :: HasCallStack => Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> m ByteCount
- hGetBufSomeAt :: HasCallStack => Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> AbsOffset -> m ByteCount
- hPutBufSome :: HasCallStack => Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> m ByteCount
- hPutBufSomeAt :: HasCallStack => Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> AbsOffset -> m ByteCount
- module System.FS.API.Types
- hClose' :: (HasCallStack, Monad m) => HasFS m h -> Handle h -> m Bool
- withFile :: (HasCallStack, MonadThrow m) => HasFS m h -> FsPath -> OpenMode -> (Handle h -> m a) -> m a
- data SomeHasFS m where
- newtype BufferOffset = BufferOffset {}
- hGetBufExactly :: forall m h. (HasCallStack, MonadThrow m) => HasFS m h -> Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> m ByteCount
- hGetBufExactlyAt :: forall m h. (HasCallStack, MonadThrow m) => HasFS m h -> Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> AbsOffset -> m ByteCount
- hPutBufExactly :: forall m h. (HasCallStack, MonadThrow m) => HasFS m h -> Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> m ByteCount
- hPutBufExactlyAt :: forall m h. (HasCallStack, MonadThrow m) => HasFS m h -> Handle h -> MutableByteArray (PrimState m) -> BufferOffset -> ByteCount -> AbsOffset -> m ByteCount
Record that abstracts over the filesystem
Abstract interface for performing file I/O
- User-supplied buffers
- For functions that require
user-supplied buffers (i.e.,
MutableByteArray
), it is the user's responsiblity to provide buffers that are large enough. Behaviour is undefined if the I/O operations access the buffer outside it's allocated range.
HasFS | |
|
Types
module System.FS.API.Types
Opening and closing files
hClose' :: (HasCallStack, Monad m) => HasFS m h -> Handle h -> m Bool Source #
Returns True
when the handle was still open.
withFile :: (HasCallStack, MonadThrow m) => HasFS m h -> FsPath -> OpenMode -> (Handle h -> m a) -> m a Source #
SomeHasFS
data SomeHasFS m where Source #
It is often inconvenient to have to parameterise over h
. This data type
hides an existential h
parameter of a HasFS
.
File I/O with user-supplied buffers
newtype BufferOffset Source #
Absolute offset into a buffer (i.e., MutableByteArray
).
Can be negative, because buffer offsets can be added together to change
offset positions. This is similar to plusPtr
for Ptr
types. However, note
that reading or writing from a buffer at a negative offset leads to undefined
behaviour.
Instances
:: forall m h. (HasCallStack, MonadThrow m) | |
=> HasFS m h | |
-> Handle h | |
-> MutableByteArray (PrimState m) | Buffer to read bytes into |
-> BufferOffset | Offset into buffer |
-> ByteCount | The number of bytes to read |
-> m ByteCount |
Wrapper for hGetBufSome
that ensures that we read exactly as many
bytes as requested. If EOF is found before the requested number of bytes is
read, an FsError
exception is thrown.
:: forall m h. (HasCallStack, MonadThrow m) | |
=> HasFS m h | |
-> Handle h | |
-> MutableByteArray (PrimState m) | Buffer to read bytes into |
-> BufferOffset | Offset into buffer |
-> ByteCount | The number of bytes to read |
-> AbsOffset | The file offset at which to read |
-> m ByteCount |
Wrapper for hGetBufSomeAt
that ensures that we read exactly as many bytes
as requested. If EOF is found before the requested number of bytes is read,
an FsError
exception is thrown.
:: forall m h. (HasCallStack, MonadThrow m) | |
=> HasFS m h | |
-> Handle h | |
-> MutableByteArray (PrimState m) | Buffer to write bytes from |
-> BufferOffset | Offset into buffer |
-> ByteCount | The number of bytes to write |
-> m ByteCount |
Wrapper for hPutBufSome
that ensures we write exactly as many bytes as
requested.
:: forall m h. (HasCallStack, MonadThrow m) | |
=> HasFS m h | |
-> Handle h | |
-> MutableByteArray (PrimState m) | Buffer to write bytes from |
-> BufferOffset | Offset into buffer |
-> ByteCount | The number of bytes to write |
-> AbsOffset | The file offset at which to write |
-> m ByteCount |
Wrapper for hPutBufSomeAt
that ensures we write exactly as many bytes as
requested.