{-# LANGUAGE OverloadedStrings, BangPatterns #-}
{-# LANGUAGE CPP #-}
module Yesod.Auth.Util.PasswordStore (
pbkdf1,
pbkdf2,
makePassword,
makePasswordWith,
makePasswordSalt,
makePasswordSaltWith,
verifyPassword,
verifyPasswordWith,
strengthenPassword,
passwordStrength,
Salt,
isPasswordFormatValid,
genSaltIO,
genSaltRandom,
makeSalt,
exportSalt,
importSalt
) where
import qualified Crypto.MAC.HMAC as CH
import qualified Crypto.Hash as CH
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import qualified Data.Binary as Binary
import Control.Monad
import Control.Monad.ST
import Data.STRef
import Data.Bits
import Data.ByteString.Char8 (ByteString)
import Data.ByteString.Base64 (encode, decodeLenient)
import System.IO
import System.Random
import Data.Maybe
import qualified Control.Exception
import Data.ByteArray (convert)
pbkdf1 :: ByteString -> Salt -> Int -> ByteString
pbkdf1 :: ByteString -> Salt -> Int -> ByteString
pbkdf1 ByteString
password (SaltBS ByteString
salt) Int
iter = ByteString -> Int -> ByteString
hashRounds ByteString
first_hash (Int
iter Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
where
first_hash :: ByteString
first_hash =
Digest SHA256 -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert (Digest SHA256 -> ByteString) -> Digest SHA256 -> ByteString
forall a b. (a -> b) -> a -> b
$
((Context SHA256 -> Digest SHA256
forall a. HashAlgorithm a => Context a -> Digest a
CH.hashFinalize (Context SHA256 -> Digest SHA256)
-> Context SHA256 -> Digest SHA256
forall a b. (a -> b) -> a -> b
$ Context SHA256
forall a. HashAlgorithm a => Context a
CH.hashInit Context SHA256 -> ByteString -> Context SHA256
forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
Context a -> ba -> Context a
`CH.hashUpdate` ByteString
password Context SHA256 -> ByteString -> Context SHA256
forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
Context a -> ba -> Context a
`CH.hashUpdate` ByteString
salt) :: CH.Digest CH.SHA256)
hashRounds :: ByteString -> Int -> ByteString
hashRounds :: ByteString -> Int -> ByteString
hashRounds (!ByteString
bs) Int
0 = ByteString
bs
hashRounds ByteString
bs Int
rounds = ByteString -> Int -> ByteString
hashRounds (Digest SHA256 -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert (ByteString -> Digest SHA256
forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
ba -> Digest a
CH.hash ByteString
bs :: CH.Digest CH.SHA256)) (Int
rounds Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
hmacSHA256 :: ByteString
-> ByteString
-> ByteString
hmacSHA256 :: ByteString -> ByteString -> ByteString
hmacSHA256 ByteString
secret ByteString
msg =
Digest SHA256 -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert (HMAC SHA256 -> Digest SHA256
forall a. HMAC a -> Digest a
CH.hmacGetDigest (ByteString -> ByteString -> HMAC SHA256
forall key message a.
(ByteArrayAccess key, ByteArrayAccess message, HashAlgorithm a) =>
key -> message -> HMAC a
CH.hmac ByteString
secret ByteString
msg) :: CH.Digest CH.SHA256)
pbkdf2 :: ByteString -> Salt -> Int -> ByteString
pbkdf2 :: ByteString -> Salt -> Int -> ByteString
pbkdf2 ByteString
password (SaltBS ByteString
salt) Int
c =
let hLen :: Int
hLen = Int
32
dkLen :: Int
dkLen = Int
hLen in Int -> Int -> ByteString
go Int
hLen Int
dkLen
where
go :: Int -> Int -> ByteString
go Int
hLen Int
dkLen | Int
dkLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> (Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
32 :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
hLen = [Char] -> ByteString
forall a. HasCallStack => [Char] -> a
error [Char]
"Derived key too long."
| Bool
otherwise =
let !l :: Int
l = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
ceiling ((Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dkLen Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
hLen) :: Double)
!r :: Int
r = Int
dkLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
hLen
chunks :: [ByteString]
chunks = [Int -> ByteString
f Int
i | Int
i <- [Int
1 .. Int
l]]
in ([ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> ([ByteString] -> [ByteString]) -> [ByteString] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> [ByteString]
forall a. [a] -> [a]
init ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ [ByteString]
chunks) ByteString -> ByteString -> ByteString
`B.append` Int -> ByteString -> ByteString
B.take Int
r ([ByteString] -> ByteString
forall a. [a] -> a
last [ByteString]
chunks)
f :: Int -> ByteString
f :: Int -> ByteString
f Int
i = let !u1 :: ByteString
u1 = ByteString -> ByteString -> ByteString
hmacSHA256 ByteString
password (ByteString
salt ByteString -> ByteString -> ByteString
`B.append` Int -> ByteString
int Int
i)
in (forall s. ST s ByteString) -> ByteString
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ByteString) -> ByteString)
-> (forall s. ST s ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ do
STRef s ByteString
u <- ByteString -> ST s (STRef s ByteString)
forall a s. a -> ST s (STRef s a)
newSTRef ByteString
u1
STRef s ByteString
accum <- ByteString -> ST s (STRef s ByteString)
forall a s. a -> ST s (STRef s a)
newSTRef ByteString
u1
[Int] -> (Int -> ST s ()) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
2 .. Int
c] ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s ()
forall a b. (a -> b) -> a -> b
$ \Int
_ -> do
STRef s ByteString -> (ByteString -> ByteString) -> ST s ()
forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef' STRef s ByteString
u (ByteString -> ByteString -> ByteString
hmacSHA256 ByteString
password)
ByteString
currentU <- STRef s ByteString -> ST s ByteString
forall s a. STRef s a -> ST s a
readSTRef STRef s ByteString
u
STRef s ByteString -> (ByteString -> ByteString) -> ST s ()
forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef' STRef s ByteString
accum (ByteString -> ByteString -> ByteString
`xor'` ByteString
currentU)
STRef s ByteString -> ST s ByteString
forall s a. STRef s a -> ST s a
readSTRef STRef s ByteString
accum
int :: Int -> ByteString
int :: Int -> ByteString
int Int
i = let str :: [Word8]
str = ByteString -> [Word8]
BL.unpack (ByteString -> [Word8]) -> (Int -> ByteString) -> Int -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode (Int -> [Word8]) -> Int -> [Word8]
forall a b. (a -> b) -> a -> b
$ Int
i
in [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> [Word8] -> [Word8]
forall a. Int -> [a] -> [a]
drop ([Word8] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
str Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
4) [Word8]
str
xor' :: ByteString -> ByteString -> ByteString
xor' :: ByteString -> ByteString -> ByteString
xor' !ByteString
b1 !ByteString
b2 = [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> [Word8]
forall a. (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
BS.zipWith Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
xor ByteString
b1 ByteString
b2
genSaltIO :: IO Salt
genSaltIO :: IO Salt
genSaltIO =
IO Salt -> (IOError -> IO Salt) -> IO Salt
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Control.Exception.catch IO Salt
genSaltDevURandom IOError -> IO Salt
def
where
def :: IOError -> IO Salt
def :: IOError -> IO Salt
def IOError
_ = IO Salt
genSaltSysRandom
genSaltDevURandom :: IO Salt
genSaltDevURandom :: IO Salt
genSaltDevURandom = [Char] -> IOMode -> (Handle -> IO Salt) -> IO Salt
forall r. [Char] -> IOMode -> (Handle -> IO r) -> IO r
withFile [Char]
"/dev/urandom" IOMode
ReadMode ((Handle -> IO Salt) -> IO Salt) -> (Handle -> IO Salt) -> IO Salt
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
ByteString
rawSalt <- Handle -> Int -> IO ByteString
B.hGet Handle
h Int
16
Salt -> IO Salt
forall (m :: * -> *) a. Monad m => a -> m a
return (Salt -> IO Salt) -> Salt -> IO Salt
forall a b. (a -> b) -> a -> b
$ ByteString -> Salt
makeSalt ByteString
rawSalt
genSaltSysRandom :: IO Salt
genSaltSysRandom :: IO Salt
genSaltSysRandom = IO [Char]
randomChars IO [Char] -> ([Char] -> IO Salt) -> IO Salt
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Salt -> IO Salt
forall (m :: * -> *) a. Monad m => a -> m a
return (Salt -> IO Salt) -> ([Char] -> Salt) -> [Char] -> IO Salt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Salt
makeSalt (ByteString -> Salt) -> ([Char] -> ByteString) -> [Char] -> Salt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ByteString
B.pack
where randomChars :: IO [Char]
randomChars = [IO Char] -> IO [Char]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([IO Char] -> IO [Char]) -> [IO Char] -> IO [Char]
forall a b. (a -> b) -> a -> b
$ Int -> IO Char -> [IO Char]
forall a. Int -> a -> [a]
replicate Int
16 (IO Char -> [IO Char]) -> IO Char -> [IO Char]
forall a b. (a -> b) -> a -> b
$ (Char, Char) -> IO Char
forall a (m :: * -> *). (Random a, MonadIO m) => (a, a) -> m a
randomRIO (Char
'\NUL', Char
'\255')
readPwHash :: ByteString -> Maybe (Int, Salt, ByteString)
readPwHash :: ByteString -> Maybe (Int, Salt, ByteString)
readPwHash ByteString
pw | [ByteString] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ByteString]
broken Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
4
Bool -> Bool -> Bool
|| ByteString
algorithm ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
/= ByteString
"sha256"
Bool -> Bool -> Bool
|| ByteString -> Int
B.length ByteString
hash Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
44 = Maybe (Int, Salt, ByteString)
forall a. Maybe a
Nothing
| Bool
otherwise = case ByteString -> Maybe (Int, ByteString)
B.readInt ByteString
strBS of
Just (Int
strength, ByteString
_) -> (Int, Salt, ByteString) -> Maybe (Int, Salt, ByteString)
forall a. a -> Maybe a
Just (Int
strength, ByteString -> Salt
SaltBS ByteString
salt, ByteString
hash)
Maybe (Int, ByteString)
Nothing -> Maybe (Int, Salt, ByteString)
forall a. Maybe a
Nothing
where broken :: [ByteString]
broken = Char -> ByteString -> [ByteString]
B.split Char
'|' ByteString
pw
[ByteString
algorithm, ByteString
strBS, ByteString
salt, ByteString
hash] = [ByteString]
broken
writePwHash :: (Int, Salt, ByteString) -> ByteString
writePwHash :: (Int, Salt, ByteString) -> ByteString
writePwHash (Int
strength, SaltBS ByteString
salt, ByteString
hash) =
ByteString -> [ByteString] -> ByteString
B.intercalate ByteString
"|" [ByteString
"sha256", [Char] -> ByteString
B.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
strength), ByteString
salt, ByteString
hash]
makePassword :: ByteString -> Int -> IO ByteString
makePassword :: ByteString -> Int -> IO ByteString
makePassword = (ByteString -> Salt -> Int -> ByteString)
-> ByteString -> Int -> IO ByteString
makePasswordWith ByteString -> Salt -> Int -> ByteString
pbkdf1
makePasswordWith :: (ByteString -> Salt -> Int -> ByteString)
-> ByteString
-> Int
-> IO ByteString
makePasswordWith :: (ByteString -> Salt -> Int -> ByteString)
-> ByteString -> Int -> IO ByteString
makePasswordWith ByteString -> Salt -> Int -> ByteString
algorithm ByteString
password Int
strength = do
Salt
salt <- IO Salt
genSaltIO
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int) -> ByteString -> Salt -> Int -> ByteString
makePasswordSaltWith ByteString -> Salt -> Int -> ByteString
algorithm (Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^) ByteString
password Salt
salt Int
strength
makePasswordSaltWith :: (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int)
-> ByteString
-> Salt
-> Int
-> ByteString
makePasswordSaltWith :: (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int) -> ByteString -> Salt -> Int -> ByteString
makePasswordSaltWith ByteString -> Salt -> Int -> ByteString
algorithm Int -> Int
strengthModifier ByteString
pwd Salt
salt Int
strength = (Int, Salt, ByteString) -> ByteString
writePwHash (Int
strength, Salt
salt, ByteString
hash)
where hash :: ByteString
hash = ByteString -> ByteString
encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Salt -> Int -> ByteString
algorithm ByteString
pwd Salt
salt (Int -> Int
strengthModifier Int
strength)
makePasswordSalt :: ByteString -> Salt -> Int -> ByteString
makePasswordSalt :: ByteString -> Salt -> Int -> ByteString
makePasswordSalt = (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int) -> ByteString -> Salt -> Int -> ByteString
makePasswordSaltWith ByteString -> Salt -> Int -> ByteString
pbkdf1 (Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^)
verifyPasswordWith :: (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int)
-> ByteString
-> ByteString
-> Bool
verifyPasswordWith :: (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int) -> ByteString -> ByteString -> Bool
verifyPasswordWith ByteString -> Salt -> Int -> ByteString
algorithm Int -> Int
strengthModifier ByteString
userInput ByteString
pwHash =
case ByteString -> Maybe (Int, Salt, ByteString)
readPwHash ByteString
pwHash of
Maybe (Int, Salt, ByteString)
Nothing -> Bool
False
Just (Int
strength, Salt
salt, ByteString
goodHash) ->
ByteString -> ByteString
encode (ByteString -> Salt -> Int -> ByteString
algorithm ByteString
userInput Salt
salt (Int -> Int
strengthModifier Int
strength)) ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
goodHash
verifyPassword :: ByteString -> ByteString -> Bool
verifyPassword :: ByteString -> ByteString -> Bool
verifyPassword = (ByteString -> Salt -> Int -> ByteString)
-> (Int -> Int) -> ByteString -> ByteString -> Bool
verifyPasswordWith ByteString -> Salt -> Int -> ByteString
pbkdf1 (Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^)
strengthenPassword :: ByteString -> Int -> ByteString
strengthenPassword :: ByteString -> Int -> ByteString
strengthenPassword ByteString
pwHash Int
newstr =
case ByteString -> Maybe (Int, Salt, ByteString)
readPwHash ByteString
pwHash of
Maybe (Int, Salt, ByteString)
Nothing -> ByteString
pwHash
Just (Int
oldstr, Salt
salt, ByteString
hashB64) ->
if Int
oldstr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
newstr then
(Int, Salt, ByteString) -> ByteString
writePwHash (Int
newstr, Salt
salt, ByteString
newHash)
else
ByteString
pwHash
where newHash :: ByteString
newHash = ByteString -> ByteString
encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Int -> ByteString
hashRounds ByteString
hash Int
extraRounds
extraRounds :: Int
extraRounds = (Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^Int
newstr) Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^Int
oldstr)
hash :: ByteString
hash = ByteString -> ByteString
decodeLenient ByteString
hashB64
passwordStrength :: ByteString -> Int
passwordStrength :: ByteString -> Int
passwordStrength ByteString
pwHash = case ByteString -> Maybe (Int, Salt, ByteString)
readPwHash ByteString
pwHash of
Maybe (Int, Salt, ByteString)
Nothing -> Int
0
Just (Int
strength, Salt
_, ByteString
_) -> Int
strength
newtype Salt = SaltBS ByteString
deriving (Int -> Salt -> ShowS
[Salt] -> ShowS
Salt -> [Char]
(Int -> Salt -> ShowS)
-> (Salt -> [Char]) -> ([Salt] -> ShowS) -> Show Salt
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Salt] -> ShowS
$cshowList :: [Salt] -> ShowS
show :: Salt -> [Char]
$cshow :: Salt -> [Char]
showsPrec :: Int -> Salt -> ShowS
$cshowsPrec :: Int -> Salt -> ShowS
Show, Salt -> Salt -> Bool
(Salt -> Salt -> Bool) -> (Salt -> Salt -> Bool) -> Eq Salt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Salt -> Salt -> Bool
$c/= :: Salt -> Salt -> Bool
== :: Salt -> Salt -> Bool
$c== :: Salt -> Salt -> Bool
Eq, Eq Salt
Eq Salt
-> (Salt -> Salt -> Ordering)
-> (Salt -> Salt -> Bool)
-> (Salt -> Salt -> Bool)
-> (Salt -> Salt -> Bool)
-> (Salt -> Salt -> Bool)
-> (Salt -> Salt -> Salt)
-> (Salt -> Salt -> Salt)
-> Ord Salt
Salt -> Salt -> Bool
Salt -> Salt -> Ordering
Salt -> Salt -> Salt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Salt -> Salt -> Salt
$cmin :: Salt -> Salt -> Salt
max :: Salt -> Salt -> Salt
$cmax :: Salt -> Salt -> Salt
>= :: Salt -> Salt -> Bool
$c>= :: Salt -> Salt -> Bool
> :: Salt -> Salt -> Bool
$c> :: Salt -> Salt -> Bool
<= :: Salt -> Salt -> Bool
$c<= :: Salt -> Salt -> Bool
< :: Salt -> Salt -> Bool
$c< :: Salt -> Salt -> Bool
compare :: Salt -> Salt -> Ordering
$ccompare :: Salt -> Salt -> Ordering
$cp1Ord :: Eq Salt
Ord)
makeSalt :: ByteString -> Salt
makeSalt :: ByteString -> Salt
makeSalt = ByteString -> Salt
SaltBS (ByteString -> Salt)
-> (ByteString -> ByteString) -> ByteString -> Salt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
encode (ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
check_length
where check_length :: ByteString -> ByteString
check_length ByteString
salt | ByteString -> Int
B.length ByteString
salt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
8 =
[Char] -> ByteString
forall a. HasCallStack => [Char] -> a
error [Char]
"Salt too short. Minimum length is 8 characters."
| Bool
otherwise = ByteString
salt
exportSalt :: Salt -> ByteString
exportSalt :: Salt -> ByteString
exportSalt (SaltBS ByteString
bs) = ByteString
bs
importSalt :: ByteString -> Salt
importSalt :: ByteString -> Salt
importSalt = ByteString -> Salt
SaltBS
isPasswordFormatValid :: ByteString -> Bool
isPasswordFormatValid :: ByteString -> Bool
isPasswordFormatValid = Maybe (Int, Salt, ByteString) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (Int, Salt, ByteString) -> Bool)
-> (ByteString -> Maybe (Int, Salt, ByteString))
-> ByteString
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (Int, Salt, ByteString)
readPwHash
genSaltRandom :: (RandomGen b) => b -> (Salt, b)
genSaltRandom :: b -> (Salt, b)
genSaltRandom b
gen = (Salt
salt, b
newgen)
where rands :: t -> Int -> [(Char, t)]
rands t
_ Int
0 = []
rands t
g Int
n = (Char
a, t
g') (Char, t) -> [(Char, t)] -> [(Char, t)]
forall a. a -> [a] -> [a]
: t -> Int -> [(Char, t)]
rands t
g' (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1 :: Int)
where (Char
a, t
g') = (Char, Char) -> t -> (Char, t)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Char
'\NUL', Char
'\255') t
g
salt :: Salt
salt = ByteString -> Salt
makeSalt (ByteString -> Salt) -> ByteString -> Salt
forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
B.pack ([Char] -> ByteString) -> [Char] -> ByteString
forall a b. (a -> b) -> a -> b
$ ((Char, b) -> Char) -> [(Char, b)] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map (Char, b) -> Char
forall a b. (a, b) -> a
fst (b -> Int -> [(Char, b)]
forall t. RandomGen t => t -> Int -> [(Char, t)]
rands b
gen Int
16)
newgen :: b
newgen = (Char, b) -> b
forall a b. (a, b) -> b
snd ((Char, b) -> b) -> (Char, b) -> b
forall a b. (a -> b) -> a -> b
$ [(Char, b)] -> (Char, b)
forall a. [a] -> a
last (b -> Int -> [(Char, b)]
forall t. RandomGen t => t -> Int -> [(Char, t)]
rands b
gen Int
16)
#if !MIN_VERSION_base(4, 6, 0)
modifySTRef' :: STRef s a -> (a -> a) -> ST s ()
modifySTRef' ref f = do
x <- readSTRef ref
let x' = f x
x' `seq` writeSTRef ref x'
#endif