module Crypto.KDF.Argon2
(
Options(..)
, TimeCost
, MemoryCost
, Parallelism
, Variant(..)
, Version(..)
, defaultOptions
, hash
) where
import Crypto.Internal.ByteArray (ScrubbedBytes, ByteArray, ByteArrayAccess)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Error
import Control.Monad (when)
import Data.Word
import Foreign.C
import Foreign.Ptr
data Variant =
Argon2d
| Argon2i
| Argon2id
deriving (Eq,Ord,Read,Show,Enum,Bounded)
data Version = Version10 | Version13
deriving (Eq,Ord,Read,Show,Enum,Bounded)
type TimeCost = Word32
type MemoryCost = Word32
type Parallelism = Word32
data Options = Options
{ iterations :: !TimeCost
, memory :: !MemoryCost
, parallelism :: !Parallelism
, variant :: !Variant
, version :: !Version
}
deriving (Eq,Ord,Read,Show)
saltMinLength :: Int
saltMinLength = 8
outputMinLength :: Int
outputMinLength = 4
outputMaxLength :: Int
outputMaxLength = 0x7fffffff
defaultOptions :: Options
defaultOptions =
Options { iterations = 1
, memory = 2 ^ (17 :: Int)
, parallelism = 4
, variant = Argon2i
, version = Version13
}
hash :: (ByteArrayAccess password, ByteArrayAccess salt, ByteArray out)
=> Options
-> password
-> salt
-> Int
-> CryptoFailable out
hash options password salt outLen
| saltLen < saltMinLength = CryptoFailed CryptoError_SaltTooSmall
| outLen < outputMinLength = CryptoFailed CryptoError_OutputLengthTooSmall
| outLen > outputMaxLength = CryptoFailed CryptoError_OutputLengthTooBig
| otherwise = CryptoPassed $ B.allocAndFreeze outLen $ \out -> do
res <- B.withByteArray password $ \pPass ->
B.withByteArray salt $ \pSalt ->
argon2_hash (iterations options)
(memory options)
(parallelism options)
pPass
(csizeOfInt passwordLen)
pSalt
(csizeOfInt saltLen)
out
(csizeOfInt outLen)
(cOfVariant $ variant options)
(cOfVersion $ version options)
when (res /= 0) $ error "argon2: hash: internal error"
where
saltLen = B.length salt
passwordLen = B.length password
data Pass
data Salt
data HashOut
type CVariant = CInt
type CVersion = CInt
cOfVersion :: Version -> CVersion
cOfVersion Version10 = 0x10
cOfVersion Version13 = 0x13
cOfVariant :: Variant -> CVariant
cOfVariant Argon2d = 0
cOfVariant Argon2i = 1
cOfVariant Argon2id = 2
csizeOfInt :: Int -> CSize
csizeOfInt = fromIntegral
foreign import ccall unsafe "cryptonite_argon2_hash"
argon2_hash :: Word32 -> Word32 -> Word32
-> Ptr Pass -> CSize
-> Ptr Salt -> CSize
-> Ptr HashOut -> CSize
-> CVariant
-> CVersion
-> IO CInt