Copyright | (c) Promethea Raschke 2018 Max Amanshauser 2021 |
---|---|
License | MIT |
Maintainer | max@lambdalifting.org |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Password hashing and key derivation
When in doubt, just use one of [ interactivePolicy, moderatePolicy, sensitivePolicy ], but this module also allows you to fine-tune parameters for specific circumstances.
This module uses the Text
type for passwords, because this seems to be the only
reasonable way to get consistent encodings across locales and architectures, short of
letting users mess around with ByteStrings themselves.
Synopsis
- data Salt
- newSalt :: IO Salt
- needsRehash :: Opslimit -> Memlimit -> PasswordHash -> Maybe Bool
- pwhashStr :: Text -> Policy -> IO (Maybe PasswordHash)
- pwhashStrVerify :: PasswordHash -> Text -> Bool
- pwhash :: Text -> Int -> Salt -> Policy -> Maybe ByteString
- data Policy = Policy {}
- interactivePolicy :: Policy
- moderatePolicy :: Policy
- sensitivePolicy :: Policy
- data Opslimit
- opslimit :: Algorithm -> Int -> Maybe Opslimit
- getOpslimit :: Opslimit -> Int
- minOpslimit :: Algorithm -> Opslimit
- maxOpslimit :: Algorithm -> Opslimit
- opslimitInteractive :: Algorithm -> Opslimit
- opslimitModerate :: Algorithm -> Opslimit
- opslimitSensitive :: Algorithm -> Opslimit
- data Memlimit
- memlimit :: Algorithm -> Int -> Maybe Memlimit
- getMemlimit :: Memlimit -> Int
- minMemlimit :: Algorithm -> Memlimit
- maxMemlimit :: Algorithm -> Memlimit
- memlimitInteractive :: Algorithm -> Memlimit
- memlimitModerate :: Algorithm -> Memlimit
- memlimitSensitive :: Algorithm -> Memlimit
- data Algorithm
- defaultAlgorithm :: Algorithm
Documentation
Salt for deriving keys from passwords
Instances
Data Salt Source # | |
Defined in Crypto.Saltine.Internal.Password gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Salt -> c Salt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Salt # dataTypeOf :: Salt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Salt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Salt) # gmapT :: (forall b. Data b => b -> b) -> Salt -> Salt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Salt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Salt -> r # gmapQ :: (forall d. Data d => d -> u) -> Salt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Salt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Salt -> m Salt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Salt -> m Salt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Salt -> m Salt # | |
Generic Salt Source # | |
Show Salt Source # | |
NFData Salt Source # | |
Defined in Crypto.Saltine.Internal.Password | |
Eq Salt Source # | |
Ord Salt Source # | |
Hashable Salt Source # | |
Defined in Crypto.Saltine.Internal.Password | |
IsEncoding Salt Source # | |
Defined in Crypto.Saltine.Internal.Password encode :: Salt -> ByteString Source # decode :: ByteString -> Maybe Salt Source # encoded :: (Choice p, Applicative f) => p Salt (f Salt) -> p ByteString (f ByteString) Source # | |
type Rep Salt Source # | |
Defined in Crypto.Saltine.Internal.Password type Rep Salt = D1 ('MetaData "Salt" "Crypto.Saltine.Internal.Password" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "Salt" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSalt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
needsRehash :: Opslimit -> Memlimit -> PasswordHash -> Maybe Bool Source #
Indicates whether a password needs to be rehashed, because the opslimit/memlimit parameters used to hash the password are inconsistent with the supplied values. Returns Nothing if the hash appears to be invalid. Internally this function will always use the current DefaultAlgorithm and hence will give undefined results if a different algorithm was used to hash the password.
pwhashStr :: Text -> Policy -> IO (Maybe PasswordHash) Source #
Hashes a password according to the policy This function is non-deterministic and hence in IO. Since this function may cause a huge amount of memory to be allocated, it will return Nothing if the allocation failed and on any other error.
pwhashStrVerify :: PasswordHash -> Text -> Bool Source #
Verifies that a certain password hash was constructed from the supplied password
pwhash :: Text -> Int -> Salt -> Policy -> Maybe ByteString Source #
Derives a key of the specified length from a password using a salt according to the provided policy. Since this function may cause a huge amount of memory to be allocated, it will return Nothing if the allocation failed and on any other error.
Wrapper for opslimit, memlimit and algorithm
Instances
Data Policy Source # | |
Defined in Crypto.Saltine.Internal.Password gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Policy -> c Policy # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Policy # toConstr :: Policy -> Constr # dataTypeOf :: Policy -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Policy) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Policy) # gmapT :: (forall b. Data b => b -> b) -> Policy -> Policy # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Policy -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Policy -> r # gmapQ :: (forall d. Data d => d -> u) -> Policy -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Policy -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Policy -> m Policy # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Policy -> m Policy # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Policy -> m Policy # | |
Generic Policy Source # | |
Show Policy Source # | |
Eq Policy Source # | |
Ord Policy Source # | |
Hashable Policy Source # | |
Defined in Crypto.Saltine.Internal.Password | |
type Rep Policy Source # | |
Defined in Crypto.Saltine.Internal.Password type Rep Policy = D1 ('MetaData "Policy" "Crypto.Saltine.Internal.Password" "saltine-0.2.1.0-inplace" 'False) (C1 ('MetaCons "Policy" 'PrefixI 'True) (S1 ('MetaSel ('Just "opsPolicy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Opslimit) :*: (S1 ('MetaSel ('Just "memPolicy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Memlimit) :*: S1 ('MetaSel ('Just "algPolicy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Algorithm)))) |
moderatePolicy :: Policy Source #
Moderate policy with a balance of speed and security
Takes approximately 1 second on a typical desktop computer and requires 256 MiB of dedicated RAM
sensitivePolicy :: Policy Source #
High-security policy designed to make attacking the password extremely expensive
Takes several seconds on a typical desktop computer and requires 1024 MiB of dedicated RAM
Wrapper type for the operations used by password hashing
Instances
Data Opslimit Source # | |
Defined in Crypto.Saltine.Internal.Password gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Opslimit -> c Opslimit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Opslimit # toConstr :: Opslimit -> Constr # dataTypeOf :: Opslimit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Opslimit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Opslimit) # gmapT :: (forall b. Data b => b -> b) -> Opslimit -> Opslimit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Opslimit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Opslimit -> r # gmapQ :: (forall d. Data d => d -> u) -> Opslimit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Opslimit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Opslimit -> m Opslimit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Opslimit -> m Opslimit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Opslimit -> m Opslimit # | |
Generic Opslimit Source # | |
Show Opslimit Source # | |
NFData Opslimit Source # | |
Defined in Crypto.Saltine.Internal.Password | |
Eq Opslimit Source # | |
Ord Opslimit Source # | |
Defined in Crypto.Saltine.Internal.Password | |
Hashable Opslimit Source # | |
Defined in Crypto.Saltine.Internal.Password | |
type Rep Opslimit Source # | |
Defined in Crypto.Saltine.Internal.Password |
getOpslimit :: Opslimit -> Int Source #
minOpslimit :: Algorithm -> Opslimit Source #
maxOpslimit :: Algorithm -> Opslimit Source #
opslimitModerate :: Algorithm -> Opslimit Source #
Wrapper type for the memory used by password hashing
Instances
Data Memlimit Source # | |
Defined in Crypto.Saltine.Internal.Password gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Memlimit -> c Memlimit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Memlimit # toConstr :: Memlimit -> Constr # dataTypeOf :: Memlimit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Memlimit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Memlimit) # gmapT :: (forall b. Data b => b -> b) -> Memlimit -> Memlimit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Memlimit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Memlimit -> r # gmapQ :: (forall d. Data d => d -> u) -> Memlimit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Memlimit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Memlimit -> m Memlimit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Memlimit -> m Memlimit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Memlimit -> m Memlimit # | |
Generic Memlimit Source # | |
Show Memlimit Source # | |
NFData Memlimit Source # | |
Defined in Crypto.Saltine.Internal.Password | |
Eq Memlimit Source # | |
Ord Memlimit Source # | |
Defined in Crypto.Saltine.Internal.Password | |
Hashable Memlimit Source # | |
Defined in Crypto.Saltine.Internal.Password | |
type Rep Memlimit Source # | |
Defined in Crypto.Saltine.Internal.Password |
getMemlimit :: Memlimit -> Int Source #
minMemlimit :: Algorithm -> Memlimit Source #
maxMemlimit :: Algorithm -> Memlimit Source #
memlimitModerate :: Algorithm -> Memlimit Source #
Algorithms known to Libsodium, as an enum datatype