
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/PBKDF2
Since no one took up my code review request I just did the best I
could and uploaded to hackage. There were indeed some mistakes in my
initial post, fixed now. (Code review is still wished, though!)
Alas, documentation doesn't build with hackage, altough it does for me
locally. (Seems like almost everything I do these days -- what am I
doing wrong?!)
Also I'm open to folding this into a more established crypto package
if there are any takers... psst, dominic.
Also, dominic, shouldn't your crypto package be added to category
Cryptography (a cabal file change) so it lists aside the other crypto
packages?
thanks, thomas.
2008/11/26 Thomas Hartman
Sorry about the hideous formatting above. Reattached as a text file.
t.
2008/11/26 Thomas Hartman
: OK, I went ahead and implemented pbkdf2, following the algorithm linked to by bulat and Michael.
If there are any crypto gurus who can code-review this I would be much obliged, and when I'm confident enough that this does the right thing I'll put it up on hackage.
I don't do much crypto so this *definitely* needs a review before it becomes a library?
How's this looks, cafe?
Thanks!
Thomas.
{-# LANGUAGE ScopedTypeVariables #-} module Crypto.PBKDF2 (pbkdf2, pbkdf2') where
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Lazy as L import GHC.Word import Control.Monad (foldM) import Random import Data.Digest.SHA512 (hash) import Data.Word import Data.Bits import Data.Binary
newtype Password = Password [Word8] newtype Salt = Salt [Word8] newtype HashedPass = HashedPass [Word8] deriving Show {- | A reasonable default for rsa pbkdf2? Actually I'm not really sure, ask folk with more experience.
pbkdf2 = pbkdf2' prfSHA512 512 512 512 -} t = pbkdf2 ( Password . toWord8s $ "meh" ) ( Salt . toWord8s $ "moo" ) pbkdf2 :: Password -> Salt -> HashedPass pbkdf2 = pbkdf2' prfSHA512 512 512 512
{- | Password Based Key Derivation Function, from RSA labs.
pbkdf2' prf hlen cIters dklen (Password pass) (Salt salt) -} pbkdf2' :: ([Word8] -> [Word8] -> [Word8]) -> Integer -> Integer -> Integer -> Password -> Salt -> HashedPass pbkdf2' prf hlen cIters dklen (Password pass) (Salt salt) | dklen > ( (2^32-1) * hlen) = error $ "pbkdf2, (dklen,hlen) : " ++ (show (dklen,hlen)) | otherwise = let --l,r :: Int l = ceiling $ (fromIntegral dklen) / (fromIntegral hlen ) r = dklen - ( (l-1) * hlen) ustream :: [Word8] -> [Word8] -> [[Word8]] ustream p s = let x = prf p s in x : ustream p x --us :: Integer -> [[Word8]] us i = take (fromIntegral cIters) $ ustream pass ( salt `myor` ((intToFourWord8s i) )) --f :: [Word8] -> [Word8] -> Integer -> Integer -> [Word8] f pass salt cIters i = foldr1 myxor $ us i ts :: [[Word8]] ts = map (f pass salt cIters) ( [1..l] ) in HashedPass . take (fromIntegral dklen) . concat $ ts
-- The spec says -- Here, INT (i) is a four-octet encoding of the integer i, most significant octet first. -- I'm reading from the right... is this the right thing? toWord8s x = L.unpack . encode $ x
--intToFourWord8s :: Integer -> [Word8] intToFourWord8s i = let w8s = toWord8s $ i in drop (length w8s -4) w8s
myxor :: [Word8] -> [Word8] -> [Word8] myxor = zipWith xor
myor :: [Word8] -> [Word8] -> [Word8] myor = zipWith (.|.)
prfSHA512 :: [Word8] -> [Word8] -> [Word8] prfSHA512 x y = hash $ x ++ y
2008/11/26 John Meacham
: What you are using there is not a salt, but rather a secret key. The important thing about a salt is that it is different for _every user_. and you actually store the salt unhashed along with the hash. (it is not secret information). A salt protects against a dictionary attack, for instance, you might have a dictionary of hash's and the common passwords they go to but if you add a 32 bit salt, you would need 2^32 entries for each dictionary word, making such an attack unworkable. You can also trivially tell if two users have the _same_ password just by comparing the hashes without a salt.
John
-- John Meacham - ⑆repetae.net⑆john⑈ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe