summaryrefslogtreecommitdiffhomepage
path: root/Tunables.hs
blob: 18e3f84f4a60617d20a25d91cd6642ad6409b7cf (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

{- Copyright 2016 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

module Tunables where

import Cost
import qualified Crypto.Argon2 as Argon2

-- | 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 -> (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 = UsePuzzleIV (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 = UsePuzzleIV (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 weakargonoptions argoncost
	, encryptionTunable = UseAES256
	, decryptionPuzzleTunable = UsePuzzleIV (GPUCost (Seconds 0))
	}
  where
	UseArgon2 argonoptions argoncost = expensiveHashTunable defaultTunables
	weakargonoptions = argonoptions { Argon2.hashIterations = 1 }