summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-10-07 10:18:31 -0400
committerJoey Hess <joeyh@joeyh.name>2016-10-07 10:21:02 -0400
commit3e432c60d2c6b3fecd920e8053ba4e9a75965dbd (patch)
tree4d6d8bda9efe4fae54e5509703b30aa2097239f9
parent8069f11684819fb229cfe9e40c680732776c7c9c (diff)
downloadkeysafe-3e432c60d2c6b3fecd920e8053ba4e9a75965dbd.tar.gz
Removed dependency on crypto-random.
Use raaz for random bytestring generation exclusively. It was already used in all important places, but chaffing was using crypto-random. Note that System.Random is used for delays during chaffing and by random-shuffle.
-rw-r--r--ByteStrings.hs12
-rw-r--r--CHANGELOG1
-rw-r--r--Encryption.hs8
-rw-r--r--HTTP/ProofOfWork.hs2
-rw-r--r--Storage.hs17
-rw-r--r--keysafe.cabal1
6 files changed, 23 insertions, 18 deletions
diff --git a/ByteStrings.hs b/ByteStrings.hs
index 02e22ab..cecf617 100644
--- a/ByteStrings.hs
+++ b/ByteStrings.hs
@@ -1,3 +1,5 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
{- Copyright 2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
@@ -6,6 +8,9 @@
module ByteStrings where
import qualified Data.ByteString as B
+import qualified Raaz
+import Control.Monad
+import Data.Word
allByteStringsOfLength :: Int -> [B.ByteString]
allByteStringsOfLength = go []
@@ -28,3 +33,10 @@ chunkByteString n = go []
| otherwise =
let (h, t) = B.splitAt n b
in go (h:cs) t
+
+instance Raaz.Random Word8
+
+randomByteStringOfLength :: Int -> Raaz.SystemPRG -> IO B.ByteString
+randomByteStringOfLength n prg = B.pack <$> replicateM n randbyte
+ where
+ randbyte = Raaz.random prg :: IO Word8
diff --git a/CHANGELOG b/CHANGELOG
index 3ad1fc9..7763a4f 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -1,6 +1,7 @@
keysafe (0.20161007) UNRELEASED; urgency=medium
* Check if --store-local directory is writable.
+ * Removed dependency on crypto-random.
-- Joey Hess <id@joeyh.name> Thu, 06 Oct 2016 16:48:57 -0400
diff --git a/Encryption.hs b/Encryption.hs
index 12edbc6..880095d 100644
--- a/Encryption.hs
+++ b/Encryption.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings, MultiParamTypeClasses, DataKinds #-}
-{-# OPTIONS_GHC -fno-warn-orphans #-}
{- Copyright 2016 Joey Hess <id@joeyh.name>
-
@@ -15,8 +14,6 @@ import ExpensiveHash
import ByteStrings
import Data.Monoid
import Data.Maybe
-import Data.Word
-import Control.Monad
import qualified Raaz
import qualified Raaz.Cipher.AES as Raaz
import qualified Raaz.Cipher.Internal as Raaz
@@ -152,12 +149,9 @@ genIV (Name name) =
type SaltPrefix = B.ByteString
genRandomSaltPrefix :: Raaz.SystemPRG -> Tunables -> IO SaltPrefix
-genRandomSaltPrefix prg tunables = B.pack <$> replicateM n randbyte
+genRandomSaltPrefix prg tunables = randomByteStringOfLength n prg
where
n = randomSaltBytes $ keyEncryptionKeyTunable tunables
- randbyte = Raaz.random prg :: IO Word8
-
-instance Raaz.Random Word8
-- | Make an AES key out of a hash value.
--
diff --git a/HTTP/ProofOfWork.hs b/HTTP/ProofOfWork.hs
index 39073b9..a94b19b 100644
--- a/HTTP/ProofOfWork.hs
+++ b/HTTP/ProofOfWork.hs
@@ -119,8 +119,6 @@ mkRandomSalt = do
rs <- replicateM 16 (Raaz.random prg :: IO Word8)
return $ RandomSalt $ T.pack $ concatMap show rs
-instance Raaz.Random Word8
-
class POWIdent p where
getPOWIdent :: p -> B.ByteString
diff --git a/Storage.hs b/Storage.hs
index 5ad1408..c481d77 100644
--- a/Storage.hs
+++ b/Storage.hs
@@ -16,16 +16,17 @@ import Share
import Storage.Network
import Servers
import Tunables
+import ByteStrings
import Data.Maybe
import Data.List
import Data.Monoid
import Control.Monad
-import Crypto.Random
-import System.Random
import Control.Concurrent.Thread.Delay
import Control.Concurrent.Async
import qualified Data.Set as S
+import System.Random
import System.Random.Shuffle
+import qualified Raaz
networkStorageLocations :: Maybe LocalStorageDirectory -> StorageLocations
networkStorageLocations = StorageLocations . serverList
@@ -170,25 +171,25 @@ storeChaff :: HostName -> Port -> Maybe Seconds -> IO ()
storeChaff hn port delayseconds = forever $ do
say $ "Sending chaff to " ++ hn ++ " (press ctrl-c to stop)"
say "Legend: + = successful upload, ! = upload failure"
- rng <- (cprgCreate <$> createEntropyPool) :: IO SystemRNG
- let (randomname, rng') = cprgGenerate 128 rng
+ prg <- Raaz.newPRG () :: IO Raaz.SystemPRG
+ randomname <- randomByteStringOfLength 128 prg
-- It's ok the use the testModeTunables here because
-- the randomname is not something that can be feasibly guessed.
-- Prefix "random chaff" to the name to avoid ever using a name
-- that a real user might want to use.
let sis = shareIdents testModeTunables (Name $ "random chaff:" <> randomname) AnyGpgKey
- mapConcurrently (go sis rng')
+ mapConcurrently (go sis prg)
[1..totalObjects (shareParams testModeTunables)]
where
server = networkStorage Untrusted Nothing $
Server (ServerName hn) [ServerAddress hn port] "chaff server"
objsize = objectSize defaultTunables * shareOverhead defaultTunables
maxmsdelay = ceiling $ 1000000 * fromMaybe 0 delayseconds
- go sis rng n = do
+ go sis prg n = do
msdelay <- getStdRandom (randomR (0, maxmsdelay))
delay msdelay
- let (b, rng') = cprgGenerate objsize rng
+ b <- randomByteStringOfLength objsize prg
let share = Share 0 (StorableObject b)
let (is, sis') = nextShareIdents sis
let i = S.toList is !! (n - 1)
@@ -196,7 +197,7 @@ storeChaff hn port delayseconds = forever $ do
case r of
StoreSuccess -> progress "+"
_ -> progress "!"
- go sis' rng' n
+ go sis' prg n
-- | Shuffles the list, keeping Recommended first, then
-- Alternate, and finally Untrusted.
diff --git a/keysafe.cabal b/keysafe.cabal
index 39fb22d..e5edad4 100644
--- a/keysafe.cabal
+++ b/keysafe.cabal
@@ -68,7 +68,6 @@ Executable keysafe
, unbounded-delays == 0.1.*
, fast-logger == 2.4.*
, SafeSemaphore == 0.10.*
- , crypto-random == 0.0.*
, async == 2.1.*
, unix-compat == 0.4.*
, exceptions == 0.8.*