summaryrefslogtreecommitdiffhomepage
path: root/Cost.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-08-07 18:49:15 -0400
committerJoey Hess <joeyh@joeyh.name>2016-08-07 18:51:09 -0400
commit07bd29a80ed36c63296214af34689d0cce14751f (patch)
treec22aa59dde551c5fb7f54f26e406c70dc441171f /Cost.hs
parent6f2d6120533070ce48bbc1e12465d1f7d603aec8 (diff)
downloadkeysafe-07bd29a80ed36c63296214af34689d0cce14751f.tar.gz
reorg, and working on serialization
Diffstat (limited to 'Cost.hs')
-rw-r--r--Cost.hs56
1 files changed, 5 insertions, 51 deletions
diff --git a/Cost.hs b/Cost.hs
index 8a47fcc..4a90310 100644
--- a/Cost.hs
+++ b/Cost.hs
@@ -1,23 +1,11 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
-module Cost where
+module Cost (
+ module Cost,
+ module Types.Cost
+) where
-import Entropy
-import Utility.HumanTime
-import Data.Monoid
-
--- | An estimated cost to perform an operation.
-data Cost op
- = CPUCost Seconds -- ^ using 1 CPU core
- | 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)
+import Types.Cost
-- | Cost in seconds, with the type of hardware needed.
totalCost :: Cost op -> (Seconds, [UsingHardware])
@@ -28,9 +16,6 @@ totalCost (CombinedCost a b) =
(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)
@@ -44,33 +29,6 @@ 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
-
-- | CostCalc for a brute force linear search through an entropy space
-- in which each step entails paying a cost.
--
@@ -80,10 +38,6 @@ 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