summaryrefslogtreecommitdiffhomepage
path: root/Cost.hs
blob: 38b6e2822077a4e8ddcf3d1874302d67357f2b46 (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
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}

module Cost where

import Types
import Entropy
import Utility.HumanTime
import Data.Monoid

-- | An estimated cost to perform an operation.
data Cost op 
	= CPUCost Seconds
	| GPUCost Seconds
	| CombinedCost (Cost op) (Cost op)
	deriving (Show)

newtype Seconds = Seconds Integer
	deriving (Num)

instance Show Seconds where
	show (Seconds n) = fromDuration (Duration n)

-- | Cost in seconds, with the type of hardware needed.
totalCost :: Cost op -> (Seconds, [UsingHardware])
totalCost (CPUCost s) = (s, [UsingCPU])
totalCost (GPUCost s) = (s, [UsingGPU])
totalCost (CombinedCost a b) = 
	let (s1, h1) = totalCost a
	    (s2, h2) = totalCost b
	in (s1+s2, h1++h2)

data UsingHardware = UsingCPU | UsingGPU | UsingASIC
	deriving (Show)

raiseCostPower :: Cost c -> Entropy e -> Cost c
raiseCostPower c (Entropy e) = adjustCost c (* 2^e)

adjustCost :: Cost c -> (Seconds -> Seconds) -> Cost c
adjustCost (CPUCost s) f = CPUCost (f s)
adjustCost (GPUCost s) f = GPUCost (f s)
adjustCost (CombinedCost a b) f = CombinedCost (adjustCost a f) (adjustCost b f)

castCost :: Cost a -> Cost b
castCost (CPUCost s) = CPUCost s
castCost (GPUCost s) = GPUCost s
castCost (CombinedCost a b) = CombinedCost (castCost a) (castCost b)

instance Monoid (Cost t) where
	mempty = CPUCost (Seconds 0)
	CPUCost (Seconds a) `mappend` CPUCost (Seconds b) =
		CPUCost (Seconds (a+b))
	GPUCost (Seconds a) `mappend` GPUCost (Seconds b) =
		GPUCost (Seconds (a+b))
	a `mappend` b = CombinedCost a b

-- | Operations whose cost can be measured.
data DecryptionOp
data CreationOp
data BruteForceOp

-- | Calculation of a cost that depends on some amount of entropy.
type CostCalc op t = Entropy t -> Cost op

-- | Number of bits of entropy
newtype Entropy t = Entropy Int
	deriving (Num, Show)

-- | Entropy can never go negative when subtracting bits from it.
reduceEntropy :: Entropy t -> Int -> Entropy t
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.
--
-- On average, the solution will be found half way through.
-- This is equivilant to one bit less of entropy.
bruteForceLinearSearch :: Cost step -> CostCalc BruteForceOp t
bruteForceLinearSearch stepcost e = 
	castCost stepcost `raiseCostPower` reduceEntropy e 1

-- | Things that can be brute-forced track their CostCalc.
class Bruteforceable t a where
	getBruteCostCalc :: t -> CostCalc BruteForceOp a

-- | Estimate of cost of a brute force attack.
estimateBruteforceOf :: Bruteforceable t a => t -> Entropy a -> Cost BruteForceOp
estimateBruteforceOf t e = getBruteCostCalc t e

data DataCenterPrice = DataCenterPrice
	{ instanceCpuCores :: Integer
	, instanceCostPerHour :: Cents
	}

-- August 2016 spot pricing: 36 CPU core c4.8xlarge at 33c/hour
spotAWS :: DataCenterPrice
spotAWS = DataCenterPrice
	{ instanceCpuCores = 36
	, instanceCostPerHour = Cents 33
	}

-- | Estimate of cost of brute force attack using a datacenter.
--
-- Note that this assumes that CPU cores and GPU cores are of equal number,
-- which is unlikely to be the case; typically there will be many more
-- cores than GPUs. So, this underestimates the price to brute force
-- operations which run faster on GPUs.
estimateAttack :: DataCenterPrice -> Cost BruteForceOp -> Dollars
estimateAttack dc opcost = centsToDollars $ costcents
  where
	(Seconds cpuseconds) = fst (totalCost opcost)
	cpuyears = cpuseconds `div` (60*60*24*365)
	costpercpuyear = Cents $
		fromIntegral (instanceCostPerHour dc) * 24 * 365
			`div` instanceCpuCores dc
	costcents = Cents cpuyears * costpercpuyear

newtype Cents = Cents Integer
	deriving (Num, Integral, Enum, Real, Ord, Eq, Show)

newtype Dollars = Dollars Integer
	deriving (Num, Integral, Enum, Real, Ord, Eq, Show)

centsToDollars :: Cents -> Dollars
centsToDollars (Cents c) = Dollars (c `div` 100)