summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2017-03-03 15:44:01 -0400
committerJoey Hess <joeyh@joeyh.name>2017-03-03 15:49:51 -0400
commitfc39ddb96af70c14c5de739408b03a14ef2053bf (patch)
treed81aedc573531e1e0e45d110a1eae1e12c296d21
parent0e5dac41b5d08d72c3799d9cc52de0ed95c2e870 (diff)
downloadkeysafe-fc39ddb96af70c14c5de739408b03a14ef2053bf.tar.gz
Updated to use raaz-0.1.1.
This commit was sponsored by John Peloquin on Patreon.
-rw-r--r--ByteStrings.hs13
-rw-r--r--CHANGELOG6
-rw-r--r--Encryption.hs18
-rw-r--r--HTTP/ProofOfWork.hs17
-rw-r--r--HTTP/Server.hs1
-rw-r--r--Storage.hs12
-rw-r--r--doc/todo/Update_to_new_version_of_raaz___40__0.1.1__41__/comment_1_5f3f9b9337e82674dc03a3de4b96ac9f._comment17
-rw-r--r--keysafe.cabal2
-rw-r--r--stack.yaml2
9 files changed, 54 insertions, 34 deletions
diff --git a/ByteStrings.hs b/ByteStrings.hs
index cecf617..90b42f0 100644
--- a/ByteStrings.hs
+++ b/ByteStrings.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-
{- Copyright 2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
@@ -9,8 +7,6 @@ module ByteStrings where
import qualified Data.ByteString as B
import qualified Raaz
-import Control.Monad
-import Data.Word
allByteStringsOfLength :: Int -> [B.ByteString]
allByteStringsOfLength = go []
@@ -34,9 +30,8 @@ chunkByteString n = go []
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
+randomByteStringOfLength :: Int -> IO B.ByteString
+randomByteStringOfLength n = Raaz.securely gen
where
- randbyte = Raaz.random prg :: IO Word8
+ gen :: Raaz.RandM B.ByteString
+ gen = Raaz.randomByteString (Raaz.BYTES n)
diff --git a/CHANGELOG b/CHANGELOG
index 8d8036b..786943d 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -1,3 +1,9 @@
+keysafe (0.20170123) UNRELEASED; urgency=medium
+
+ * Updated to use raaz-0.1.1.
+
+ -- Joey Hess <id@joeyh.name> Fri, 03 Mar 2017 15:41:36 -0400
+
keysafe (0.20170122) unstable; urgency=medium
* Adjust cabal bounds to allow building with ghc 8.0.
diff --git a/Encryption.hs b/Encryption.hs
index 880095d..3e085a0 100644
--- a/Encryption.hs
+++ b/Encryption.hs
@@ -32,10 +32,9 @@ encrypt :: Tunables -> KeyEncryptionKey -> SecretKey -> EncryptedSecretKey
encrypt tunables kek (SecretKey secret) =
EncryptedSecretKey (chunkByteString (objectSize tunables) b) (keyBruteForceCalc kek)
where
- -- Raaz does not seem to provide a high-level interface
- -- for AES encryption, so use unsafeEncrypt. The use of
- -- EncryptableBytes makes sure it's provided with a
- -- multiple of the AES block size.
+ -- Raaz does not provide a high-level interface for AES encryption,
+ -- so we use unsafeEncrypt. The use of EncryptableBytes makes
+ -- sure it's provided with a multiple of the AES block size.
b = Raaz.unsafeEncrypt cipher (keyEncryptionKey kek, keyEncryptionIV kek) $
getEncryptableBytes $ encodeEncryptableBytes tunables secret
@@ -104,8 +103,7 @@ instance HasDecryptionCost (Candidates a) where
-- run the hash repeatedly.
genKeyEncryptionKey :: Tunables -> Name -> Password -> IO KeyEncryptionKey
genKeyEncryptionKey tunables name password = do
- prg <- Raaz.newPRG () :: IO Raaz.SystemPRG
- saltprefix <- genRandomSaltPrefix prg tunables
+ saltprefix <- genRandomSaltPrefix tunables
return $ head $
genKeyEncryptionKeys [saltprefix] tunables name password
@@ -144,12 +142,12 @@ genIV (Name name) =
Raaz.fromByteString $ B.take ivlen $
Raaz.toByteString $ Raaz.sha256 name
where
- ivlen = fromIntegral $ Raaz.byteSize (undefined :: Raaz.IV)
+ ivlen = fromIntegral $ Raaz.sizeOf (undefined :: Raaz.IV)
type SaltPrefix = B.ByteString
-genRandomSaltPrefix :: Raaz.SystemPRG -> Tunables -> IO SaltPrefix
-genRandomSaltPrefix prg tunables = randomByteStringOfLength n prg
+genRandomSaltPrefix :: Tunables -> IO SaltPrefix
+genRandomSaltPrefix tunables = randomByteStringOfLength n
where
n = randomSaltBytes $ keyEncryptionKeyTunable tunables
@@ -164,7 +162,7 @@ hashToAESKey (ExpensiveHash _ t) =
fromMaybe (error "hashToAESKey fromByteString failed") $
Raaz.fromByteString b
where
- b = B.take (fromIntegral $ Raaz.byteSize (undefined :: AesKey)) $
+ b = B.take (fromIntegral $ Raaz.sizeOf (undefined :: AesKey)) $
Raaz.toByteString $ Raaz.sha256 (E.encodeUtf8 t)
-- | A bytestring that can be AES encrypted.
diff --git a/HTTP/ProofOfWork.hs b/HTTP/ProofOfWork.hs
index a94b19b..61fea20 100644
--- a/HTTP/ProofOfWork.hs
+++ b/HTTP/ProofOfWork.hs
@@ -95,10 +95,13 @@ mkProofOfWorkRequirement (Seconds n)
newtype RequestIDSecret = RequestIDSecret (Raaz.Key (Raaz.HMAC Raaz.SHA256))
+-- | Random data is generated insecurely, eg not locked in memory because
+-- this is a transient secret.
newRequestIDSecret :: IO RequestIDSecret
-newRequestIDSecret = do
- prg <- Raaz.newPRG () :: IO Raaz.SystemPRG
- RequestIDSecret <$> Raaz.random prg
+newRequestIDSecret = RequestIDSecret <$> Raaz.insecurely gen
+ where
+ gen :: Raaz.RandM (Raaz.Key (Raaz.HMAC Raaz.SHA256))
+ gen = Raaz.random
mkRequestID :: RequestIDSecret -> IO RequestID
mkRequestID secret = mkRequeestID' secret <$> mkRandomSalt
@@ -113,11 +116,15 @@ validRequestID secret rid =
let rid' = mkRequeestID' secret (randomSalt rid)
in requestHMAC rid == requestHMAC rid'
+-- | Random data is generated insecurely, eg not locked in memory because
+-- this is a transient secret.
mkRandomSalt :: IO RandomSalt
mkRandomSalt = do
- prg <- Raaz.newPRG () :: IO Raaz.SystemPRG
- rs <- replicateM 16 (Raaz.random prg :: IO Word8)
+ rs <- Raaz.insecurely $ replicateM 16 gen
return $ RandomSalt $ T.pack $ concatMap show rs
+ where
+ gen :: Raaz.RandM Word8
+ gen = Raaz.random
class POWIdent p where
getPOWIdent :: p -> B.ByteString
diff --git a/HTTP/Server.hs b/HTTP/Server.hs
index 6fd570d..61bdbfd 100644
--- a/HTTP/Server.hs
+++ b/HTTP/Server.hs
@@ -18,7 +18,6 @@ import CmdLine (ServerConfig(..))
import Storage.Local
import Serialization ()
import Servant
-import Network.Wai
import Network.Wai.Handler.Warp
import Control.Monad.IO.Class
import Control.Concurrent
diff --git a/Storage.hs b/Storage.hs
index c481d77..feb5791 100644
--- a/Storage.hs
+++ b/Storage.hs
@@ -26,7 +26,6 @@ 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
@@ -171,25 +170,24 @@ 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"
- prg <- Raaz.newPRG () :: IO Raaz.SystemPRG
- randomname <- randomByteStringOfLength 128 prg
+ randomname <- randomByteStringOfLength 128
-- 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 prg)
+ mapConcurrently (go sis)
[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 prg n = do
+ go sis n = do
msdelay <- getStdRandom (randomR (0, maxmsdelay))
delay msdelay
- b <- randomByteStringOfLength objsize prg
+ b <- randomByteStringOfLength objsize
let share = Share 0 (StorableObject b)
let (is, sis') = nextShareIdents sis
let i = S.toList is !! (n - 1)
@@ -197,7 +195,7 @@ storeChaff hn port delayseconds = forever $ do
case r of
StoreSuccess -> progress "+"
_ -> progress "!"
- go sis' prg n
+ go sis' n
-- | Shuffles the list, keeping Recommended first, then
-- Alternate, and finally Untrusted.
diff --git a/doc/todo/Update_to_new_version_of_raaz___40__0.1.1__41__/comment_1_5f3f9b9337e82674dc03a3de4b96ac9f._comment b/doc/todo/Update_to_new_version_of_raaz___40__0.1.1__41__/comment_1_5f3f9b9337e82674dc03a3de4b96ac9f._comment
new file mode 100644
index 0000000..0c9734e
--- /dev/null
+++ b/doc/todo/Update_to_new_version_of_raaz___40__0.1.1__41__/comment_1_5f3f9b9337e82674dc03a3de4b96ac9f._comment
@@ -0,0 +1,17 @@
+[[!comment format=mdwn
+ username="joey"
+ subject="""comment 1"""
+ date="2017-03-03T19:30:06Z"
+ content="""
+Got it to compile without a great deal of difficulty. Only needed changes
+around random data generation, and that is done with secure memory now
+(in cases where it matters), which is nice! (Although I still need to do
+further work to make keysafe use exclusively secure memory for gpg key
+related material.)
+
+Keysafe's test suite passes, so this *probably* avoids breaking restore of
+keys backed up before.
+
+I've committed this to master but want to test it some more before
+releasing.
+"""]]
diff --git a/keysafe.cabal b/keysafe.cabal
index 064a0e8..ebac775 100644
--- a/keysafe.cabal
+++ b/keysafe.cabal
@@ -38,7 +38,7 @@ Executable keysafe
-- the version ranges, it's important to run keysafe --test
secret-sharing == 1.0.*
, argon2 == 1.2.*
- , raaz == 0.0.2
+ , raaz == 0.1.1
, base (>= 4.5 && < 5.0)
, bytestring == 0.10.*
, text == 1.2.*
diff --git a/stack.yaml b/stack.yaml
index 2658ab6..0deb662 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -6,7 +6,7 @@ extra-deps:
- dice-entropy-conduit-1.0.0.1
- polynomial-0.7.2
- finite-field-0.8.0
- - raaz-0.0.2
+ - raaz-0.1.1
- zxcvbn-c-1.0.0
- servant-0.7.1
- servant-server-0.7.1