summaryrefslogtreecommitdiffhomepage
path: root/Cost.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Cost.hs')
-rw-r--r--Cost.hs150
1 files changed, 150 insertions, 0 deletions
diff --git a/Cost.hs b/Cost.hs
new file mode 100644
index 0000000..dc2438e
--- /dev/null
+++ b/Cost.hs
@@ -0,0 +1,150 @@
+{-# 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
+import Data.List
+import Data.Maybe
+import Text.Read
+
+-- | 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) = mapCost (* 2^e) c
+
+mapCost :: (Rational-> Rational) -> Cost op -> Cost op
+mapCost f (CPUCost (Seconds n) d) = CPUCost (Seconds (f n)) d
+
+type NumCores = Integer
+
+showCostMinutes :: NumCores -> Cost op -> String
+showCostMinutes numcores (CPUCost (Seconds n) (Divisibility d))
+ | n' < 61 = "1 minute"
+ | otherwise = show (n' / 60) ++ " minutes"
+ where
+ n' :: Double
+ n' = fromRational n / fromIntegral (min numcores d)
+
+-- If an operation took n seconds on a number of cores,
+-- multiply to get the CPUCost, which is for a single core.
+coreCost :: NumCores -> Seconds -> Divisibility -> Cost op
+coreCost cores (Seconds n) d = CPUCost (Seconds (fromIntegral cores * n)) d
+
+castCost :: Cost a -> Cost b
+castCost (CPUCost s d) = CPUCost s d
+
+-- | 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
+ , instanceCpuCoreMultiplier :: Integer
+ -- ^ If the cores are twice as fast as the commodity hardware
+ -- that keysafe's cost estimates are based on, use 2 to indicate
+ -- this, etc.
+ , instanceCostPerHour :: Cents
+ }
+
+-- August 2016 spot pricing: 36 CPU core c4.8xlarge at 33c/hour
+spotAWS :: DataCenterPrice
+spotAWS = DataCenterPrice
+ { instanceCpuCores = 36
+ , instanceCpuCoreMultiplier = 2
+ , 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 / (60*60*24*365)
+ costpercpuyear = Cents $
+ fromIntegral (instanceCostPerHour dc) * 24 * 365
+ `div` (instanceCpuCores dc * instanceCpuCoreMultiplier dc)
+ costcents = Cents (ceiling 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
+
+-- Number of physical cores. This is not the same as
+-- getNumProcessors, which includes hyper-threading.
+getNumCores :: IO (Maybe NumCores)
+getNumCores = getmax . mapMaybe parse . lines <$> readFile "/proc/cpuinfo"
+ where
+ getmax [] = Nothing
+ getmax l = Just $
+ maximum l + 1 -- add 1 because /proc/cpuinfo counts from 0
+ parse l
+ | "core id" `isPrefixOf` l =
+ readMaybe $ drop 1 $ dropWhile (/= ':') l
+ | otherwise = Nothing