From cf91cbc1c61d6ec86feccb6e130e71d80ba139f1 Mon Sep 17 00:00:00 2001
From: Jean-Paul Calderone <exarkun@twistedmatrix.com>
Date: Tue, 15 Aug 2023 13:17:35 -0400
Subject: [PATCH] doodles

---
 src/Tahoe/Capability/Internal/Capability.hs | 62 +++++++++++++++++++++
 1 file changed, 62 insertions(+)
 create mode 100644 src/Tahoe/Capability/Internal/Capability.hs

diff --git a/src/Tahoe/Capability/Internal/Capability.hs b/src/Tahoe/Capability/Internal/Capability.hs
new file mode 100644
index 0000000..b77ef26
--- /dev/null
+++ b/src/Tahoe/Capability/Internal/Capability.hs
@@ -0,0 +1,62 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module Tahoe.Capability.Internal.Capability where
+
+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 verifyCap where
+    -- | Represent the type of share to operate on.
+    type ShareT 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 => verifyCap -> (StorageIndex -> m (Set.Set ShareNum)) -> 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).
+    --
+    -- XXX Remove this, replace it with
+    getRequiredTotal :: MonadIO m => verifyCap -> (StorageIndex -> m LB.ByteString) -> m (Maybe (Int, Int))
+
+    -- | Get the location information for shares of this capability.
+    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.
+        verifyCap ->
+        -- | The bytes of the serialized share.
+        LB.ByteString ->
+        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 VerifierT r
+
+    -- | Attentuate the capability.
+    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 -> [(ShareNum, ShareT r)] -> LB.ByteString
+    --
+    -- cipherTextToPlainText :: r -> LB.ByteString -> LB.ByteString
+    decodeShares :: MonadIO m => r -> [(ShareNum, ShareT (VerifierT r))] -> m (Either DownloadError LB.ByteString)
+
+data DownloadError = DownloadError
-- 
GitLab