summaryrefslogtreecommitdiffhomepage
path: root/Shard.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Shard.hs')
-rw-r--r--Shard.hs56
1 files changed, 47 insertions, 9 deletions
diff --git a/Shard.hs b/Shard.hs
index 14ebbf5..a6043fd 100644
--- a/Shard.hs
+++ b/Shard.hs
@@ -1,22 +1,60 @@
+{-# LANGUAGE OverloadedStrings, MultiParamTypeClasses #-}
+
module Shard where
import Types
-import Serialization
+import Tunables
+import ExpensiveHash
import Cost
import qualified Crypto.SecretSharing as SS
+import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
-import Raaz.Core.Encode (toByteString, fromByteString)
+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
+ { getIdents :: [StorableObjectIdent]
+ , identsCreationCost :: Cost CreationOp
+ , identsBruteForceCalc :: CostCalc BruteForceOp UnknownName
+ }
+
+instance Bruteforceable ShardIdents UnknownName where
+ getBruteCostCalc = identsBruteForceCalc
+
+-- | Generates identifiers to use for storing shards.
+--
+-- This is an expensive operation, to make it difficult for an attacker
+-- to brute force known/guessed names and find matching shards.
+-- The keyid is used as a salt, both to avoid collisions when the same
+-- name is chosen for multiple keys, and to prevent the attacker
+-- from using a rainbow table from names to expensivehashes.
+shardIdents :: Tunables -> Name -> KeyId -> ShardIdents
+shardIdents tunables (Name name) keyid =
+ ShardIdents idents creationcost bruteforcecalc
+ where
+ (ExpensiveHash creationcost basename) =
+ expensiveHash tunables (Salt keyid) name
+ mk n = StorableObjectIdent $ Raaz.toByteString $ mksha $
+ E.encodeUtf8 $ basename <> T.pack (show n)
+ mksha :: B.ByteString -> Raaz.Base16
+ mksha = Raaz.encode . Raaz.sha256
+ idents = map mk [1..totalObjects (head (shardParams tunables))]
+ bruteforcecalc = bruteForceLinearSearch creationcost
-genShards :: EncryptedSecretKey -> ShardParams -> IO [StorableObject]
-genShards esk ps =
+genShards :: EncryptedSecretKey -> Tunables -> IO [StorableObject]
+genShards (EncryptedSecretKey esk _) tunables =
map (StorableObject . encode) <$> SS.encode
- (neededObjects ps)
- (totalObjects ps)
- (BL.fromStrict (toByteString esk))
+ (neededObjects $ head $ shardParams tunables)
+ (totalObjects $ head $ shardParams tunables)
+ (BL.fromStrict esk)
-- Throws AssertionFailed if the number of shares is too small.
-combineShards :: [StorableObject] -> Maybe EncryptedSecretKey
-combineShards = fromByteString . BL.toStrict . SS.decode . map conv
+combineShards :: [StorableObject] -> EncryptedSecretKey
+combineShards = mk . BL.toStrict . SS.decode . map conv
where
conv = decode . fromStorableObject
+ mk b = EncryptedSecretKey b unknownCostCalc