gbs-downloader-0.1.0.0: A library for downloading data from a Great Black Swamp server
Safe HaskellNone
LanguageHaskell2010

Tahoe.Download.Internal.Capability

Synopsis

Documentation

class Verifiable v where Source #

A capability which confers the ability to locate and verify some stored data.

Associated Types

type ShareT v Source #

Represent the type of share to operate on.

Methods

getShareNumbers :: MonadIO m => v -> StorageServer -> m (Set ShareNum) Source #

Ask a storage server which share numbers related to this capability it is holding. This is an unverified result and the storage server could present incorrect information. Even if it correctly reports that it holds a share, it could decline to give it out when asked.

getRequiredTotal :: MonadIO m => v -> StorageServer -> m (Maybe (Int, Int)) Source #

Get the encoding parameters used for the shares of this capability. The information is presented as a tuple of (required, total).

getStorageIndex :: v -> StorageIndex Source #

Get the location information for shares of this capability.

deserializeShare Source #

Arguments

:: v

A type witness revealing what type of share to decode to.

-> ByteString

The bytes of the serialized share.

-> Either (ByteString, ByteOffset, String) (ShareT v) 

Deserialize some bytes representing some kind of share to the kind of share associated with this capability type, if possible.

Instances

Instances details
Verifiable Verifier Source # 
Instance details

Defined in Tahoe.Download.Internal.Capability

Associated Types

type ShareT Verifier Source #

Methods

getShareNumbers :: MonadIO m => Verifier -> StorageServer -> m (Set ShareNum) Source #

getRequiredTotal :: MonadIO m => Verifier -> StorageServer -> m (Maybe (Int, Int)) Source #

getStorageIndex :: Verifier -> StorageIndex Source #

deserializeShare :: Verifier -> ByteString -> Either (ByteString, ByteOffset, String) (ShareT Verifier) Source #

Verifiable Verifier Source # 
Instance details

Defined in Tahoe.Download.Internal.Capability

Associated Types

type ShareT Verifier Source #

Methods

getShareNumbers :: MonadIO m => Verifier -> StorageServer -> m (Set ShareNum) Source #

getRequiredTotal :: MonadIO m => Verifier -> StorageServer -> m (Maybe (Int, Int)) Source #

getStorageIndex :: Verifier -> StorageIndex Source #

deserializeShare :: Verifier -> ByteString -> Either (ByteString, ByteOffset, String) (ShareT Verifier) Source #

class Readable r where Source #

A capability which confers the ability to recover plaintext from ciphertext.

Associated Types

type Verifier r Source #

Represent the type of a Verifiable associated with the Readable.

Methods

getVerifiable :: r -> Verifier r Source #

Attentuate the capability.

decodeShare :: MonadIO m => r -> [(Int, ShareT (Verifier r))] -> m (Either DownloadError ByteString) Source #

Interpret the required number of shares to recover the plaintext.

Note: might want to split the two functions below out of decodeShare

shareToCipherText :: r -> [(Int, ShareT r)] -> LB.ByteString

cipherTextToPlainText :: r -> LB.ByteString -> LB.ByteString

Instances

Instances details
Readable Reader Source #

A capability which confers the ability to interpret some stored data to recover the original plaintext. Additionally, it can be attentuated to a Verifiable.

Instance details

Defined in Tahoe.Download.Internal.Capability

Associated Types

type Verifier Reader Source #

Methods

getVerifiable :: Reader -> Verifier Reader Source #

decodeShare :: MonadIO m => Reader -> [(Int, ShareT (Verifier Reader))] -> m (Either DownloadError ByteString) Source #

Readable Reader Source # 
Instance details

Defined in Tahoe.Download.Internal.Capability

Associated Types

type Verifier Reader Source #

Methods

getVerifiable :: Reader -> Verifier Reader Source #

decodeShare :: MonadIO m => Reader -> [(Int, ShareT (Verifier Reader))] -> m (Either DownloadError ByteString) Source #

firstJustsM :: (Monad m, Foldable f) => f (m (Maybe a)) -> m (Maybe a) Source #

isStatusCode :: Int -> ResponseF a -> Bool Source #

Test the status code of a response for equality against a given value.

print' :: MonadIO m => String -> m () Source #