Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

[Haskell-cafe] Password hashing

174 views
Skip to first unread message

Bit Connor

unread,
Oct 28, 2008, 11:43:17 AM10/28/08
to haskel...@haskell.org
Hello,

What library can be used to securely hash passwords? From what I
understand, the "bcrypt" algorithm is what the experts recommend. It
is described in the paper:

http://www.openbsd.org/papers/bcrypt-paper.ps

I couldn't find a haskell library for this.

There is a BSD licensed C implementation that looks very simple here:

http://www.mindrot.org/projects/py-bcrypt/

A translation to haskell should be straight forward.
Alternatively, a haskell bcrypt library could directly use this
implementation and provide a very light FFI wrapper.

Any thoughts?
_______________________________________________
Haskell-Cafe mailing list
Haskel...@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Bulat Ziganshin

unread,
Oct 28, 2008, 11:50:33 AM10/28/08
to Bit Connor, haskel...@haskell.org
Hello Bit,

Tuesday, October 28, 2008, 6:42:34 PM, you wrote:

> What library can be used to securely hash passwords? From what I

any secure hash, say SHA512


--
Best regards,
Bulat mailto:Bulat.Z...@gmail.com

Michał Pałka

unread,
Oct 28, 2008, 11:57:04 AM10/28/08
to Bit Connor, Bulat Ziganshin, haskel...@haskell.org
On Tue, 2008-10-28 at 18:49 +0300, Bulat Ziganshin wrote:
> Tuesday, October 28, 2008, 6:42:34 PM, you wrote:
>
> > What library can be used to securely hash passwords? From what I
>
> any secure hash, say SHA512

It's a good idea to salt your passwords before hashing, though. See
http://en.wikipedia.org/wiki/Salt_(cryptography)

Best,
Michał

Krzysztof Skrzętnicki

unread,
Oct 28, 2008, 11:57:55 AM10/28/08
to Bit Connor, haskel...@haskell.org
On Tue, Oct 28, 2008 at 16:42, Bit Connor <b...@mutantlemon.com> wrote:
> Hello,
>
> What library can be used to securely hash passwords? From what I
> understand, the "bcrypt" algorithm is what the experts recommend. It
> is described in the paper:
>
> http://www.openbsd.org/papers/bcrypt-paper.ps
>
> I couldn't find a haskell library for this.
>
> There is a BSD licensed C implementation that looks very simple here:
>
> http://www.mindrot.org/projects/py-bcrypt/
>
> A translation to haskell should be straight forward.
> Alternatively, a haskell bcrypt library could directly use this
> implementation and provide a very light FFI wrapper.
>
> Any thoughts?

Direct Haskell implementation has significant advantage of being more
portable: from my experience building C libraries on Windows is much
more complicated and quite often fails in default setting [1]. Fixing
it may require some non-trivial (and time consuming) hacking. On the
other hand reusing existing implementation is likely to be faster from
developers view: just write a bunch of FFI imports and you are done.
It may also benefit from C's high speed.

All best

Christopher Skrzętnicki

[1] All regex-*, OpenGL and bunch of others

Don Stewart

unread,
Oct 28, 2008, 1:21:19 PM10/28/08
to Bulat Ziganshin, haskel...@haskell.org
bulat.ziganshin:

> Hello Bit,
>
> Tuesday, October 28, 2008, 6:42:34 PM, you wrote:
>
> > What library can be used to securely hash passwords? From what I
>
> any secure hash, say SHA512

And there are multiple bindings and implementations of SHA on
hackage.haskell.org.

nano-hmac provides a binding to openssl's version, while 'crypto' has a
pure haskell version.

Bit Connor

unread,
Oct 29, 2008, 9:33:16 AM10/29/08
to Michał Pałka, Bulat Ziganshin, haskel...@haskell.org
On Tue, Oct 28, 2008 at 5:56 PM, Michał Pałka <michal...@poczta.fm> wrote:
> It's a good idea to salt your passwords before hashing, though. See
> http://en.wikipedia.org/wiki/Salt_(cryptography)

What can be used for generating a random salt? Is System.Random secure enough?

Thanks

Bulat Ziganshin

unread,
Oct 29, 2008, 9:48:34 AM10/29/08
to Bit Connor, haskel...@haskell.org, Bulat Ziganshin
Hello Bit,

Wednesday, October 29, 2008, 4:32:51 PM, you wrote:

>> It's a good idea to salt your passwords before hashing, though. See

> What can be used for generating a random salt? Is System.Random secure enough?

if you use mkStdRNG it's good enough for non high-secure programs. it
inits rnd generator with current time upo to picoseconds (if your OS
provides such granularity). you can add a bit f security by reading a
few bytes from /dev/urandom and passing these to mkStdRNG

--
Best regards,
Bulat mailto:Bulat.Z...@gmail.com

_______________________________________________

Achim Schneider

unread,
Oct 29, 2008, 1:44:14 PM10/29/08
to haskel...@haskell.org
Bulat Ziganshin <bulat.z...@gmail.com> wrote:

> Hello Bit,
>
> Wednesday, October 29, 2008, 4:32:51 PM, you wrote:
>
> >> It's a good idea to salt your passwords before hashing, though. See
> > What can be used for generating a random salt? Is System.Random
> > secure enough?
>
> if you use mkStdRNG it's good enough for non high-secure programs. it
> inits rnd generator with current time upo to picoseconds (if your OS
> provides such granularity). you can add a bit f security by reading a
> few bytes from /dev/urandom and passing these to mkStdRNG
>

..or by pinging a random host and taking the time difference, checking
the current cpu temperature and fan speed, counting how many times
your process gets suspended in a certain amount of time, taking a
picture of a lava lamp and hashing it, booting windows, not doing
anything, and measure the time it takes to crash, hashing a snapshot
of the slashdot frontpage, and, last, but not least, measuring the
amount of spam per second currently swooshing into your mail account.

--
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.

Don Stewart

unread,
Oct 29, 2008, 7:14:18 PM10/29/08
to Andrew Butterfield, haskel...@haskell.org
Andrew.Butterfield:
>
> >someone asked:

> >>>What can be used for generating a random salt? Is System.Random
> >>>secure enough?
> >>>
> Achim Schneider wrote:
> >...or by pinging a random host and taking the time difference, checking

> >the current cpu temperature and fan speed, counting how many times
> >your process gets suspended in a certain amount of time, taking a
> >picture of a lava lamp and hashing it, booting windows, not doing
> >anything, and measure the time it takes to crash, hashing a snapshot
> >of the slashdot frontpage, and, last, but not least, measuring the
> >amount of spam per second currently swooshing into your mail account.
> >
> >
>
> or http://www.random.org/ perhaps ?

Via,
System.Random.Atmosphere

http://hackage.haskell.org/packages/archive/RandomDotOrg/0.2.1/doc/html/System-Random-Atmosphere.html

Thomas Schilling

unread,
Oct 29, 2008, 8:28:06 PM10/29/08
to Bulat Ziganshin, haskel...@haskell.org
In general, it is recommended that password hash functions are
comparatively *slow* in order to make offline attacks harder. You can
somewhat emulate this by running the hashing function multiple times.
And, of course, salting should always be done.

2008/10/28 Bulat Ziganshin <bulat.z...@gmail.com>:

brian

unread,
Oct 29, 2008, 8:33:17 PM10/29/08
to haskel...@haskell.org
Please be careful not to invent or reinvent a password hashing scheme.
I'd go with bcrypt. That'd be a worthy module.

roger peppe

unread,
Oct 30, 2008, 4:49:27 AM10/30/08
to haskel...@haskell.org
if you're prepared to expend a few cpu cycles, you can always
use something like the following "beating clocks" algorithm, which
should generate
at least some genuine randomness, as long as you've got preemptive
scheduling, and a few hardware interrupts around the place.

>module Clockbeat where
>import Control.Concurrent
>import Control.Monad
>import Data.IORef
>
>random :: IO Int
>random = do
> m <- newEmptyMVar
> v <- newIORef (0 :: Int)
>
> fast <- forkIO $ forever $ do
> v' <- readIORef v
> let v'' = v' + 1 in
> v'' `seq` writeIORef v v''
> slow <- forkIO $ forever $
> do
> threadDelay 500000
> val <- readIORef v
> putMVar m (val `mod` 2)
> r <- replicateM 31 $ takeMVar m
> killThread fast
> killThread slow
> return $ sum $ zipWith (*) (map (2 ^) [0..]) r

Thomas Hartman

unread,
Oct 30, 2008, 8:33:08 AM10/30/08
to haskell-cafe
In my happs-tutorial application I do the following to keep passwords.

No salt, but apart from that, should be fine, right?

thomas.

**********

import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as L

-- store passwords as md5 hash, as a security measure
scramblepass :: B.ByteString -> B.ByteString
scramblepass = B.pack . show . md5 . L.pack . B.unpack

2008/10/30 roger peppe <rogp...@gmail.com>:

Martijn van Steenbergen

unread,
Oct 30, 2008, 8:44:04 AM10/30/08
to roger peppe, haskel...@haskell.org
roger peppe wrote:
> if you're prepared to expend a few cpu cycles, you can always
> use something like the following "beating clocks" algorithm, which
> should generate
> at least some genuine randomness, as long as you've got preemptive
> scheduling, and a few hardware interrupts around the place.

I was taught that using the scheduler to generate randomness is a pretty
bad idea, because randomness is actually a *very* strong property to
demand from a stream of bits, and a scheduler doesn't offer any such
guarantees.

Martijn.

roger peppe

unread,
Oct 30, 2008, 9:13:05 AM10/30/08
to haskel...@haskell.org
i'd be interested to know if you know of any studies on this.

i know of at least one system that uses it as the basis for
its crypto. superficially it's certainly an attractive method, with minimal
external dependencies, and, i'd have thought, at least a useful
addition to just using the system time.

obviously, an actual implementation would mix in the
full value of the counter, to take advantage of as much
randomness as possible.

in practice, the results don't seem too bad, but as with any
randomness, it's difficult to be really sure...

rog.

Achim Schneider

unread,
Oct 30, 2008, 9:14:31 AM10/30/08
to haskel...@haskell.org
Martijn van Steenbergen <mar...@van.steenbergen.nl> wrote:

> roger peppe wrote:
> > if you're prepared to expend a few cpu cycles, you can always
> > use something like the following "beating clocks" algorithm, which
> > should generate
> > at least some genuine randomness, as long as you've got preemptive
> > scheduling, and a few hardware interrupts around the place.
>
> I was taught that using the scheduler to generate randomness is a
> pretty bad idea, because randomness is actually a *very* strong
> property to demand from a stream of bits, and a scheduler doesn't
> offer any such guarantees.
>

The scheduler is as fine a chaotic system as your average cube
centimetre of air: Very, very little disturbances (like a keypress or a
network packet) can change the order of task switching drastically,
even more so if stuff runs with different priorities.

What it certainly (hopefully) won't guarantee is a random distribution
over a wide range, but what it will have is an infinite period as it's
based on external events. You can fix the distribution problem with a
secure hash of your choice.

--
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.

_______________________________________________

Bulat Ziganshin

unread,
Oct 30, 2008, 10:26:19 AM10/30/08
to Thomas Hartman, haskell-cafe
Hello Thomas,

Thursday, October 30, 2008, 3:32:46 PM, you wrote:

> No salt, but apart from that, should be fine, right?

1) without salt, it's not serious - easily breaked by dictionary
attack

2) afair, md5 isn't condidered now as cryptographic hash

--
Best regards,
Bulat mailto:Bulat.Z...@gmail.com

_______________________________________________

Daniel B. Giffin

unread,
Oct 30, 2008, 3:31:19 PM10/30/08
to Thomas Hartman, haskell-cafe
to expand on this:

Bulat Ziganshin wrote:
> 1) without salt, it's not serious - easily breaked by dictionary
> attack

and this:

Thomas Schilling wrote:
> In general, it is recommended that password hash functions are
> comparatively *slow* in order to make offline attacks harder. You can
> somewhat emulate this by running the hashing function multiple times.
> And, of course, salting should always be done.

(and leaving aside vulnerabilities in MD5 itself ...)

without a salt, the concern is that someone has a list of the
MD5-hashes of a few million likely passwords (such things are
available on the internet, and also straightforward to compute
yourself). an attacker in possession of your hashed-passwords file
may then look up each hash in his list; if one matches, he knows the
plaintext password. if everyone used this simple scheme, the same
dictionary (mapping hashes back to plaintext) could be leveraged to
attack anyone's password file.

if you append some random salt material to every password before
hashing it, an attacker will in essense need a separate dictionary for
every salt value. in practice (because there are too many such
dictionaries to bother pre-computing them), to attack a particular
salted-and-hashed password, he will just start hashing all his
favorite passwords along with the associated salt until he gets lucky
and one matches. (or perhaps he will do this in parallel over the
whole file, not caring which account is broken.)

in order to make this take as long as possible, you want the hashing
function to be slow to compute. if it takes you a second or two to
compute the hash when somebody logs in, fine -- this means the bad guy
will have to spend over a week trying a million passwords against one
of your accounts (unless he has a faster algorithm or better hardware
than you).

the nice thing about bcrypt, then, is that it has configurable cost.
you pick whatever cost you can tolerate now, and then as new passwords
are hashed over the years you can keep increasing the cost in order to
keep up with the faster hardware that is available (to you and to
attackers). (storing the cost along with each hash allows a single
password file with heterogenous hash-costs.)

i might try my hand at a haskell-native module if i find the time, but
for now using FFI to access bcrypt (or just forking a child process to
compute it) is probably the safest bet.

A Future-Adaptable Password Scheme
http://www.usenix.org/events/usenix99/provos.html

(hm, bcrypt implementations appear to be hard to find outside of
OpenBSD, and also there is the confusing existence of a "bcrypt"
utility that just does normal blowfish encryption. anybody know of a
packaged linux library or utility that does the eksblowfish hash?)

Brandon S. Allbery KF8NH

unread,
Oct 30, 2008, 9:43:22 PM10/30/08
to Martijn van Steenbergen, haskel...@haskell.org
On 2008 Oct 30, at 8:43, Martijn van Steenbergen wrote:
> roger peppe wrote:
>> if you're prepared to expend a few cpu cycles, you can always
>> use something like the following "beating clocks" algorithm, which
>> should generate
>> at least some genuine randomness, as long as you've got preemptive
>> scheduling, and a few hardware interrupts around the place.
>
> I was taught that using the scheduler to generate randomness is a
> pretty bad idea, because randomness is actually a *very* strong
> property to demand from a stream of bits, and a scheduler doesn't
> offer any such guarantees.


There's quite a body of research about cracking such schemes; note for
example that "hyperthreading" quietly dropped off the radar after
someone demonstrated they could snoop on any crypto algorithm running
in one hyperthread from the other.

In general, if you think you've come up with a good randomness or
encryption scheme on your own, back away from the keyboard and don't
come back until you're ready to use an existing well-understood scheme
--- even the experts make mistakes in this area, and most "neat" new
ideas" turn out to be trivially unraveled.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] all...@kf8nh.com
system administrator [openafs,heimdal,too many hats] all...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH

unread,
Oct 30, 2008, 9:47:29 PM10/30/08
to roger peppe, haskel...@haskell.org
On 2008 Oct 30, at 9:12, roger peppe wrote:
> i'd be interested to know if you know of any studies on this.
>
> i know of at least one system that uses it as the basis for
> its crypto. superficially it's certainly an attractive method, with
> minimal
> external dependencies, and, i'd have thought, at least a useful
> addition to just using the system time.

It turns out to be trivial to game randomness generated from scheduler
activations: just launch enough other CPU-using processes to max out
the scheduler and the search space gets *very* small.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] all...@kf8nh.com
system administrator [openafs,heimdal,too many hats] all...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university KF8NH

Thomas Hartman

unread,
Nov 25, 2008, 10:38:48 AM11/25/08
to Bulat Ziganshin, haskell-cafe, HAppS
What does haskell cafe think of the following module for drop-in
password hasing for webapps? Seem reasonable?

import Data.Digest.SHA512 (hash)
import qualified Data.ByteString as B'


import qualified Data.ByteString.Char8 as B

-- store passwords as md5 hash, as a security measure
scramblepass :: String -> IO String
scramblepass p = do
etSalt <- try $ readFile "secure/salt"
case etSalt of
Left e -> fail errmsg
Right s -> -- return . show . md5 . L.pack $ p ++ s
return . B.unpack . B'.pack . hash . B'.unpack . B.pack $ p ++ s
where errmsg = "scramblepass error, you probably need to create a
salt file in secure/salt. This is used for \
\hashing passwords, so keep it secure. chmod u=r
secure/salt, and make sure it's skipped \
\in version control commits, etc. A good way to generate a
salt file is (e.g., on ubuntu) \
\writeFile \"secure/salt\" =<< ( strongsalt $ readFile
\"/dev/urandom\")\
\You could also just type some random seeming text into
this file, though that's not quite as secure.\
\Keep a backup copy of this file somewhere safe in case of
disaster."


-- | eg, on ubuntu: strongsalt $ readFile "/dev/urandom"
strongsalt :: IO String -> IO String
strongsalt randomSource = return . salt' =<< randomSource
where salt' = show . fst . next . mkStdGen . read . concat . map
(show . ord) . take 10

2008/10/30 Bulat Ziganshin <bulat.z...@gmail.com>:

Thomas Hartman

unread,
Nov 25, 2008, 10:39:45 AM11/25/08
to Bulat Ziganshin, haskell-cafe, HAppS
Just to note, the comment about md5 is incorrect. I switched to SHA512
as you can see in the code.

2008/11/25 Thomas Hartman <tphy...@gmail.com>:

Bulat Ziganshin

unread,
Nov 25, 2008, 10:51:38 AM11/25/08
to Thomas Hartman, HAppS, Bulat Ziganshin, haskell-cafe
Hello Thomas,

Tuesday, November 25, 2008, 6:39:27 PM, you wrote:

> Just to note, the comment about md5 is incorrect. I switched to SHA512
> as you can see in the code.

really? :)

>> Right s -> -- return . show . md5 . L.pack $ p ++ s

typical salt usage is generation of new salt for every encryption
operation and storing together with encrypted data

Jake McArthur

unread,
Nov 25, 2008, 11:12:39 AM11/25/08
to Bulat Ziganshin, haskell-cafe, HAppS
Bulat Ziganshin wrote:
>> Just to note, the comment about md5 is incorrect. I switched to SHA512
>> as you can see in the code.
>
> really? :)
>
>>> Right s -> -- return . show . md5 . L.pack $ p ++ s

Yes, really. If you look carefully, it is commented out. ;)

- Jake

signature.asc

Thomas Hartman

unread,
Nov 25, 2008, 11:38:39 AM11/25/08
to Bulat Ziganshin, HAppS, haskell-cafe
ah thanks, I'll try again.

> typical salt usage is generation of new salt for every encryption
>operation and storing together with encrypted data

2008/11/25 Bulat Ziganshin <bulat.z...@gmail.com>:

Thomas Hartman

unread,
Nov 25, 2008, 1:14:13 PM11/25/08
to Bulat Ziganshin, HAppS, haskell-cafe
How about the following?

The main doubts I'm having at this point concern the takerandom part.
Does this seem reasonable?

Also, someone in the thread mentioned that a calculation that took a
couple of seconds to complete was a good thing because it makes
dictionary cracking harder. But

makeSaltedPasswordLinux "meh"

is virtually instantaneous, so I guess I'm doing something wrong?

Thanks for advice!

thomas.

thartman@thartman-laptop:~/hackage/HAppSHelpers>cat HAppS/Helpers/Security.hs

-- | Password hashes are based on a salt from a source of randomness
(eg /dev/urandom), and
-- | the SHA512 hashing function
module HAppS.Helpers.Security (
makeSaltedPassword, makeSaltedPasswordLinux, checkpass
)

where

import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString as B'

import Control.Monad.Error
import System.IO.Error
import Random
import Data.Digest.SHA512 (hash)
import Data.Char

data SaltedPassword = SaltedPassword HashedPass Salt
deriving Show

newtype Password = Password String
deriving Show
newtype Salt = Salt String
deriving Show
newtype HashedPass = HashedPass String
deriving (Eq, Show)
checkpass :: Password -> SaltedPassword -> Bool
checkpass passattempt ( SaltedPassword hashedPass salt ) =
let hashedPassAttempt = hashpass passattempt salt
in hashedPassAttempt == hashedPass

hashpass :: Password -> Salt -> HashedPass
hashpass (Password p) (Salt s) = HashedPass . B.unpack . B'.pack .


hash . B'.unpack . B.pack $ p ++ s

-- | This works at least on ubuntu hardy heron, I don't know how portable it is
-- > makeSaltedPasswordLinux p = getSaltedPassword $ readFile "/dev/urandom")
makeSaltedPasswordLinux :: Password -> IO SaltedPassword
makeSaltedPasswordLinux = makeSaltedPassword $ readFile "/dev/urandom"

makeSaltedPassword :: IO String -> Password -> IO SaltedPassword
makeSaltedPassword randomsource pass = do
etR <- try $ return . takerandom =<< randomsource
case etR of
Left e -> fail . show $ e
Right s -> do let salt = Salt s
hp = hashpass pass salt
return $ SaltedPassword hp salt

takerandom :: String -> String
takerandom = show . fst . next . mkStdGen . read . concat . map (show
ord) . take 1000

2008/11/25 Bulat Ziganshin <bulat.z...@gmail.com>:

Michael Giagnocavo

unread,
Nov 25, 2008, 1:26:54 PM11/25/08
to Thomas Hartman, Bulat Ziganshin, haskell-cafe, HAppS
Some password hashing schemes will also perform a number of iterations to increase the attack time needed. (For instance, hashing 1024 times would increase the strength of the password against brute force by 10 bits.) Usually the iterations are stored unencrypted with the hash and salt so that the iterations can be changed as app needs do.

There's even an RFC on the subject:
http://www.ietf.org/rfc/rfc2898.txt (PBKDF2 is the function)

-Michael

_______________________________________________

Bulat Ziganshin

unread,
Nov 25, 2008, 1:31:41 PM11/25/08
to Thomas Hartman, HAppS, Bulat Ziganshin, haskell-cafe
Hello Thomas,

Tuesday, November 25, 2008, 9:13:53 PM, you wrote:

don't reinvent the wheel, use PBKDF2 from PKCS #5
http://www.truecrypt.org/docs/pkcs5v2-0.pdf

> How about the following?

> makeSaltedPasswordLinux "meh"

> Thanks for advice!

> thomas.

> thartman@thartman-laptop:~/hackage/HAppSHelpers>cat HAppS/Helpers/Security.hs

> where

> . ord) . take 1000

John Meacham

unread,
Nov 25, 2008, 8:08:21 PM11/25/08
to haskel...@haskell.org
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⑈

Thomas Hartman

unread,
Nov 25, 2008, 8:37:33 PM11/25/08
to haskel...@haskell.org
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 <jo...@repetae.net>:

Thomas Hartman

unread,
Nov 25, 2008, 8:39:26 PM11/25/08
to haskel...@haskell.org
Sorry about the hideous formatting above. Reattached as a text file.

t.

2008/11/26 Thomas Hartman <tphy...@gmail.com>:

PBKDF2.hs
0 new messages