summaryrefslogtreecommitdiffhomepage
path: root/Shard.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Shard.hs')
-rw-r--r--Shard.hs38
1 files changed, 31 insertions, 7 deletions
diff --git a/Shard.hs b/Shard.hs
index a6043fd..5ec58be 100644
--- a/Shard.hs
+++ b/Shard.hs
@@ -1,19 +1,23 @@
{-# LANGUAGE OverloadedStrings, MultiParamTypeClasses #-}
+{- Copyright 2016 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU AGPL version 3 or higher.
+ -}
+
module Shard where
import Types
import Tunables
import ExpensiveHash
import Cost
-import qualified Crypto.SecretSharing as SS
+import qualified Crypto.SecretSharing.Internal as SS
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Raaz.Core.Encode as Raaz
import qualified Raaz.Hash.Sha256 as Raaz
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
-import Data.Binary
import Data.Monoid
data ShardIdents = ShardIdents
@@ -47,14 +51,34 @@ shardIdents tunables (Name name) keyid =
genShards :: EncryptedSecretKey -> Tunables -> IO [StorableObject]
genShards (EncryptedSecretKey esk _) tunables =
- map (StorableObject . encode) <$> SS.encode
+ map (StorableObject . encodeShare) <$> SS.encode
(neededObjects $ head $ shardParams tunables)
(totalObjects $ head $ shardParams tunables)
(BL.fromStrict esk)
-- Throws AssertionFailed if the number of shares is too small.
-combineShards :: [StorableObject] -> EncryptedSecretKey
-combineShards = mk . BL.toStrict . SS.decode . map conv
+combineShards :: Tunables -> [StorableObject] -> EncryptedSecretKey
+combineShards tunables = mk . SS.decode
+ . map ds . zip [1..] . map fromStorableObject
+ where
+ mk b = EncryptedSecretKey (BL.toStrict b) unknownCostCalc
+ ds (sharenum, b) = decodeShare sharenum sharesneeded b
+ sharesneeded = neededObjects $ head $ shardParams tunables
+
+-- | This efficient encoding relies on the share using a finite field of
+-- size 256, so it maps directly to bytes.
+--
+-- Note that this does not include the share number in the encoded
+-- bytestring. This prevents an attacker from partitioning their shards
+-- by share number.
+encodeShare :: SS.Share -> B.ByteString
+encodeShare = B.pack . map (fromIntegral . SS.shareValue) . SS.theShare
+
+decodeShare :: Int -> Int -> B.ByteString -> SS.Share
+decodeShare sharenum sharesneeded = SS.Share . map mk . B.unpack
where
- conv = decode . fromStorableObject
- mk b = EncryptedSecretKey b unknownCostCalc
+ mk w = SS.ByteShare
+ { SS.shareId = sharenum
+ , SS.reconstructionThreshold = sharesneeded
+ , SS.shareValue = fromIntegral w
+ }