saltine-0.2.1.0: Cryptography that's easy to digest (NaCl/libsodium bindings).
Copyright(c) Promethea Raschke 2018
Max Amanshauser 2021
LicenseMIT
Maintainermax@lambdalifting.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.Saltine.Core.Password

Description

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

Documentation

data Salt Source #

Salt for deriving keys from passwords

Instances

Instances details
Data Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

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 #

toConstr :: Salt -> Constr #

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 # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Associated Types

type Rep Salt :: Type -> Type #

Methods

from :: Salt -> Rep Salt x #

to :: Rep Salt x -> Salt #

Show Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

showsPrec :: Int -> Salt -> ShowS #

show :: Salt -> String #

showList :: [Salt] -> ShowS #

NFData Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

rnf :: Salt -> () #

Eq Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

(==) :: Salt -> Salt -> Bool #

(/=) :: Salt -> Salt -> Bool #

Ord Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

compare :: Salt -> Salt -> Ordering #

(<) :: Salt -> Salt -> Bool #

(<=) :: Salt -> Salt -> Bool #

(>) :: Salt -> Salt -> Bool #

(>=) :: Salt -> Salt -> Bool #

max :: Salt -> Salt -> Salt #

min :: Salt -> Salt -> Salt #

Hashable Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

hashWithSalt :: Int -> Salt -> Int #

hash :: Salt -> Int #

IsEncoding Salt Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

type Rep Salt Source # 
Instance details

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.

data Policy Source #

Wrapper for opslimit, memlimit and algorithm

Instances

Instances details
Data Policy Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

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 # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Associated Types

type Rep Policy :: Type -> Type #

Methods

from :: Policy -> Rep Policy x #

to :: Rep Policy x -> Policy #

Show Policy Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Eq Policy Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

(==) :: Policy -> Policy -> Bool #

(/=) :: Policy -> Policy -> Bool #

Ord Policy Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Hashable Policy Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

hashWithSalt :: Int -> Policy -> Int #

hash :: Policy -> Int #

type Rep Policy Source # 
Instance details

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

data Opslimit Source #

Wrapper type for the operations used by password hashing

Instances

Instances details
Data Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

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 # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Associated Types

type Rep Opslimit :: Type -> Type #

Methods

from :: Opslimit -> Rep Opslimit x #

to :: Rep Opslimit x -> Opslimit #

Show Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

NFData Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

rnf :: Opslimit -> () #

Eq Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Ord Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Hashable Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

hashWithSalt :: Int -> Opslimit -> Int #

hash :: Opslimit -> Int #

type Rep Opslimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

type Rep Opslimit = D1 ('MetaData "Opslimit" "Crypto.Saltine.Internal.Password" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "Opslimit" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOpslimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

opslimit :: Algorithm -> Int -> Maybe Opslimit Source #

Smart constructor for opslimit

data Memlimit Source #

Wrapper type for the memory used by password hashing

Instances

Instances details
Data Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

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 # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Associated Types

type Rep Memlimit :: Type -> Type #

Methods

from :: Memlimit -> Rep Memlimit x #

to :: Rep Memlimit x -> Memlimit #

Show Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

NFData Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

rnf :: Memlimit -> () #

Eq Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Ord Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Hashable Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

hashWithSalt :: Int -> Memlimit -> Int #

hash :: Memlimit -> Int #

type Rep Memlimit Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

type Rep Memlimit = D1 ('MetaData "Memlimit" "Crypto.Saltine.Internal.Password" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "Memlimit" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMemlimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

memlimit :: Algorithm -> Int -> Maybe Memlimit Source #

Smart constructor for memlimit

data Algorithm Source #

Algorithms known to Libsodium, as an enum datatype

Instances

Instances details
Data Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Algorithm -> c Algorithm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Algorithm #

toConstr :: Algorithm -> Constr #

dataTypeOf :: Algorithm -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Algorithm) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Algorithm) #

gmapT :: (forall b. Data b => b -> b) -> Algorithm -> Algorithm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Algorithm -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Algorithm -> r #

gmapQ :: (forall d. Data d => d -> u) -> Algorithm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Algorithm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Algorithm -> m Algorithm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Algorithm -> m Algorithm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Algorithm -> m Algorithm #

Bounded Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Enum Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Generic Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Associated Types

type Rep Algorithm :: Type -> Type #

Show Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Eq Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Ord Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Hashable Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

type Rep Algorithm Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

type Rep Algorithm = D1 ('MetaData "Algorithm" "Crypto.Saltine.Internal.Password" "saltine-0.2.1.0-inplace" 'False) (C1 ('MetaCons "DefaultAlgorithm" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Argon2i13" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Argon2id13" 'PrefixI 'False) (U1 :: Type -> Type)))