summaryrefslogtreecommitdiffhomepage
path: root/Types.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-08-07 18:49:15 -0400
committerJoey Hess <joeyh@joeyh.name>2016-08-07 18:51:09 -0400
commit07bd29a80ed36c63296214af34689d0cce14751f (patch)
treec22aa59dde551c5fb7f54f26e406c70dc441171f /Types.hs
parent6f2d6120533070ce48bbc1e12465d1f7d603aec8 (diff)
downloadkeysafe-07bd29a80ed36c63296214af34689d0cce14751f.tar.gz
reorg, and working on serialization
Diffstat (limited to 'Types.hs')
-rw-r--r--Types.hs112
1 files changed, 75 insertions, 37 deletions
diff --git a/Types.hs b/Types.hs
index b4d68f4..7873175 100644
--- a/Types.hs
+++ b/Types.hs
@@ -2,30 +2,95 @@
module Types where
-import Cost
+import Types.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
-import Data.Time.Clock
+import qualified Crypto.Argon2 as Argon2
import Data.String
-import Text.Read
-- | 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)
+
+-- | What encryption to use.
+data EncryptionTunable = UseAES256
+
+-- | An additional puzzle that makes decryption more expensive.
+data DecryptionPuzzleTunable = KeyBlindingLeftSide (Cost DecryptionOp)
+
+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
--- | 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)
@@ -52,20 +117,6 @@ gpgKey = KeyType "gpg"
data KeyIdent = KeyIdent KeyType Name
deriving (Show)
--- | A KeyIdent is serialized in the form "keytype name".
--- For example "gpg Joey Hess"
-instance Encodable KeyIdent where
- toByteString (KeyIdent (KeyType t) (Name n)) =
- t <> B.singleton identSepChar <> n
- fromByteString b = case B.break (== identSepChar) b of
- (t, n)
- | B.null n -> Nothing
- | otherwise -> Just $
- KeyIdent (KeyType t) (Name (B.drop 1 n))
-
-identSepChar :: Word8
-identSepChar = 32
-
newtype ShardNum = ShardNum Int
deriving (Show)
@@ -74,18 +125,5 @@ newtype ShardNum = ShardNum Int
data ObjectIdent = ObjectIdent ShardNum KeyIdent
deriving (Show)
--- | An ObjectIdent is serialied in the form "shardnum keytype name"
--- For example "1 gpg Joey Hess"
-instance Encodable ObjectIdent where
- toByteString (ObjectIdent (ShardNum n) keyident) =
- B8.pack (show n) <> B.singleton identSepChar <> toByteString keyident
- fromByteString b = case B.break (== identSepChar) b of
- (ns, rest)
- | B.null ns -> Nothing
- | otherwise -> do
- keyident <- fromByteString (B.drop 1 rest)
- n <- readMaybe (B8.unpack ns)
- return $ ObjectIdent (ShardNum n) keyident
-
data Benchmark t = Benchmark { expectedBenchmark :: t, actualBenchmark :: t }
deriving (Show)