Safe Haskell | None |
---|---|
Language | Haskell2010 |
An abstract view over the filesystem.
Synopsis
-
data
Handle
h =
Handle
{
- handleRaw :: !h
- handlePath :: ! FsPath
-
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
- removeFile :: HasCallStack => FsPath -> m ()
- renameFile :: HasCallStack => FsPath -> FsPath -> m ()
- mkFsErrorPath :: FsPath -> FsErrorPath
- data SomeHasFS m where
- hClose' :: ( HasCallStack , Monad m) => HasFS m h -> Handle h -> m Bool
- hGetAll :: Monad m => HasFS m h -> Handle h -> m ByteString
- hGetAllAt :: Monad m => HasFS m h -> Handle h -> AbsOffset -> m ByteString
- hGetExactly :: forall m h. ( HasCallStack , MonadThrow m) => HasFS m h -> Handle h -> Word64 -> m ByteString
- hGetExactlyAt :: forall m h. ( HasCallStack , MonadThrow m) => HasFS m h -> Handle h -> Word64 -> AbsOffset -> m ByteString
- hPut :: forall m h. ( HasCallStack , Monad m) => HasFS m h -> Handle h -> Builder -> m Word64
- hPutAll :: forall m h. ( HasCallStack , Monad m) => HasFS m h -> Handle h -> ByteString -> m Word64
- hPutAllStrict :: forall m h. ( HasCallStack , Monad m) => HasFS m h -> Handle h -> ByteString -> m Word64
- withFile :: ( HasCallStack , MonadThrow m) => HasFS m h -> FsPath -> OpenMode -> ( Handle h -> m a) -> m a
Documentation
Handle | |
|
Instances
Eq h => Eq ( Handle h) Source # | |
Show ( Handle h) Source # | |
Generic ( Handle h) Source # | |
NoThunks ( Handle h) Source # | |
Condense ( Handle h) Source # | |
type Rep ( Handle h) Source # | |
Defined in Ouroboros.Consensus.Storage.FS.API.Types
type
Rep
(
Handle
h) =
D1
('
MetaData
"Handle" "Ouroboros.Consensus.Storage.FS.API.Types" "ouroboros-consensus-0.1.0.1-DT4Cvwf63DZKctsEvaJqCU" '
False
) (
C1
('
MetaCons
"Handle" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"handleRaw") '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
h)
:*:
S1
('
MetaSel
('
Just
"handlePath") '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
FsPath
)))
|
HasFS | |
|
hClose' :: ( HasCallStack , Monad m) => HasFS m h -> Handle h -> m Bool Source #
Returns
True
when the handle was still open.
hGetAll :: Monad m => HasFS m h -> Handle h -> m ByteString Source #
Read all the data from the given file handle 64kB at a time.
Stops when EOF is reached.
:: Monad m | |
=> HasFS m h | |
-> Handle h | |
-> AbsOffset |
The offset at which to read. |
-> m ByteString |
Like
hGetAll
, but is thread safe since it does not change or depend
on the file offset.
pread
syscall is used internally.
hGetExactly :: forall m h. ( HasCallStack , MonadThrow m) => HasFS m h -> Handle h -> Word64 -> m ByteString Source #
Makes sure it reads all requested bytes. If eof is found before all bytes are read, it throws an exception.
:: forall m h. ( HasCallStack , MonadThrow m) | |
=> HasFS m h | |
-> Handle h | |
-> Word64 |
The number of bytes to read. |
-> AbsOffset |
The offset at which to read. |
-> m ByteString |
Like
hGetExactly
, but is thread safe since it does not change or depend
on the file offset.
pread
syscall is used internally.
hPut :: forall m h. ( HasCallStack , Monad m) => HasFS m h -> Handle h -> Builder -> m Word64 Source #
This function makes sure that the whole
Builder
is written.
The chunk size of the resulting
ByteString
determines how much memory
will be used while writing to the handle.
hPutAll :: forall m h. ( HasCallStack , Monad m) => HasFS m h -> Handle h -> ByteString -> m Word64 Source #
This function makes sure that the whole
ByteString
is written.
hPutAllStrict :: forall m h. ( HasCallStack , Monad m) => HasFS m h -> Handle h -> ByteString -> m Word64 Source #
This function makes sure that the whole
ByteString
is written.
withFile :: ( HasCallStack , MonadThrow m) => HasFS m h -> FsPath -> OpenMode -> ( Handle h -> m a) -> m a Source #