summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--Cost.hs8
-rw-r--r--Shard.hs18
-rw-r--r--Tunables.hs8
-rw-r--r--Types.hs24
4 files changed, 47 insertions, 11 deletions
diff --git a/Cost.hs b/Cost.hs
index ba3017b..8a47fcc 100644
--- a/Cost.hs
+++ b/Cost.hs
@@ -2,7 +2,6 @@
module Cost where
-import Types
import Entropy
import Utility.HumanTime
import Data.Monoid
@@ -72,13 +71,6 @@ reduceEntropy (Entropy a) b = Entropy (max 0 (a - b))
-- | Things that can have entropy
data UnknownPassword
--- | Naive calculation of the entropy of a password.
--- Does not take common passowrds and password generation patterns into
--- account, so this is an overestimation of how hard a password
--- is to crack.
-passwordEntropy :: Password -> Entropy UnknownPassword
-passwordEntropy (Password p) = Entropy $ floor $ totalEntropy p
-
-- | CostCalc for a brute force linear search through an entropy space
-- in which each step entails paying a cost.
--
diff --git a/Shard.hs b/Shard.hs
new file mode 100644
index 0000000..cd510cd
--- /dev/null
+++ b/Shard.hs
@@ -0,0 +1,18 @@
+module Shard where
+
+import Types
+import qualified Crypto.SecretSharing as SS
+import qualified Data.ByteString.Lazy as BL
+import Data.Binary
+
+-- | Parameters for sharding. The secret is split into
+-- N objects, such that only M are needed to reconstruct it.
+data ShardParams = ShardParams
+ { totalObjects :: Int -- ^ N
+ , neededObjects :: Int -- ^ M
+ }
+
+genShards :: EncryptedSecretKey -> ShardParams -> IO [StorableObject]
+genShards (EncryptedSecretKey esk _) ps =
+ map (StorableObject . encode) <$> SS.encode
+ (neededObjects ps) (totalObjects ps) (BL.fromStrict esk)
diff --git a/Tunables.hs b/Tunables.hs
index 79fb2a8..1806703 100644
--- a/Tunables.hs
+++ b/Tunables.hs
@@ -1,11 +1,13 @@
module Tunables where
import Types
+import Shard
import Cost
import qualified Crypto.Argon2 as Argon2
data Tunables = Tunables
{ objectSize :: Int
+ , shardParams :: shardParams
-- ^ size of objects stored in keysafe, in bytes
, argonOptions :: Argon2.HashOptions
, argonCost :: Cost CreationOp
@@ -16,7 +18,8 @@ data Tunables = Tunables
defaultTunables :: Tunables
defaultTunables = Tunables
- { objectSize = 1024*64 -- 64 kb
+ { shardParams = ShardParams { totalObjects = 3, neededObjects = 2 }
+ , objectSize = 1024*64 -- 64 kb
, argonOptions = Argon2.HashOptions
{ Argon2.hashIterations = 10000
, Argon2.hashMemory = 131072 -- 128 mebibtyes per thread
@@ -39,7 +42,8 @@ defaultTunables = Tunables
-- | Dials back cryptographic difficulty, not for production use.
testModeTunables :: Tunables
testModeTunables = Tunables
- { objectSize = 1024*64
+ { shardParams = shardParams { totalObjects = 3, neededObjects = 2 }
+ , objectSize = 1024*64
, argonOptions = Argon2.defaultHashOptions
, argonCost = CPUCost (Seconds (2*600))
, decryptionPuzzleCost = GPUCost (Seconds 60)
diff --git a/Types.hs b/Types.hs
index 8787273..b4d68f4 100644
--- a/Types.hs
+++ b/Types.hs
@@ -1,9 +1,12 @@
-{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleInstances #-}
module Types where
+import Cost
+import Entropy
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
+import qualified Data.ByteString.Lazy as BL
import Raaz.Core.Encode
import Data.Monoid
import Data.Word
@@ -11,10 +14,29 @@ import Data.Time.Clock
import Data.String
import Text.Read
+-- | keysafe stores secret keys.
+newtype SecretKey = SecretKey B.ByteString
+
+-- | The secret key, encrypted with a password.
+data EncryptedSecretKey = EncryptedSecretKey B.ByteString (CostCalc BruteForceOp UnknownPassword)
+
+instance Bruteforceable EncryptedSecretKey UnknownPassword where
+ getBruteCostCalc (EncryptedSecretKey _ cc) = cc
+
+-- | An object that can be stored on a keysafe server.
+data StorableObject = StorableObject BL.ByteString
+
-- | A password used to encrypt a key stored in keysafe.
newtype Password = Password B.ByteString
deriving (IsString)
+-- | Naive calculation of the entropy of a password.
+-- Does not take common passwords and password generation patterns into
+-- account, so this is an overestimation of how hard a password
+-- is to crack.
+passwordEntropy :: Password -> Entropy UnknownPassword
+passwordEntropy (Password p) = Entropy $ floor $ totalEntropy p
+
-- | A name associated with a key stored in keysafe.
newtype Name = Name B.ByteString
deriving (Show)