[Haskell-cafe] Password hashing
Bulat Ziganshin
bulat.ziganshin at gmail.com
Tue Nov 25 13:31:04 EST 2008
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?
> 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 at 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.ziganshin at gmail.com>:
>> 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
>>
>>
>> --
>> Best regards,
>> Bulat mailto:Bulat.Ziganshin at gmail.com
>>
>>
--
Best regards,
Bulat mailto:Bulat.Ziganshin at gmail.com
More information about the Haskell-Cafe
mailing list