tahoe-great-black-swamp-types-0.5.0.0: Types related to implementation of a Tahoe-LAFS Great Black Swamp server
Safe HaskellNone
LanguageHaskell2010

Tahoe.Storage.Backend

Description

Types involved in the implementation of the backend for a Tahoe-LAFS storage server.

Synopsis

Documentation

type ApplicationVersion = ByteString Source #

A human-readable description of the backend software in use.

data Version1Parameters Source #

Give certain operational details about this storage server.

Instances

Instances details
Eq Version1Parameters Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show Version1Parameters Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic Version1Parameters Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep Version1Parameters :: Type -> Type #

type Rep Version1Parameters Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep Version1Parameters = D1 ('MetaData "Version1Parameters" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "Version1Parameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "maximumImmutableShareSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size) :*: (S1 ('MetaSel ('Just "maximumMutableShareSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size) :*: S1 ('MetaSel ('Just "availableSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size))))

data Version Source #

Carry a version string and operational parameters.

Instances

Instances details
Eq Version Source # 
Instance details

Defined in Tahoe.Storage.Backend

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Show Version Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic Version Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

type Rep Version Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep Version = D1 ('MetaData "Version" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version1Parameters) :*: S1 ('MetaSel ('Just "applicationVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ApplicationVersion)))

type Size = Integer Source #

The number of bytes in some data.

type Offset = Integer Source #

A position in some data identified by a number of bytes into that data from the beginning.

type QueryRange = Maybe ByteRanges Source #

Some ranges of data, possibly. Nothing conventionally refers to the entire data.

type StorageIndex = String Source #

An opaque identifier for a single storage area. Multiple storage objects may exist at one storage index if they have different share numbers. TODO: This should probably be ByteString instead.

type ShareData = ByteString Source #

Some data.

newtype ShareNumber Source #

The identifier of a distinct storage object, unique within the context of a particular storage index. In practice, values are in the range [0..255] (endpoints included).

Constructors

ShareNumber Integer 

Instances

Instances details
Eq ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

Ord ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep ShareNumber :: Type -> Type #

Hashable ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

ToJSON ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

FromJSON ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

FromJSONKey ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep ShareNumber Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep ShareNumber = D1 ('MetaData "ShareNumber" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'True) (C1 ('MetaCons "ShareNumber" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

newtype CBORSet a Source #

A new type for which we can define our own CBOR serialisation rules. The cborg library provides a Serialise instance for Set which is not compatible with the representation required by Tahoe-LAFS.

Constructors

CBORSet 

Fields

Instances

Instances details
Eq a => Eq (CBORSet a) Source # 
Instance details

Defined in Tahoe.Storage.Backend

Methods

(==) :: CBORSet a -> CBORSet a -> Bool #

(/=) :: CBORSet a -> CBORSet a -> Bool #

Show a => Show (CBORSet a) Source # 
Instance details

Defined in Tahoe.Storage.Backend

Methods

showsPrec :: Int -> CBORSet a -> ShowS #

show :: CBORSet a -> String #

showList :: [CBORSet a] -> ShowS #

ToJSON a => ToJSON (CBORSet a) Source # 
Instance details

Defined in Tahoe.Storage.Backend

(Ord a, FromJSON a) => FromJSON (CBORSet a) Source # 
Instance details

Defined in Tahoe.Storage.Backend

newtype CorruptionDetails Source #

Describe a client-detected incidence of data corruption.

Constructors

CorruptionDetails 

Fields

Instances

Instances details
Eq CorruptionDetails Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show CorruptionDetails Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic CorruptionDetails Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep CorruptionDetails :: Type -> Type #

type Rep CorruptionDetails Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep CorruptionDetails = D1 ('MetaData "CorruptionDetails" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'True) (C1 ('MetaCons "CorruptionDetails" 'PrefixI 'True) (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype UploadSecret Source #

A secret shared between a client and this storage server for the purpose of authorizing certain operations related to immutable uploads.

Constructors

UploadSecret ByteString 

Instances

Instances details
Eq UploadSecret Source # 
Instance details

Defined in Tahoe.Storage.Backend

newtype WriteEnablerSecret Source #

A secret shared between an SSK write capability holder and this storage server for the purpose of authorizing write operations on a mutable object.

Instances

Instances details
Eq WriteEnablerSecret Source # 
Instance details

Defined in Tahoe.Storage.Backend

data ReadTestWriteVectors Source #

Describe tests, reads, and writes to perform on a mutable object.

Instances

Instances details
Eq ReadTestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show ReadTestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic ReadTestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep ReadTestWriteVectors :: Type -> Type #

Semigroup ReadTestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Monoid ReadTestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep ReadTestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep ReadTestWriteVectors = D1 ('MetaData "ReadTestWriteVectors" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "ReadTestWriteVectors" 'PrefixI 'True) (S1 ('MetaSel ('Just "testWriteVectors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ShareNumber TestWriteVectors)) :*: S1 ('MetaSel ('Just "readVector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ReadVector])))

data TestWriteVectors Source #

Describe tests and writes to perform on a mutable object.

Constructors

TestWriteVectors 

Fields

Instances

Instances details
Eq TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep TestWriteVectors :: Type -> Type #

Semigroup TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

Monoid TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

ToJSON TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

FromJSON TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep TestWriteVectors Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep TestWriteVectors = D1 ('MetaData "TestWriteVectors" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "TestWriteVectors" 'PrefixI 'True) (S1 ('MetaSel ('Just "test") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TestVector]) :*: (S1 ('MetaSel ('Just "write") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [WriteVector]) :*: S1 ('MetaSel ('Just "newLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)))))

data TestVector Source #

Describe a single test to perform on a mutable object.

Instances

Instances details
Eq TestVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show TestVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic TestVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep TestVector :: Type -> Type #

ToJSON TestVector Source #

Serialize to the JSON as specified by the specification.

Instance details

Defined in Tahoe.Storage.Backend

FromJSON TestVector Source #

Deserialize from JSON as specified by the specification.

Instance details

Defined in Tahoe.Storage.Backend

type Rep TestVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep TestVector = D1 ('MetaData "TestVector" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "TestVector" 'PrefixI 'True) ((S1 ('MetaSel ('Just "testOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Offset) :*: S1 ('MetaSel ('Just "testSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size)) :*: (S1 ('MetaSel ('Just "operator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TestOperator) :*: S1 ('MetaSel ('Just "specimen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShareData))))

data WriteVector Source #

Describe a single write to perform on a mutable object.

Constructors

WriteVector 

Instances

Instances details
Eq WriteVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show WriteVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic WriteVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep WriteVector :: Type -> Type #

ToJSON WriteVector Source #

Serialize to the JSON as specified by the specification.

Instance details

Defined in Tahoe.Storage.Backend

FromJSON WriteVector Source #

Deserialize from JSON as specified by the specification.

Instance details

Defined in Tahoe.Storage.Backend

type Rep WriteVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep WriteVector = D1 ('MetaData "WriteVector" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "WriteVector" 'PrefixI 'True) (S1 ('MetaSel ('Just "writeOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Offset) :*: S1 ('MetaSel ('Just "shareData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShareData)))

data ReadVector Source #

Describe one read to perform on an immutable object.

Constructors

ReadVector 

Fields

Instances

Instances details
Eq ReadVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show ReadVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic ReadVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep ReadVector :: Type -> Type #

type Rep ReadVector Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep ReadVector = D1 ('MetaData "ReadVector" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "ReadVector" 'PrefixI 'True) (S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Offset) :*: S1 ('MetaSel ('Just "readSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size)))

data ReadTestWriteResult Source #

The result of a request to read andor write some data fromto some shares.

Constructors

ReadTestWriteResult 

Instances

Instances details
Eq ReadTestWriteResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show ReadTestWriteResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic ReadTestWriteResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep ReadTestWriteResult :: Type -> Type #

type Rep ReadTestWriteResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep ReadTestWriteResult = D1 ('MetaData "ReadTestWriteResult" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "ReadTestWriteResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "success") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "readData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReadResult)))

type ReadResult = Map ShareNumber [ShareData] Source #

The result of a request to read some data from some shares.

readv :: Offset -> Size -> ReadTestWriteVectors Source #

Create a ReadTestWriteVectors which performs one read at the given offset of the given size.

writev :: ShareNumber -> Offset -> ShareData -> ReadTestWriteVectors Source #

Create a ReadTestWriteVectors which performs one write on the given share number at the given offset.

testv :: ShareNumber -> Offset -> ShareData -> ReadTestWriteVectors Source #

Create a ReadTestWriteVectors which performs one test on the given share number using the given specimen.

data AllocateBuckets Source #

Describe some allocations for immutable objects requested by a client.

Instances

Instances details
Eq AllocateBuckets Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show AllocateBuckets Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic AllocateBuckets Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep AllocateBuckets :: Type -> Type #

type Rep AllocateBuckets Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep AllocateBuckets = D1 ('MetaData "AllocateBuckets" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "AllocateBuckets" 'PrefixI 'True) (S1 ('MetaSel ('Just "shareNumbers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ShareNumber]) :*: S1 ('MetaSel ('Just "allocatedSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size)))

data AllocationResult Source #

Describe the server's willingness to allocate space for some immutable objects.

Instances

Instances details
Eq AllocationResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show AllocationResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic AllocationResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep AllocationResult :: Type -> Type #

Semigroup AllocationResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

Monoid AllocationResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep AllocationResult Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep AllocationResult = D1 ('MetaData "AllocationResult" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) (C1 ('MetaCons "AllocationResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "alreadyHave") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ShareNumber]) :*: S1 ('MetaSel ('Just "allocated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ShareNumber])))

data LeaseSecret Source #

One of several kinds of shared secrets for authorizing a client to perform various operations.

data TestOperator Source #

Constructors

Lt 
Le 
Eq 
Ne 
Ge 
Gt 

Instances

Instances details
Eq TestOperator Source # 
Instance details

Defined in Tahoe.Storage.Backend

Show TestOperator Source # 
Instance details

Defined in Tahoe.Storage.Backend

Generic TestOperator Source # 
Instance details

Defined in Tahoe.Storage.Backend

Associated Types

type Rep TestOperator :: Type -> Type #

ToJSON TestOperator Source # 
Instance details

Defined in Tahoe.Storage.Backend

FromJSON TestOperator Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep TestOperator Source # 
Instance details

Defined in Tahoe.Storage.Backend

type Rep TestOperator = D1 ('MetaData "TestOperator" "Tahoe.Storage.Backend" "tahoe-great-black-swamp-types-0.5.0.0-inplace" 'False) ((C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Le" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Ne" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype Base64 Source #

A ByteString wrapper which can have its own serialization semantics.

Constructors

Base64 

Fields

Instances

Instances details
ToJSON Base64 Source #

Serialize a ByteString by encoding with Base64.

Instance details

Defined in Tahoe.Storage.Backend

FromJSON Base64 Source #

Deserialize a ByteString which has been encoded with Base64.

Instance details

Defined in Tahoe.Storage.Backend

data WriteImmutableError Source #

Exceptional cases which might be encounted by various backend for operations related to immutable shares.

Constructors

MissingUploadSecret

Used to reject an immutable allocate or upload with no upload secret.

IncorrectUploadSecret

Used to reject an immutable upload with an incorrect upload secret.

ShareSizeMismatch

Used to reject an immutable allocate of a size that does not match existing shares with the same storage index.

MaximumShareSizeExceeded

Used to reject an immutable allocate of a size greater than the maximum allowed by the server.

ImmutableShareAlreadyWritten

Used to reject an immutable write to a share that is already completely written.

ShareNotAllocated

Used to reject an immutable write to a share which has not been allocated.

ConflictingWrite

Used to reject an immutable write that overlaps with data that has already been written.

data WriteMutableError Source #

Exceptional cases which might be encounted by various backend for operations related to mutable shares.

Constructors

MissingWriteEnablerSecret

Used to reject a mutable write with no write enabler secret.

IncorrectWriteEnablerSecret

Used to reject a mutable write with an incorrect write enabler secret.

class Backend b where Source #

Methods

version :: b -> IO Version Source #

renewLease :: b -> StorageIndex -> [LeaseSecret] -> IO () Source #

Update the lease expiration time on the shares associated with the given storage index.

createImmutableStorageIndex :: b -> StorageIndex -> Maybe [LeaseSecret] -> AllocateBuckets -> IO AllocationResult Source #

writeImmutableShare :: b -> StorageIndex -> ShareNumber -> Maybe [LeaseSecret] -> ShareData -> Maybe ByteRanges -> IO () Source #

abortImmutableUpload :: b -> StorageIndex -> ShareNumber -> Maybe [LeaseSecret] -> IO () Source #

adviseCorruptImmutableShare :: b -> StorageIndex -> ShareNumber -> CorruptionDetails -> IO () Source #

getImmutableShareNumbers :: b -> StorageIndex -> IO (CBORSet ShareNumber) Source #

readImmutableShare :: b -> StorageIndex -> ShareNumber -> QueryRange -> IO ShareData Source #

readvAndTestvAndWritev Source #

Arguments

:: b 
-> StorageIndex

The storage index at which to operate.

-> WriteEnablerSecret

A shared secret which the backend can use to authorize the writes.

-> ReadTestWriteVectors

The reads, tests, and writes to perform.

-> IO ReadTestWriteResult 

Read some ranges of all shares held and/or, if test conditions are met, overwrite some ranges of some shares.

readMutableShare :: b -> StorageIndex -> ShareNumber -> QueryRange -> IO ShareData Source #

getMutableShareNumbers :: b -> StorageIndex -> IO (CBORSet ShareNumber) Source #

adviseCorruptMutableShare :: b -> StorageIndex -> ShareNumber -> CorruptionDetails -> IO () Source #