From 13c408d2295597540f0b2dfb6f7b86e739876c90 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 12 Sep 2016 22:35:47 -0400 Subject: implement client-server Proof Of Work Mashed up a argon2-based PoW with token buckets and bloom filters. This is intended to prevent a few abuses including: * Using a keysafe server for general file storage, by storing a whole lot of chunks. * An attacker guessing names that people will use, and uploading junk to keysafe servers under those names, to make it harder for others to use keysafe later. * An attacker trying to guess the names used for objects on keysafe servers in order to download them and start password cracking. (As a second level of defense, since the name generation hash is expensive already.) Completely untested, but it builds! This commit was sponsored by Andreas on Patreon. --- ExpensiveHash.hs | 61 -------------------------------------------------------- 1 file changed, 61 deletions(-) (limited to 'ExpensiveHash.hs') diff --git a/ExpensiveHash.hs b/ExpensiveHash.hs index b46b23c..6fab15c 100644 --- a/ExpensiveHash.hs +++ b/ExpensiveHash.hs @@ -7,20 +7,14 @@ module ExpensiveHash where -import Types import Tunables import Cost import Serialization () import qualified Data.Text as T import qualified Data.ByteString as B -import qualified Data.ByteString.UTF8 as BU8 import qualified Crypto.Argon2 as Argon2 import Raaz.Core.Encode -import Data.Time.Clock -import Control.DeepSeq -import Control.Monad import Data.Monoid -import Data.Maybe -- | A hash that is expensive to calculate. -- @@ -46,58 +40,3 @@ expensiveHash (UseArgon2 cost opts) (Salt s) b = ExpensiveHash cost $ argonsalt = let sb = toByteString s in sb <> B.replicate (8 - B.length sb ) 32 - -benchmarkExpensiveHash :: Int -> ExpensiveHashTunable -> Cost op -> IO (BenchmarkResult (Cost op)) -benchmarkExpensiveHash rounds tunables@(UseArgon2 _ hashopts) expected = do - numcores <- fromIntegral . fromMaybe (error "Unknown number of physical cores.") - <$> getNumCores - start <- getCurrentTime - forM_ [1..rounds] $ \n -> do - -- Must vary the data being hashed to avoid laziness - -- caching hash results. - let base = BU8.fromString (show n) - let ExpensiveHash _ t = expensiveHash tunables - (Salt (GpgKey (KeyId (base <> "dummy")))) - (base <> "himom") - t `deepseq` return () - end <- getCurrentTime - let diff = floor $ end `diffUTCTime` start - let maxthreads = Argon2.hashParallelism hashopts - let actual = CPUCost (Seconds diff) (Divisibility $ fromIntegral maxthreads) - -- The expected cost is for a single core, so adjust it - -- based on the number of cores, up to a maximum of the number - -- of threads that the hash is configred to use. - let usedcores = min maxthreads numcores - let adjustedexpected = mapCost (`div` fromIntegral usedcores) expected - return $ BenchmarkResult - { expectedBenchmark = adjustedexpected - , actualBenchmark = actual - } - -benchmarkTunables :: Tunables -> IO () -benchmarkTunables tunables = do - putStrLn "/proc/cpuinfo:" - putStrLn =<< readFile "/proc/cpuinfo" - - -- Rather than run all 256 rounds of this hash, which would - -- probably take on the order of 1 hour, run only 16, and scale - -- the expected cost accordingly. - let normalrounds = fromIntegral $ - 256 * randomSaltBytes (keyEncryptionKeyTunable tunables) - putStrLn $ "Benchmarking 16/" ++ show normalrounds ++ " rounds of key encryption key hash..." - r <- benchmarkExpensiveHash 16 - (keyEncryptionKeyHash $ keyEncryptionKeyTunable tunables) - (mapCost (`div` (normalrounds `div` 16)) $ randomSaltBytesBruteForceCost $ keyEncryptionKeyTunable tunables) - print r - putStrLn $ "Estimated time for " ++ show normalrounds ++ " rounds of key encryption key hash..." - print $ BenchmarkResult - { expectedBenchmark = mapCost (* 16) (expectedBenchmark r) - , actualBenchmark = mapCost (* 16) (actualBenchmark r) - } - - putStrLn "Benchmarking 1 round of name generation hash..." - print =<< benchmarkExpensiveHash 1 - (nameGenerationHash $ nameGenerationTunable tunables) - (getexpected $ nameGenerationHash $ nameGenerationTunable tunables) - where - getexpected (UseArgon2 cost _) = cost -- cgit v1.2.3