summaryrefslogtreecommitdiffhomepage
path: root/Cost.hs
blob: 88d1d61fd1976117393a31f9601418e228ed40fd (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
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}

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

module Cost (
	module Cost,
	module Types.Cost
) where

import Types.Cost

-- | Cost in seconds, with the type of hardware needed.
totalCost :: Cost op -> (Seconds, [UsingHardware])
totalCost (CPUCost s) = (s, [UsingCPU])

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)

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

-- | 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

-- | 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.
estimateAttackCost :: DataCenterPrice -> Cost BruteForceOp -> Dollars
estimateAttackCost 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)

instance Show Dollars where
	show (Dollars n) = go 
		[ (1000000000000, "trillion")
		, (1000000000, "billion")
		, (1000000, "million")
		, (1000, "thousand")
		]
	  where
		go [] = "$" ++ show n
		go ((d, u):us)
			| n >= d = 
				let n' = n `div` d
				in "$" ++ show n' ++ " " ++ u
			| otherwise = go us

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

type Year = Integer

-- | Apply Moore's law to show how a cost might vary over time.
costOverTime :: Dollars -> Year -> [(Dollars, Year)]
costOverTime (Dollars currcost) thisyear = 
	(Dollars currcost, thisyear) : map calc otheryears
  where
	otheryears = [thisyear+1, thisyear+5, thisyear+10]
	calc y = 
		let monthdelta = (fromIntegral ((y * 12) - (thisyear * 12))) :: Double
		    cost = floor $ fromIntegral currcost / 2 ** (monthdelta / 18)
		in (Dollars cost, y)

costOverTimeTable :: Dollars -> Year -> [String]
costOverTimeTable cost thisyear = go [] thisyear $ costOverTime cost thisyear
  where
	go t _ [] = reverse t
	go t yprev ((c, y):ys) =
		let s = "  in " ++ show y ++ ":  " ++ show c
		in if yprev < y - 1
			then go (s:"  ...":t) y ys
			else go (s:t) y ys