| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
System.FS.Sim.Error
Description
HasFS instance wrapping SimFS that generates errors, suitable for
testing error handling.
Synopsis
- simErrorHasFS :: forall m. (MonadSTM m, MonadThrow m, PrimMonad m) => StrictTMVar m MockFS -> StrictTVar m Errors -> HasFS m HandleMock
- simErrorHasFS' :: (MonadSTM m, MonadThrow m, PrimMonad m) => MockFS -> Errors -> m (HasFS m HandleMock)
- runSimErrorFS :: (MonadSTM m, MonadThrow m, PrimMonad m) => MockFS -> Errors -> (StrictTVar m Errors -> HasFS m HandleMock -> m a) -> m (a, MockFS)
- withErrors :: MonadSTM m => StrictTVar m Errors -> Errors -> m a -> m a
- type ErrorStream = Stream FsErrorType
- type ErrorStreamGetSome = Stream (Either FsErrorType Partial)
- type ErrorStreamPutSome = Stream (Either (FsErrorType, Maybe PutCorruption) Partial)
- newtype Partial = Partial Word64
- partialiseByteCount :: Partial -> ByteCount -> ByteCount
- partialiseWord64 :: Partial -> Word64 -> Word64
- partialiseByteString :: Partial -> ByteString -> ByteString
- newtype Blob = MkBlob {}
- blobFromBS :: ByteString -> Blob
- blobToBS :: Blob -> ByteString
- data PutCorruption
- corruptByteString :: ByteString -> PutCorruption -> ByteString
- data Errors = Errors {
- dumpStateE :: ErrorStream
- hOpenE :: ErrorStream
- hCloseE :: ErrorStream
- hSeekE :: ErrorStream
- hGetSomeE :: ErrorStreamGetSome
- hGetSomeAtE :: ErrorStreamGetSome
- hPutSomeE :: ErrorStreamPutSome
- hTruncateE :: ErrorStream
- hGetSizeE :: ErrorStream
- createDirectoryE :: ErrorStream
- createDirectoryIfMissingE :: ErrorStream
- listDirectoryE :: ErrorStream
- doesDirectoryExistE :: ErrorStream
- doesFileExistE :: ErrorStream
- removeDirectoryRecursiveE :: ErrorStream
- removeFileE :: ErrorStream
- renameFileE :: ErrorStream
- hGetBufSomeE :: ErrorStreamGetSome
- hGetBufSomeAtE :: ErrorStreamGetSome
- hPutBufSomeE :: ErrorStreamPutSome
- hPutBufSomeAtE :: ErrorStreamPutSome
- allNull :: Errors -> Bool
- emptyErrors :: Errors
- genErrors :: Bool -> Bool -> Gen Errors
- simpleErrors :: ErrorStream -> Errors
Simulate Errors monad
simErrorHasFS :: forall m. (MonadSTM m, MonadThrow m, PrimMonad m) => StrictTMVar m MockFS -> StrictTVar m Errors -> HasFS m HandleMock Source #
Introduce possibility of errors
simErrorHasFS' :: (MonadSTM m, MonadThrow m, PrimMonad m) => MockFS -> Errors -> m (HasFS m HandleMock) Source #
Alternative to simErrorHasFS that creates TVars internally.
runSimErrorFS :: (MonadSTM m, MonadThrow m, PrimMonad m) => MockFS -> Errors -> (StrictTVar m Errors -> HasFS m HandleMock -> m a) -> m (a, MockFS) Source #
withErrors :: MonadSTM m => StrictTVar m Errors -> Errors -> m a -> m a Source #
Streams
type ErrorStream = Stream FsErrorType Source #
An ErrorStream is a possibly infinite Stream of (Maybe)
s.FsErrorType
Nothing indicates that there is no error.
Each time the ErrorStream is used (see runErrorStream), the first
element (Nothing in case the list is empty) is taken from the list and an
ErrorStream with the remainder of the list is returned. The first element
represents whether an error should be returned or not.
An FsError consists of a number of fields: fsErrorType, a
fsErrorPath, etc. Only the first fields is interesting. Therefore, we
only generate the FsErrorType. The FsErrorType will be used to
construct the actual FsError.
type ErrorStreamGetSome = Stream (Either FsErrorType Partial) Source #
ErrorStream for reading bytes from a file: an error or a partial get.
type ErrorStreamPutSome = Stream (Either (FsErrorType, Maybe PutCorruption) Partial) Source #
ErrorStream for writing bytes to a file: an error and possibly some
corruption, or a partial write.
Generating partial reads/writes
A , where Partial pp > 0, is a number representing how many fewer
bytes should be read or written than requested.
partialiseByteCount :: Partial -> ByteCount -> ByteCount Source #
Given a requested number of bytes to read/write, compute a partial number of bytes to read/write.
We subtract p from the number of requested bytes. If that would result in 0
requested bytes or less, we request 1 byte. If the number of requested bytes
was already 0, we can't simulate a partial read so we return 0 again.
partialiseWord64 :: Partial -> Word64 -> Word64 Source #
Like partialiseByteCount, but for Word64.
partialiseByteString :: Partial -> ByteString -> ByteString Source #
Given a bytestring that is requested to be written to disk, use
partialiseByteCount to compute a partial bytestring.
Blob
Constructors
| MkBlob | |
Fields | |
blobFromBS :: ByteString -> Blob Source #
blobToBS :: Blob -> ByteString Source #
Generating corruption for hPutSome
data PutCorruption Source #
Model possible corruptions that could happen to a hPutSome call.
Constructors
| SubstituteWithJunk Blob | The blob to write is substituted with corrupt junk |
| PartialWrite Partial | Only perform the write partially |
Instances
| Arbitrary PutCorruption Source # | |
Defined in System.FS.Sim.Error | |
| Show PutCorruption Source # | |
Defined in System.FS.Sim.Error Methods showsPrec :: Int -> PutCorruption -> ShowS # show :: PutCorruption -> String # showList :: [PutCorruption] -> ShowS # | |
corruptByteString :: ByteString -> PutCorruption -> ByteString Source #
Apply the PutCorruption to the ByteString.
If the bytestring is substituted by corrupt junk, then the output bytestring might be larger than the input bytestring.
Error streams for HasFS
Error streams for the methods of the HasFS type class.
An ErrorStream is provided for each method of the HasFS type class.
This ErrorStream will be used to generate potential errors that will be
thrown by the corresponding method.
For hPutSome, an ErrorStreamWithCorruption is provided to simulate
corruption.
An Errors is used in conjunction with SimErrorFS, which is a layer on
top of SimFS that simulates methods throwing FsErrors.
Constructors
emptyErrors :: Errors Source #
simpleErrors :: ErrorStream -> Errors Source #
Use the given ErrorStream for each field/method. No corruption of
hPutSome.