{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} {- Copyright 2016 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} module Tunables where import Cost import qualified Crypto.Argon2 as Argon2 import Data.Word -- | To determine the tunables 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 tunables. -- -- Since this process is expensive, it's important that the most commonly -- used tunables come first, so that the expensive hash does not have to be -- calculated repatedly. -- -- The reason for using this expensive method of encoding the tunables -- is that it prevents attacks where related objects are correlated based -- on their tunables. knownTunings :: [(ExpensiveHashTunable, Tunables)] knownTunings = map (\t -> (nameGenerationHash (nameGenerationTunable 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 { shareParams :: ShareParams , objectSize :: Int -- ^ a StorableObject is exactly this many bytes in size -- (must be a multiple of AES block size 16, and cannot be smaller -- than 256 bytes) , shareOverhead :: Int -- ^ Share encoding overhead as a multiple of the objectSize , nameGenerationTunable :: NameGenerationTunable , keyEncryptionKeyTunable :: KeyEncryptionKeyTunable , encryptionTunable :: EncryptionTunable } deriving (Show) -- | Parameters for shareing. The secret is split into -- N objects, such that only M are needed to reconstruct it. data ShareParams = ShareParams { totalObjects :: Int -- ^ N , neededObjects :: Int -- ^ M } deriving (Show) -- | An expensive hash, which makes brute-forcing hard. -- -- The creation cost estimate must be manually tuned to match the -- hash options. Use benchmarkTunables to check this. data ExpensiveHashTunable = UseArgon2 (Cost CreationOp) Argon2.HashOptions deriving (Show) data NameGenerationTunable = NameGenerationTunable { nameGenerationHash :: ExpensiveHashTunable } deriving (Show) -- | How to generate the encryption key used to encrypt the secret key. -- This is an expensive hash of the password, but not a super expensive -- hash, because a password brute forcing attacker needs to run the hash -- 256 times per random salt byte. data KeyEncryptionKeyTunable = KeyEncryptionKeyTunable { keyEncryptionKeyHash :: ExpensiveHashTunable , randomSaltBytes :: Int , randomSaltBytesBruteForceCost :: Cost BruteForceOp } deriving (Show) -- | What encryption to use. data EncryptionTunable = UseAES256 deriving (Show) -- | Tunables used by default to backup. defaultTunables :: Tunables defaultTunables = Tunables { shareParams = ShareParams { totalObjects = 3, neededObjects = 2 } , objectSize = 1024*32 -- 32 kb , shareOverhead = 2 -- The nameGenerationHash was benchmarked at 600 seconds -- on a 2 core Intel(R) Core(TM) i5-5200U CPU @ 2.20GHz. , nameGenerationTunable = NameGenerationTunable { nameGenerationHash = argon2 10000 (coreCost 2 (Seconds 600) d) } , keyEncryptionKeyTunable = KeyEncryptionKeyTunable { keyEncryptionKeyHash = argon2 169 (CPUCost (Seconds 12) d) , randomSaltBytes = 1 -- The keyEncryptionKeyHash is run 256 times per -- random salt byte to brute-force, and its parameters -- were chosen so the total brute forcing time is 50 minutes, -- on a 2 core Intel(R) Core(TM) i5-5200U CPU @ 2.20GHz. , randomSaltBytesBruteForceCost = coreCost 2 (Seconds (50*60)) d } , encryptionTunable = UseAES256 } where argon2 i c = UseArgon2 c $ Argon2.HashOptions { Argon2.hashIterations = i , Argon2.hashMemory = 131072 -- 128 mebibtyes per thread , Argon2.hashParallelism = let Divisibility n = d in fromIntegral n , Argon2.hashVariant = Argon2.Argon2i , Argon2.hashVersion = Argon2.Argon2Version13 , Argon2.hashLength = 64 } d = Divisibility 4 -- argon2 uses 4 threads -- | Dials back hash difficulty, lies about costs. -- Not for production use! testModeTunables :: Tunables testModeTunables = Tunables { shareParams = ShareParams { totalObjects = 3, neededObjects = 2 } , objectSize = 1024*32 , shareOverhead = 2 , nameGenerationTunable = NameGenerationTunable { nameGenerationHash = weakargon2 (coreCost 2 (Seconds 600) d) } , keyEncryptionKeyTunable = KeyEncryptionKeyTunable { keyEncryptionKeyHash = weakargon2 (CPUCost (Seconds 12) d) , randomSaltBytes = 1 , randomSaltBytesBruteForceCost = coreCost 2 (Seconds (50*60)) d } , encryptionTunable = UseAES256 } where weakargon2 c = UseArgon2 c Argon2.defaultHashOptions d = Divisibility 4 knownObjectSizes :: [Int] knownObjectSizes = map (calc . snd) knownTunings where calc t = objectSize t * shareOverhead t -- Hash for client-server Proof Of Work. This is tuned to take around -- 4 seconds to calculate the hash 256 times on a 4 core machine, with -- 0 added iterations. Adding more iterations will increase that somewhat. -- -- This is not included in Tunables because it doesn't affect object -- encryption and storage. Any change to this will break backwards -- compatability of the HTTP protocol! proofOfWorkHashTunable :: Word32 -> ExpensiveHashTunable proofOfWorkHashTunable addits = UseArgon2 (CPUCost (Seconds nsecs) (Divisibility 4)) $ Argon2.HashOptions { Argon2.hashIterations = nits , Argon2.hashMemory = 1000 , Argon2.hashParallelism = 4 , Argon2.hashVariant = Argon2.Argon2i , Argon2.hashVersion = Argon2.Argon2Version13 , Argon2.hashLength = 64 } where nits = 20 + addits nsecs = (4 * fromIntegral nits / 20) / 256