Copyright | (c) Felix Paulusma 2020 |
---|---|
License | BSD-style (see LICENSE file) |
Maintainer | cdep.illabout@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
PBKDF2
The PBKDF2 algorithm is one of the oldest and most solid password algorithms out there. It has also, however, been shown to be the least secure out of all major password algorithms. The main reason for this is that it doesn't make use of any memory cost or other method of making it difficult for specialized hardware attacks, like GPU cracking attacks.
It is still, however, used all over the world, since it has been shown to be a very reliable way to encrypt passwords. And it is most definitely better than trying to develop a password algorithm on your own, or god-forbid, not using any encryption on your stored passwords.
Other algorithms
Seeing as PBKDF2 is shown to be very weak in terms of protection
against GPU cracking attacks, it is generally advised to go with
, if not Bcrypt
or Scrypt
.
When unsure, Argon2
would probably be the safest option, as it has no memory cost which
could become a problem if not properly calibrated to the machine
doing the password verifications.Bcrypt
Synopsis
- data PBKDF2
- data Password
- mkPassword :: Text -> Password
- hashPassword :: MonadIO m => Password -> m (PasswordHash PBKDF2)
- newtype PasswordHash a = PasswordHash {}
- checkPassword :: Password -> PasswordHash PBKDF2 -> PasswordCheck
- data PasswordCheck
- hashPasswordWithParams :: MonadIO m => PBKDF2Params -> Password -> m (PasswordHash PBKDF2)
- defaultParams :: PBKDF2Params
- extractParams :: PasswordHash PBKDF2 -> Maybe PBKDF2Params
- data PBKDF2Params = PBKDF2Params {}
- data PBKDF2Algorithm
- hashPasswordWithSalt :: PBKDF2Params -> Salt PBKDF2 -> Password -> PasswordHash PBKDF2
- newSalt :: MonadIO m => m (Salt PBKDF2)
- newtype Salt a = Salt {}
- unsafeShowPassword :: Password -> Text
Documentation
Plain-text 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.
mkPassword :: Text -> Password #
Construct a Password
Hash Passwords (PBKDF2)
hashPassword :: MonadIO m => Password -> m (PasswordHash PBKDF2) Source #
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.
Instances
Read (PasswordHash a) | |
Defined in Data.Password.Types readsPrec :: Int -> ReadS (PasswordHash a) # readList :: ReadS [PasswordHash a] # readPrec :: ReadPrec (PasswordHash a) # readListPrec :: ReadPrec [PasswordHash a] # | |
Show (PasswordHash a) | |
Defined in Data.Password.Types showsPrec :: Int -> PasswordHash a -> ShowS # show :: PasswordHash a -> String # showList :: [PasswordHash a] -> ShowS # | |
Eq (PasswordHash a) | |
Defined in Data.Password.Types (==) :: PasswordHash a -> PasswordHash a -> Bool # (/=) :: PasswordHash a -> PasswordHash a -> Bool # | |
Ord (PasswordHash a) | |
Defined in Data.Password.Types compare :: PasswordHash a -> PasswordHash a -> Ordering # (<) :: PasswordHash a -> PasswordHash a -> Bool # (<=) :: PasswordHash a -> PasswordHash a -> Bool # (>) :: PasswordHash a -> PasswordHash a -> Bool # (>=) :: PasswordHash a -> PasswordHash a -> Bool # max :: PasswordHash a -> PasswordHash a -> PasswordHash a # min :: PasswordHash a -> PasswordHash a -> PasswordHash a # |
Verify Passwords (PBKDF2)
checkPassword :: Password -> PasswordHash PBKDF2 -> PasswordCheck Source #
Check a Password
against a PasswordHash
PBKDF2
.
Returns PasswordCheckSuccess
on success.
>>>
let pass = mkPassword "foobar"
>>>
passHash <- hashPassword pass
>>>
checkPassword pass passHash
PasswordCheckSuccess
Returns PasswordCheckFail
if an incorrect Password
or PasswordHash
PBKDF2
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.
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. |
Instances
Read PasswordCheck Source # | |
Defined in Data.Password.Internal readsPrec :: Int -> ReadS PasswordCheck # readList :: ReadS [PasswordCheck] # | |
Show PasswordCheck Source # | |
Defined in Data.Password.Internal showsPrec :: Int -> PasswordCheck -> ShowS # show :: PasswordCheck -> String # showList :: [PasswordCheck] -> ShowS # | |
Eq PasswordCheck Source # | |
Defined in Data.Password.Internal (==) :: PasswordCheck -> PasswordCheck -> Bool # (/=) :: PasswordCheck -> PasswordCheck -> Bool # |
Hashing Manually (PBKDF2)
hashPasswordWithParams :: MonadIO m => PBKDF2Params -> Password -> m (PasswordHash PBKDF2) Source #
Hash a password using the PBKDF2
algorithm with the given PBKDF2Params
.
N.B.: If you have any doubt in your knowledge of cryptography and/or the
PBKDF2
algorithm, please just use hashPassword
.
Since: 2.0.0.0
defaultParams :: PBKDF2Params Source #
Default parameters for the PBKDF2
algorithm.
>>>
defaultParams
PBKDF2Params {pbkdf2Salt = 16, pbkdf2Algorithm = PBKDF2_SHA512, pbkdf2Iterations = 25000, pbkdf2OutputLength = 64}
Since: 2.0.0.0
extractParams :: PasswordHash PBKDF2 -> Maybe PBKDF2Params Source #
Extracts PBKDF2Params
from a PasswordHash
PBKDF2
.
Returns 'Just PBKDF2Params' on success.
>>>
let pass = mkPassword "foobar"
>>>
passHash <- hashPassword pass
>>>
extractParams passHash == Just defaultParams
True
Since: 3.0.2.0
data PBKDF2Params Source #
Parameters used in the PBKDF2
hashing algorithm.
Since: 2.0.0.0
PBKDF2Params | |
|
Instances
Show PBKDF2Params Source # | |
Defined in Data.Password.PBKDF2 showsPrec :: Int -> PBKDF2Params -> ShowS # show :: PBKDF2Params -> String # showList :: [PBKDF2Params] -> ShowS # | |
Eq PBKDF2Params Source # | |
Defined in Data.Password.PBKDF2 (==) :: PBKDF2Params -> PBKDF2Params -> Bool # (/=) :: PBKDF2Params -> PBKDF2Params -> Bool # |
data PBKDF2Algorithm Source #
Type of algorithm to use for hashing PBKDF2 passwords.
N.B.: PBKDF2_MD5
and PBKDF2_SHA1
are not considered very secure.
Instances
Show PBKDF2Algorithm Source # | |
Defined in Data.Password.PBKDF2 showsPrec :: Int -> PBKDF2Algorithm -> ShowS # show :: PBKDF2Algorithm -> String # showList :: [PBKDF2Algorithm] -> ShowS # | |
Eq PBKDF2Algorithm Source # | |
Defined in Data.Password.PBKDF2 (==) :: PBKDF2Algorithm -> PBKDF2Algorithm -> Bool # (/=) :: PBKDF2Algorithm -> PBKDF2Algorithm -> Bool # |
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 :: PBKDF2Params -> Salt PBKDF2 -> Password -> PasswordHash PBKDF2 Source #
Hash a password with the given PBKDF2Params
and also with the given Salt
instead of a randomly generated salt using pbkdf2Salt
from PBKDF2Params
. (cf. hashPasswordWithParams
)
Using hashPasswordWithSalt
is strongly disadvised and hashPasswordWithParams
should be used instead.
Never use a static salt in production applications!
>>>
let salt = Salt "abcdefghijklmnop"
>>>
hashPasswordWithSalt defaultParams salt (mkPassword "foobar")
PasswordHash {unPasswordHash = "sha512:25000:YWJjZGVmZ2hpamtsbW5vcA==:JRElYYrOMe9OIV4LDxaLTgO9ho8fFBVofXoQcdngi7AcuH6Amvmlj2B0y6y1UtQciXXBepSCS+rpy8/vDDQvoA=="}
(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
(and hashPasswordWithParams
) generates a new Salt
everytime it is called.)
A salt used by a hashing algorithm.
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{ pbkdf2Iterations = 5000 }
>>>
let salt = Salt "abcdefghijklmnop"