summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--Encryption.hs38
-rw-r--r--ExpensiveHash.hs54
-rw-r--r--Setup.hs2
-rw-r--r--Types.hs78
-rw-r--r--keysafe.hs8
5 files changed, 180 insertions, 0 deletions
diff --git a/Encryption.hs b/Encryption.hs
new file mode 100644
index 0000000..083aedd
--- /dev/null
+++ b/Encryption.hs
@@ -0,0 +1,38 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Encryption where
+
+import Types
+import ExpensiveHash
+import qualified Data.ByteString as B
+import Raaz.Core.Encode
+import qualified Raaz.Cipher.AES as AES
+import Data.Word
+
+-- | An AES key, which is used to encrypt the key that is stored
+-- in keysafe.
+newtype KeyEncryptionKey = KeyEncryptionKey AES.KEY256
+
+-- | An ExpensiveHash of the KeyIdent and a RandomObstacle are combined
+-- to form the AES key.
+--
+-- An attacker has to brute force both, while a legitimate user
+-- only has to brute force the RandomObstacle.
+genKeyEncryptionKey :: KeyIdent -> Password -> KeyEncryptionKey
+genKeyEncryptionKey = undefined
+
+-- | A random value which adds difficulty to decrypting, since it's never
+-- written down anywhere and must always be brute-forced.
+--
+-- It's always 64 bits long, and is left padded with 0's,
+-- which are followed by a series of random bits (which necessarily always
+-- starts with 1). Eg:
+--
+-- > 0000000000000000000000000000000000000000000000000000000100011100
+--
+-- The fewer leading 0's and thus longer the random bits,
+-- the harder it is.
+data RandomObstacle = RandomObstacle Word64
+
+genRandomObstacle :: Int -> RandomObstacle
+genRandomObstacle difficulty = undefined
diff --git a/ExpensiveHash.hs b/ExpensiveHash.hs
new file mode 100644
index 0000000..8bfe004
--- /dev/null
+++ b/ExpensiveHash.hs
@@ -0,0 +1,54 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module ExpensiveHash where
+
+import Types
+import qualified Data.ByteString as B
+import Raaz.Core.Encode
+import qualified Crypto.Argon2 as Argon2
+import Data.Time.Clock
+import Control.DeepSeq
+
+-- | A hash that is expensive to calculate.
+--
+-- This is a lynchpin of keysafe's security, because using this hash
+-- as an encryption key forces brute force attackers to generate
+-- hashes over and over again, taking a very long time.
+data ExpensiveHash = ExpensiveHash Cost B.ByteString
+ deriving (Show)
+
+data Salt t = Salt t
+
+expensiveHash :: Encodable t => RunMode -> Salt t -> Password -> ExpensiveHash
+expensiveHash runmode (Salt s) (Password password) =
+ ExpensiveHash cost $ Argon2.hash o password (toByteString s)
+ where
+ HashParams o cost = hashParams runmode
+
+data HashParams = HashParams Argon2.HashOptions Cost
+
+hashParams :: RunMode -> HashParams
+hashParams SecureMode = HashParams o cost
+ where
+ -- argon2 is GPU and ASIC resistent, so it uses CPU time.
+ -- The selected HashOptions were benchmarked at 661 seconds CPU time
+ -- on a 2 core Intel(R) Core(TM) i5-4210Y CPU @ 1.50GHz.
+ cost = CPUCost (Seconds 600)
+ o = Argon2.HashOptions
+ { Argon2.hashIterations = 10000
+ , Argon2.hashMemory = 131072 -- 128 mebibtyes per thread
+ , Argon2.hashParallelism = 4 -- 4 threads
+ , Argon2.hashVariant = Argon2.Argon2i
+ }
+hashParams TestingMode =
+ HashParams Argon2.defaultHashOptions $ CPUCost (Seconds 0)
+
+benchmarkExpensiveHash :: IO (Benchmark Cost)
+benchmarkExpensiveHash = do
+ start <- getCurrentTime
+ let ExpensiveHash expected b = expensiveHash SecureMode
+ (Salt (KeyIdent gpgKey (Name ("benchmark" :: B.ByteString))))
+ (Password ("himom" :: B.ByteString))
+ end <- b `deepseq` getCurrentTime
+ let actual = (CPUCost $ Seconds $ end `diffUTCTime` start)
+ return $ Benchmark { expectedBenchmark = expected, actualBenchmark = actual }
diff --git a/Setup.hs b/Setup.hs
new file mode 100644
index 0000000..9a994af
--- /dev/null
+++ b/Setup.hs
@@ -0,0 +1,2 @@
+import Distribution.Simple
+main = defaultMain
diff --git a/Types.hs b/Types.hs
new file mode 100644
index 0000000..2be82a8
--- /dev/null
+++ b/Types.hs
@@ -0,0 +1,78 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Types where
+
+import qualified Data.ByteString as B
+import qualified Data.ByteString.Char8 as B8
+import Raaz.Core.Encode
+import Data.Monoid
+import Data.Word
+import Data.Time.Clock
+import Text.Read
+
+-- | A password used to encrypt a key stored in keysafe.
+newtype Password = Password B.ByteString
+
+-- | A name associated with a key stored in keysafe.
+newtype Name = Name B.ByteString
+ deriving (Show)
+
+-- | The type of the key that is stored in keysafe.
+newtype KeyType = KeyType B.ByteString
+ deriving (Show)
+
+gpgKey :: KeyType
+gpgKey = KeyType "gpg"
+
+-- | Enough information to uniquely identify a key stored in keysafe.
+data KeyIdent = KeyIdent KeyType Name
+ deriving (Show)
+
+-- | A KeyIdent is serialized in the form "keytype name".
+-- For example "gpg Joey Hess"
+instance Encodable KeyIdent where
+ toByteString (KeyIdent (KeyType t) (Name n)) =
+ t <> B.singleton identSepChar <> n
+ fromByteString b = case B.break (== identSepChar) b of
+ (t, n)
+ | B.null n -> Nothing
+ | otherwise -> Just $
+ KeyIdent (KeyType t) (Name (B.drop 1 n))
+
+identSepChar :: Word8
+identSepChar = 32
+
+newtype ShardNum = ShardNum Int
+ deriving (Show)
+
+-- | Enough information to uniquely identify an object stored on a keysafe
+-- server for a key.
+data ObjectIdent = ObjectIdent ShardNum KeyIdent
+ deriving (Show)
+
+-- | An ObjectIdent is serialied in the form "shardnum keytype name"
+-- For example "1 gpg Joey Hess"
+instance Encodable ObjectIdent where
+ toByteString (ObjectIdent (ShardNum n) keyident) =
+ B8.pack (show n) <> B.singleton identSepChar <> toByteString keyident
+ fromByteString b = case B.break (== identSepChar) b of
+ (ns, rest)
+ | B.null ns -> Nothing
+ | otherwise -> do
+ keyident <- fromByteString (B.drop 1 rest)
+ n <- readMaybe (B8.unpack ns)
+ return $ ObjectIdent (ShardNum n) keyident
+
+-- | An estimated cost to perform an operation.
+data Cost = CPUCost Seconds | GPUCost Seconds
+ deriving (Show)
+
+newtype Seconds = Seconds NominalDiffTime
+ deriving (Show)
+
+data Benchmark t = Benchmark { expectedBenchmark :: t, actualBenchmark :: t }
+ deriving (Show)
+
+-- | In testing mode, the cryptographic difficulty is dialed back.
+data RunMode = SecureMode | TestingMode
+ deriving (Show)
diff --git a/keysafe.hs b/keysafe.hs
new file mode 100644
index 0000000..9f9cb92
--- /dev/null
+++ b/keysafe.hs
@@ -0,0 +1,8 @@
+module Main where
+
+{-# LANGUAGE OverloadedStrings #-}
+
+import Types
+import Encryption
+
+main = print $ genKeyEncryptionKey (Password "foo") (Name "bar")