{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, EmptyDataDecls #-} {- Copyright 2016 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} module Types.Cost where -- | An estimated cost to perform an operation. data Cost op = CPUCost Seconds Divisibility -- ^ cost in Seconds, using 1 physical CPU core deriving (Show, Eq, Ord) newtype Seconds = Seconds Rational deriving (Num, Fractional, Real, RealFrac, Eq, Ord) instance Show Seconds where show (Seconds n) = show (fromRational n :: Double) ++ "s" -- | How many CPU cores a single run of an operation can be divided amoung. newtype Divisibility = Divisibility Integer deriving (Show, Eq, Ord) data UsingHardware = UsingCPU | UsingGPU | UsingASIC deriving (Show) instance Monoid (Cost t) where mempty = CPUCost (Seconds 0) (Divisibility 1) CPUCost (Seconds a) (Divisibility x) `mappend` CPUCost (Seconds b) (Divisibility y) = -- Take maximum divisibility, to avoid over-estimating -- the total cost. CPUCost (Seconds (a+b)) (Divisibility $ max x y) -- | Operations whose cost can be measured. data DecryptionOp data CreationOp data BruteForceOp -- | Things that track their creation cost. class HasCreationCost t where getCreationCost :: t -> Cost CreationOp -- | Things that track their decryption cost. class HasDecryptionCost t where getDecryptionCost :: t -> Cost DecryptionOp -- | Calculation of a cost that depends on some amount of entropy. type CostCalc op t = Entropy t -> Cost op unknownCostCalc :: CostCalc op t unknownCostCalc = \_e -> error "No cost calculation available" -- | Number of bits of entropy newtype Entropy t = Entropy Int deriving (Num, Show) class CalcEntropy d t where calcEntropy :: d -> Entropy t -- | 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 be brute-forced track their CostCalc. class Bruteforceable t a where getBruteCostCalc :: t -> CostCalc BruteForceOp a -- | Things that can have entropy data UnknownPassword data UnknownName