----------------------------------------------------------------------------- -- | -- Module : Passman.Core.Hash -- Copyright : Matthew Harm Bekkema 2016 -- License : GPL-2 -- Maintainer : mbekkema97@gmail.com -- Stability : experimental -- Portability : POSIX ----------------------------------------------------------------------------- module Passman.Core.Hash ( -- * Password Generation generatePassword -- * Master Password , MasterPassword , masterPassword , fromMasterPassword -- ** Hashing , hashMasterPassword , checkMasterPassword ) where import Prelude hiding (foldr) import Passman.Core.PassList(PassListEntry(..)) import Passman.Core.Internal.Util (toBase, bytesToInt, bsPack, bsUnpack) import Passman.Core.Mode (modeToConstraint) import Passman.Core.Internal.Compat (Natural) import Passman.Core.Internal.BFEncoding as BFE import qualified Crypto.BCrypt as BCrypt import qualified Crypto.Hash.MD5 as MD5 import qualified Data.ByteString as BS import Data.ByteString (ByteString) import Data.Foldable (foldr) import Data.Maybe (fromJust) import Control.Applicative ((<$>)) import Control.Monad (mfilter) -- | Represents valid master passwords. newtype MasterPassword = MP ByteString -- | Turn a master password back into a string. fromMasterPassword :: MasterPassword -> String fromMasterPassword (MP bs) = bsUnpack bs -- | Turn a string into a master password. `Nothing` if it contains invalid -- bytes or is too long masterPassword :: String -> Maybe MasterPassword masterPassword s = let bs = bsPack s in if (BS.length bs > 72) || BS.elem 0 bs then Nothing else Just $ MP bs shorten :: Maybe Int -> String -> String shorten = flip $ foldr take -- | Deterministically generates a password. generatePassword :: PassListEntry -> MasterPassword -- ^ The master password -> String -- ^ The generated password generatePassword (PassListEntry i l m) (MP p) = shorten l $ customDigest (modeToConstraint m) h where h :: ByteString h = BFE.decode $ BS.drop 29 $ fromJust ( BCrypt.hashPassword p salt ) Just salt = BCrypt.genSalt (bsPack "$2y$") 12 $ MD5.hash $ bsPack i -- | Generates a hash of the master password to be stored in the config. hashMasterPassword :: MasterPassword -- ^ Master password -> IO String -- ^ Hash hashMasterPassword (MP p) = do Just salt <- BCrypt.genSaltUsingPolicy BCrypt.slowerBcryptHashingPolicy {BCrypt.preferredHashCost = 12} let Just hash = BCrypt.hashPassword p salt return $ bsUnpack hash -- | Tests if the master password is correct against a hash produced by -- `hashMasterPassword`. -- -- >>> hash <- hashMasterPassword pass -- >>> checkMasterPassword hash pass -- True checkMasterPassword :: String -- ^ Hash -> MasterPassword -- ^ Master password -> Bool checkMasterPassword hash (MP pass) = BCrypt.validatePassword (bsPack hash) pass customDigest :: String -> ByteString -> String customDigest charSet cs = (!!) charSet <$> is where is :: [Int] is = map fromIntegral $ toBase l (bytesToInt cs) l :: Natural l = fromIntegral $ length charSet