summaryrefslogtreecommitdiffhomepage
path: root/Types
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 /Types
parent6f2d6120533070ce48bbc1e12465d1f7d603aec8 (diff)
downloadkeysafe-07bd29a80ed36c63296214af34689d0cce14751f.tar.gz
reorg, and working on serialization
Diffstat (limited to 'Types')
-rw-r--r--Types/Cost.hs55
1 files changed, 55 insertions, 0 deletions
diff --git a/Types/Cost.hs b/Types/Cost.hs
new file mode 100644
index 0000000..c742848
--- /dev/null
+++ b/Types/Cost.hs
@@ -0,0 +1,55 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
+
+module Types.Cost where
+
+import Utility.HumanTime
+
+-- | 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)
+
+data UsingHardware = UsingCPU | UsingGPU | UsingASIC
+ deriving (Show)
+
+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
+
+unknownCostCalc :: CostCalc op t
+unknownCostCalc = \_e -> error "No cost calculation available"
+
+-- | 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 be brute-forced track their CostCalc.
+class Bruteforceable t a where
+ getBruteCostCalc :: t -> CostCalc BruteForceOp a
+
+-- | Things that can have entropy
+data UnknownPassword