module Data.Digest.BCrypt
( bcrypt
, genSalt
, BSalt
, unBSalt
)
where
import Foreign
import Foreign.C.Types
import Foreign.C.String
import qualified System.IO.Unsafe ( unsafePerformIO )
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Internal as B ( fromForeignPtr
, c_strlen
)
import qualified Data.ByteString as B
newtype BSalt = BSalt {
unBSalt::B.ByteString
} deriving (Eq, Ord, Show)
genSalt :: Monad m =>
Integer
-> B.ByteString
-> m BSalt
genSalt cost seed
| B.length seed /= 16 = fail "Bad seed size"
| otherwise = return $ unsafePerformIO $
B.useAsCString seed $ \s ->
allocaBytes 30 $ \out -> do
let seed' = (fromIntegral cost::CInt)
bsalt <- c_bcrypt_gensalt out seed' (castPtr s)
result <- B.packCString bsalt
return $ BSalt result
bcrypt :: B.ByteString
-> BSalt
-> B.ByteString
bcrypt key (BSalt salt) = unsafePerformIO $
B.useAsCString key $ \k -> B.useAsCString salt $ \s ->
allocaBytes 128 $ \out ->
B.packCString =<< c_bcrypt out k s
foreign import ccall unsafe "bcrypt.h bcrypt_gensalt"
c_bcrypt_gensalt :: CString -> CInt -> Ptr Word8 -> IO CString
foreign import ccall unsafe "bcrypt.h bcrypt"
c_bcrypt :: CString -> CString -> CString -> IO CString