{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-} module Cost where 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) -- | 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 -- | 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 expose a 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 -- | Estimate of cost of brute force attack using AWS Spot instances, -- in US dollars. -- -- August 2016 spot pricing: 36 CPU core c4.8xlarge at 33c/hour -- -- Note that less GPU time is available on these instances; -- there are not 36 GPU cores. But for simplicity we assume there are -- that many GPU cores. So, this underestimates the price to brute -- force such operations. estimateAWSSpotAttack :: Cost BruteForceOp -> Dollars estimateAWSSpotAttack opcost = centsToDollars $ costcents where (Seconds cpuseconds) = fst (totalCost opcost) cpuyears = cpuseconds `div` (60*60*24*365) cpucores = 36 costpercpuyear = Cents (33*24*365 `div` cpucores) 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)