password-3.0.1.0: Hashing and checking of passwords
Copyright(c) Felix Paulusma 2020
LicenseBSD-style (see LICENSE file)
Maintainercdep.illabout@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Data.Password.Argon2

Description

Argon2

Argon2 is probably the newest password algorithm out there. Argon2 was selected as the winner of the Password Hashing Competition in July 2015.

It has three variants, namely Argon2d, Argon2i and Argon2id. These protect against GPU cracking attacks, side-channel attacks, and both, respectively.

All three modes allow specification by three parameters that control:

  • execution time
  • memory required
  • degree of parallelism

Other algorithms

In comparison to other algorithms, Argon2 is the least "battle-tested", being the newest algorithm out there.

It is, however, recommended over Scrypt most of the time, and it also seems like it might become the go-to password algorithm if no vulnarabilities are discovered within the next couple of years.

Synopsis

Documentation

data Argon2 Source #

Phantom type for Argon2

Since: 2.0.0.0

Plain-text Password

data Password #

A plain-text password.

This represents a plain-text password that has NOT been hashed.

You should be careful with Password. Make sure not to write it to logs or store it in a database.

You can construct a Password by using the mkPassword function or as literal strings together with the OverloadedStrings pragma (or manually, by using fromString on a String). Alternatively, you could also use some of the instances in the password-instances library.

Instances

Instances details
Show Password

CAREFUL: Show-ing a Password will always print "**PASSWORD**"

>>> show ("hello" :: Password)
"**PASSWORD**"
Instance details

Defined in Data.Password.Types

IsString Password 
Instance details

Defined in Data.Password.Types

mkPassword :: Text -> Password #

Construct a Password

Hash Passwords (Argon2)

hashPassword :: MonadIO m => Password -> m (PasswordHash Argon2) Source #

Hash the Password using the Argon2 hash algorithm

>>> hashPassword $ mkPassword "foobar"
PasswordHash {unPasswordHash = "$argon2id$v=19$m=65536,t=2,p=1$...$..."}

newtype PasswordHash a #

A hashed password.

This represents a password that has been put through a hashing function. The hashed password can be stored in a database.

Constructors

PasswordHash 

Fields

Instances

Instances details
Eq (PasswordHash a) 
Instance details

Defined in Data.Password.Types

Ord (PasswordHash a) 
Instance details

Defined in Data.Password.Types

Read (PasswordHash a) 
Instance details

Defined in Data.Password.Types

Show (PasswordHash a) 
Instance details

Defined in Data.Password.Types

Verify Passwords (Argon2)

checkPassword :: Password -> PasswordHash Argon2 -> PasswordCheck Source #

Check a Password against a PasswordHash Argon2.

Returns PasswordCheckSuccess on success.

>>> let pass = mkPassword "foobar"
>>> passHash <- hashPassword pass
>>> checkPassword pass passHash
PasswordCheckSuccess

Returns PasswordCheckFail if an incorrect Password or PasswordHash Argon2 is used.

>>> let badpass = mkPassword "incorrect-password"
>>> checkPassword badpass passHash
PasswordCheckFail

This should always fail if an incorrect password is given.

\(Blind badpass) -> let correctPasswordHash = hashPasswordWithSalt testParams salt "foobar" in checkPassword badpass correctPasswordHash == PasswordCheckFail

data PasswordCheck Source #

The result of checking a password against a hashed version. This is returned by the checkPassword functions.

Constructors

PasswordCheckSuccess

The password check was successful. The plain-text password matches the hashed password.

PasswordCheckFail

The password check failed. The plain-text password does not match the hashed password.

Hashing Manually (Argon2)

hashPasswordWithParams :: MonadIO m => Argon2Params -> Password -> m (PasswordHash Argon2) Source #

Hash a password using the Argon2 algorithm with the given Argon2Params.

N.B.: If you have any doubt in your knowledge of cryptography and/or the Argon2 algorithm, please just use hashPassword.

Advice to set the parameters:

  • Figure out how many threads you can use, choose "parallelism" accordingly.
  • Figure out how much memory you can use, choose "memory cost" accordingly.
  • Decide on the maximum time x you can spend on it, choose the largest "time cost" such that it takes less than x with your system and other parameter choices.

Since: 2.0.0.0

defaultParams :: Argon2Params Source #

Default parameters for the Argon2 algorithm.

>>> defaultParams
Argon2Params {argon2Salt = 16, argon2Variant = Argon2id, argon2Version = Version13, argon2MemoryCost = 65536, argon2TimeCost = 2, argon2Parallelism = 1, argon2OutputLength = 32}

Since: 2.0.0.0

data Argon2Params Source #

Parameters used in the Argon2 hashing algorithm.

Since: 2.0.0.0

Constructors

Argon2Params 

Fields

Instances

Instances details
Eq Argon2Params Source # 
Instance details

Defined in Data.Password.Argon2

Show Argon2Params Source # 
Instance details

Defined in Data.Password.Argon2

data Variant #

Which variant of Argon2 to use. You should choose the variant that is most applicable to your intention to hash inputs.

Constructors

Argon2d

Argon2d is faster than Argon2i and uses data-depending memory access, which makes it suitable for cryptocurrencies and applications with no threats from side-channel timing attacks.

Argon2i

Argon2i uses data-independent memory access, which is preferred for password hashing and password-based key derivation. Argon2i is slower as it makes more passes over the memory to protect from tradeoff attacks.

Argon2id

Argon2id is a hybrid of Argon2i and Argon2d, using a combination of data-depending and data-independent memory accesses, which gives some of Argon2i's resistance to side-channel cache timing attacks and much of Argon2d's resistance to GPU cracking attacks

Instances

Instances details
Bounded Variant 
Instance details

Defined in Crypto.KDF.Argon2

Enum Variant 
Instance details

Defined in Crypto.KDF.Argon2

Eq Variant 
Instance details

Defined in Crypto.KDF.Argon2

Methods

(==) :: Variant -> Variant -> Bool #

(/=) :: Variant -> Variant -> Bool #

Ord Variant 
Instance details

Defined in Crypto.KDF.Argon2

Read Variant 
Instance details

Defined in Crypto.KDF.Argon2

Show Variant 
Instance details

Defined in Crypto.KDF.Argon2

data Version #

Which version of Argon2 to use

Constructors

Version10 
Version13 

Instances

Instances details
Bounded Version 
Instance details

Defined in Crypto.KDF.Argon2

Enum Version 
Instance details

Defined in Crypto.KDF.Argon2

Eq Version 
Instance details

Defined in Crypto.KDF.Argon2

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Ord Version 
Instance details

Defined in Crypto.KDF.Argon2

Read Version 
Instance details

Defined in Crypto.KDF.Argon2

Show Version 
Instance details

Defined in Crypto.KDF.Argon2

Hashing with salt (DISADVISED)

Hashing with a set Salt is almost never what you want to do. Use hashPassword or hashPasswordWithParams to have automatic generation of randomized salts.

hashPasswordWithSalt :: Argon2Params -> Salt Argon2 -> Password -> PasswordHash Argon2 Source #

Hash a password with the given Argon2Params and also with the given Salt instead of a random generated salt using argon2Salt from Argon2Params. (cf. hashPasswordWithParams) Using hashPasswordWithSalt is strongly disadvised and hashPasswordWithParams should be used instead. Never use a static salt in production applications!

N.B.: The salt HAS to be 8 bytes or more, or this function will throw an error!

>>> let salt = Salt "abcdefghijklmnop"
>>> hashPasswordWithSalt defaultParams salt (mkPassword "foobar")
PasswordHash {unPasswordHash = "$argon2id$v=19$m=65536,t=2,p=1$YWJjZGVmZ2hpamtsbW5vcA$BztdyfEefG5V18ZNlztPrfZaU5duVFKZiI6dJeWht0o"}

(Note that we use an explicit Salt in the example above. This is so that the example is reproducible, but in general you should use hashPassword. hashPassword generates a new Salt everytime it is called.)

newSalt :: MonadIO m => m (Salt Argon2) Source #

Generate a random 16-byte Argon2 salt

Since: 2.0.0.0

newtype Salt a #

A salt used by a hashing algorithm.

Constructors

Salt 

Fields

Instances

Instances details
Eq (Salt a) 
Instance details

Defined in Data.Password.Types

Methods

(==) :: Salt a -> Salt a -> Bool #

(/=) :: Salt a -> Salt a -> Bool #

Show (Salt a) 
Instance details

Defined in Data.Password.Types

Methods

showsPrec :: Int -> Salt a -> ShowS #

show :: Salt a -> String #

showList :: [Salt a] -> ShowS #

Unsafe debugging function to show a Password

unsafeShowPassword :: Password -> Text #

This is an unsafe function that shows a password in plain-text.

>>> unsafeShowPassword ("foobar" :: Password)
"foobar"

You should generally not use this function in production settings, as you don't want to accidentally print a password anywhere, like logs, network responses, database entries, etc.

This will mostly be used by other libraries to handle the actual password internally, though it is conceivable that, even in a production setting, a password might have to be handled in an unsafe manner at some point.

Setup for doctests.

>>> :set -XFlexibleInstances
>>> :set -XOverloadedStrings

Import needed libraries.

>>> import Data.Password.Types
>>> import Data.ByteString (pack)
>>> import Test.QuickCheck (Arbitrary(arbitrary), Blind(Blind), vector)
>>> import Test.QuickCheck.Instances.Text ()
>>> instance Arbitrary (Salt a) where arbitrary = Salt . pack <$> vector 16
>>> instance Arbitrary Password where arbitrary = fmap mkPassword arbitrary
>>> let testParams = defaultParams {argon2TimeCost = 1}
>>> let salt = Salt "abcdefghijklmnop"