summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-08-10 12:16:44 -0400
committerJoey Hess <joeyh@joeyh.name>2016-08-10 12:16:44 -0400
commit90b7c385f4e2f293502f9aca38aaa041b7b2f486 (patch)
tree5cc2d68b41406081d9c52271af5852ab148d1ba6
parent730c54a40681776aaaab1b727af42559cf1592fe (diff)
downloadkeysafe-90b7c385f4e2f293502f9aca38aaa041b7b2f486.tar.gz
types for new version storage scheme
-rw-r--r--Encryption.hs1
-rw-r--r--ExpensiveHash.hs3
-rw-r--r--Serialization.hs38
-rw-r--r--Types.hs81
-rw-r--r--Versions.hs95
5 files changed, 102 insertions, 116 deletions
diff --git a/Encryption.hs b/Encryption.hs
index be0a234..4a5abd8 100644
--- a/Encryption.hs
+++ b/Encryption.hs
@@ -3,6 +3,7 @@
module Encryption where
import Types
+import Versions
import Cost
import ExpensiveHash
import Data.Bits
diff --git a/ExpensiveHash.hs b/ExpensiveHash.hs
index c27f703..e089957 100644
--- a/ExpensiveHash.hs
+++ b/ExpensiveHash.hs
@@ -3,8 +3,9 @@
module ExpensiveHash where
import Types
-import Serialization
+import Versions
import Cost
+import Serialization ()
import qualified Data.ByteString as B
import Raaz.Core.Encode
import qualified Crypto.Argon2 as Argon2
diff --git a/Serialization.hs b/Serialization.hs
index 172c6f9..6a283ff 100644
--- a/Serialization.hs
+++ b/Serialization.hs
@@ -4,51 +4,13 @@
module Serialization where
import Types
-import Cost
import Raaz.Core.Encode
-import qualified Crypto.Argon2 as Argon2
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import Data.Monoid
import Data.Word
import Text.Read
-instance Encodable ExpensiveHashTunable where
- toByteString (UseArgon2 o _) = B.intercalate (B.singleton sepChar)
- [ showb (Argon2.hashIterations o)
- , showb (Argon2.hashMemory o)
- , showb (Argon2.hashParallelism o)
- , case Argon2.hashVariant o of
- Argon2.Argon2i -> "argon2i"
- Argon2.Argon2d -> "argon2d"
- ]
- where
- showb = B8.pack . show
- fromByteString b = case B.split sepChar b of
- (i:m:p:v:[]) -> do
- o <- Argon2.HashOptions
- <$> readb i
- <*> readb m
- <*> readb p
- <*> case v of
- "argon2i" -> return Argon2.Argon2i
- "argon2d" -> return Argon2.Argon2d
- _ -> Nothing
- return $ UseArgon2 o unknownCost
- _ -> Nothing
- where
- readb = readMaybe . B8.unpack
-
-instance Encodable EncryptionTunable where
- toByteString UseAES256 = "AES"
- fromByteString "AES" = Just UseAES256
- fromByteString _ = Nothing
-
-instance Encodable DecryptionPuzzleTunable where
- toByteString (KeyBlindingLeftSide _) = ">"
- fromByteString ">" = Just (KeyBlindingLeftSide unknownCost)
- fromByteString _ = Nothing
-
-- TODO
-- | An EncryptedSecretKey is serialized as first a md5sum of the rest
-- of the content, and then a SelfDescription EncryptedSecretKey,
diff --git a/Types.hs b/Types.hs
index 41c3a00..7262f33 100644
--- a/Types.hs
+++ b/Types.hs
@@ -6,94 +6,21 @@ import Types.Cost
import Entropy
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
-import qualified Crypto.Argon2 as Argon2
import Data.String
-- | keysafe stores secret keys.
newtype SecretKey = SecretKey B.ByteString
--- | Objects stored on a keysafe server are (probably) a shard of an
--- encrypted secret key.
-newtype StorableObject = StorableObject { fromStorableObject :: BL.ByteString }
-
--- | 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
- }
-
--- | keysafe stores data for a long time, and needs to be able to process
--- data from a long time ago when restoring a key. We don't want to be
--- locked into old choices of crypto primitives etc forever.
---
--- So, every parameter that can be tuned is configured in this data
--- structure. Carefully chosen parts of this are exposed at various points
--- in the data stored for a key, to allow future versions of keysafe to
--- make the right decisions when processing it.
-data Tunables = Tunables
- { shardParams :: ShardParams
- , objectSize :: Int
- -- ^ a StorableObject is exactly this many bytes in size
- , expensiveHashTunable :: ExpensiveHashTunable
- , encryptionTunable :: EncryptionTunable
- , decryptionPuzzleTunable :: DecryptionPuzzleTunable
- }
-
--- | An expensive hash, used to make it hard to crack an encrypted secret key.
-data ExpensiveHashTunable = UseArgon2 Argon2.HashOptions (Cost CreationOp)
- deriving (Show)
-
--- | What encryption to use.
-data EncryptionTunable = UseAES256
- deriving (Show)
-
--- | An additional puzzle that makes decryption more expensive.
-data DecryptionPuzzleTunable = KeyBlindingLeftSide (Cost DecryptionOp)
- deriving (Show)
-
-defaultTunables :: Tunables
-defaultTunables = Tunables
- { shardParams = ShardParams { totalObjects = 3, neededObjects = 2 }
- , objectSize = 1024*64 -- 64 kb
- , expensiveHashTunable = UseArgon2 argonoptions argoncost
- , encryptionTunable = UseAES256
- -- AES can be calculated more efficiently by a GPU, so the
- -- cost is a GPU cost.
- -- This is set to only 1 minute because GPUs are quite a lot
- -- faster than CPUs at AES, and so setting it higher would make
- -- clients too slow at key recovery.
- , decryptionPuzzleTunable = KeyBlindingLeftSide (GPUCost (Seconds 60))
- }
- where
- argonoptions = Argon2.HashOptions
- { Argon2.hashIterations = 10000
- , Argon2.hashMemory = 131072 -- 128 mebibtyes per thread
- , Argon2.hashParallelism = 4 -- 4 threads
- , Argon2.hashVariant = Argon2.Argon2i
- }
- -- argon2 is GPU and ASIC resistent, so it uses CPU time.
- -- The above HashOptions were benchmarked at 661 seconds CPU time
- -- on a 2 core Intel(R) Core(TM) i5-4210Y CPU @ 1.50GHz.
- -- Since cost is measured per core, we double that.
- argoncost = CPUCost (Seconds (2*600))
-
--- | Dials back cryptographic difficulty, not for production use.
-testModeTunables :: Tunables
-testModeTunables = Tunables
- { shardParams = ShardParams { totalObjects = 3, neededObjects = 2 }
- , objectSize = 1024*64
- , expensiveHashTunable = UseArgon2 Argon2.defaultHashOptions (CPUCost (Seconds (2*600)))
- , encryptionTunable = UseAES256
- , decryptionPuzzleTunable = KeyBlindingLeftSide (GPUCost (Seconds 60))
- }
-
-- | The secret key, encrypted with a password.
data EncryptedSecretKey = EncryptedSecretKey B.ByteString (CostCalc BruteForceOp UnknownPassword)
instance Bruteforceable EncryptedSecretKey UnknownPassword where
getBruteCostCalc (EncryptedSecretKey _ cc) = cc
+-- | Objects stored on a keysafe server are (probably) a shard of an
+-- encrypted secret key.
+newtype StorableObject = StorableObject { fromStorableObject :: BL.ByteString }
+
-- | A password used to encrypt a key stored in keysafe.
newtype Password = Password B.ByteString
deriving (IsString)
diff --git a/Versions.hs b/Versions.hs
new file mode 100644
index 0000000..a807d02
--- /dev/null
+++ b/Versions.hs
@@ -0,0 +1,95 @@
+{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
+
+module Versions where
+
+import Cost
+import qualified Crypto.Argon2 as Argon2
+
+-- | To determine the version used for a key name the expensive hash of the
+-- name is calculated, using a particular configuration, and if the
+-- object names it generates are available, we know the version.
+--
+-- Since this process is expensive, it's important that the most commonly
+-- used items come first, so that the expensive hash does not have to be
+-- calculated repatedly.
+--
+-- The reason for using this expensive method of encoding the version
+-- information is that it prevents attacks where related objects are
+-- correlated based on using an unusual version.
+knownVersions :: [(ExpensiveHashTunable, Tunables)]
+knownVersions = map (\t -> (expensiveHashTunable t, t))
+ [ defaultTunables
+ ]
+
+-- | keysafe stores data for a long time, and needs to be able to process
+-- data from a long time ago when restoring a key. We don't want to be
+-- locked into old choices of crypto primitives etc forever.
+--
+-- So, every parameter that can be tuned is configured in this data
+-- structure.
+data Tunables = Tunables
+ { shardParams :: [ShardParams]
+ -- ^ multiple ShardParams may be supported, with the user
+ -- allowed to choose between them
+ , objectSize :: Int
+ -- ^ a StorableObject is exactly this many bytes in size
+ , expensiveHashTunable :: ExpensiveHashTunable
+ , encryptionTunable :: EncryptionTunable
+ , decryptionPuzzleTunable :: DecryptionPuzzleTunable
+ }
+
+-- | 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
+ }
+
+-- | An expensive hash, used to make it hard to crack an encrypted secret key.
+data ExpensiveHashTunable = UseArgon2 Argon2.HashOptions (Cost CreationOp)
+ deriving (Show)
+
+-- | What encryption to use.
+data EncryptionTunable = UseAES256
+ deriving (Show)
+
+-- | An additional puzzle that makes decryption more expensive.
+data DecryptionPuzzleTunable = KeyBlindingLeftSide (Cost DecryptionOp)
+ deriving (Show)
+
+defaultTunables :: Tunables
+defaultTunables = Tunables
+ { shardParams = [ShardParams { totalObjects = 3, neededObjects = 2 }]
+ , objectSize = 1024*64 -- 64 kb
+ , expensiveHashTunable = UseArgon2 argonoptions argoncost
+ , encryptionTunable = UseAES256
+ -- AES can be calculated more efficiently by a GPU, so the
+ -- cost is a GPU cost.
+ -- This is set to only 1 minute because GPUs are quite a lot
+ -- faster than CPUs at AES, and so setting it higher would make
+ -- clients too slow at key recovery.
+ , decryptionPuzzleTunable = KeyBlindingLeftSide (GPUCost (Seconds 60))
+ }
+ where
+ argonoptions = Argon2.HashOptions
+ { Argon2.hashIterations = 10000
+ , Argon2.hashMemory = 131072 -- 128 mebibtyes per thread
+ , Argon2.hashParallelism = 4 -- 4 threads
+ , Argon2.hashVariant = Argon2.Argon2i
+ }
+ -- argon2 is GPU and ASIC resistent, so it uses CPU time.
+ -- The above HashOptions were benchmarked at 661 seconds CPU time
+ -- on a 2 core Intel(R) Core(TM) i5-4210Y CPU @ 1.50GHz.
+ -- Since cost is measured per core, we double that.
+ argoncost = CPUCost (Seconds (2*600))
+
+-- | Dials back cryptographic difficulty, not for production use.
+testModeTunables :: Tunables
+testModeTunables = Tunables
+ { shardParams = [ShardParams { totalObjects = 3, neededObjects = 2 }]
+ , objectSize = 1024*64
+ , expensiveHashTunable = UseArgon2 Argon2.defaultHashOptions (CPUCost (Seconds (2*600)))
+ , encryptionTunable = UseAES256
+ , decryptionPuzzleTunable = KeyBlindingLeftSide (GPUCost (Seconds 60))
+ }
+