Skip to content
Snippets Groups Projects
Commit be0fef09 authored by Jean-Paul Calderone's avatar Jean-Paul Calderone
Browse files

at least type check as a starting place for next fixes

parent b1952e77
Branches
No related tags found
No related merge requests found
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Tahoe.Capability.Internal.Capability where
import Control.Monad.IO.Class
import Data.Bifunctor (Bifunctor (..))
import Data.Binary (decodeOrFail)
import Control.Monad.IO.Class (MonadIO)
import Data.Binary.Get (ByteOffset)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as LB
import qualified Data.Set as Set
type StorageIndex = B.ByteString
type ShareNum = Int
-- | A capability which confers the ability to locate and verify some stored data.
class Verifiable v where
class Verifiable verifyCap where
-- | Represent the type of share to operate on.
type ShareT v
type ShareT verifyCap
-- | Represent the type of server we can retrieve the associated shares from.
-- XXX No, this is wrong.
type ServerT verifyCap
-- | 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.
getShareNumbers :: MonadIO m => v -> StorageServer -> m (Set.Set ShareNum)
getShareNumbers :: MonadIO m => verifyCap -> ServerT verifyCap -> m (Set.Set ShareNum)
-- | Get the encoding parameters used for the shares of this capability.
-- The information is presented as a tuple of (required, total).
getRequiredTotal :: MonadIO m => v -> StorageServer -> m (Maybe (Int, Int))
getRequiredTotal :: MonadIO m => verifyCap -> ServerT verifyCap -> m (Maybe (Int, Int))
-- | Get the location information for shares of this capability.
getStorageIndex :: v -> StorageIndex
getStorageIndex :: verifyCap -> StorageIndex
-- | Deserialize some bytes representing some kind of share to the kind of
-- share associated with this capability type, if possible.
deserializeShare ::
-- | A type witness revealing what type of share to decode to.
v ->
verifyCap ->
-- | The bytes of the serialized share.
LB.ByteString ->
Either (LB.ByteString, ByteOffset, String) (ShareT v)
deserializeShare _ = fmap (\(_, _, c) -> c) . decodeOrFail
Either (LB.ByteString, ByteOffset, String) (ShareT verifyCap)
{- | A capability which confers the ability to recover plaintext from
ciphertext.
-}
class Readable r where
-- | Represent the type of a Verifiable associated with the Readable.
type Verifier r
type VerifierT r
-- | Attentuate the capability.
getVerifiable :: r -> Verifier r
getVerifiable :: r -> VerifierT r
-- | 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
-- shareToCipherText :: r -> [(ShareNum, ShareT r)] -> LB.ByteString
--
-- cipherTextToPlainText :: r -> LB.ByteString -> LB.ByteString
decodeShare :: MonadIO m => r -> [(Int, ShareT (Verifier r))] -> m (Either DownloadError LB.ByteString)
decodeShare :: MonadIO m => r -> [(ShareNum, ShareT (VerifierT r))] -> m (Either DownloadError LB.ByteString)
data DownloadError = DownloadError
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment