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 HaskellNone
LanguageHaskell2010

Crypto.Saltine.Internal.Password

Description

 
Synopsis

Documentation

c_pwhash Source #

Arguments

:: Ptr CChar

Derived key output buffer

-> CULLong

Derived key length

-> Ptr CChar

Password input buffer

-> CULLong

Password length

-> Ptr CChar

Salt input buffer

-> CULLong

Operation limit

-> CSize

Memory usage limit

-> CInt

Algorithm

-> IO CInt 

c_pwhash_str Source #

Arguments

:: Ptr CChar

Hashed password output buffer

-> Ptr CChar

Password input buffer

-> CULLong

Password length

-> CULLong

Operation limit

-> CSize

Memory usage limit

-> IO CInt 

c_pwhash_str_verify Source #

Arguments

:: Ptr CChar

Hashed password input buffer

-> Ptr CChar

Password input buffer

-> CULLong

Password length

-> IO CInt 

c_pwhash_str_needs_rehash Source #

Arguments

:: Ptr CChar

Hashed password input buffer

-> CULLong

Operation limit

-> CSize

Memory usage limit

-> IO CInt 

pwhash_alg_argon2i13 :: Int Source #

version 1.3 of the Argon2i algorithm

pwhash_alg_argon2id13 :: Int Source #

version 1.3 of the Argon2id algorithm

pwhash_alg_default :: Int Source #

Lets libsodium pick a hashing algorithm

pwhash_bytes_max :: Int Source #

Maximum output length for key derivation.

pwhash_bytes_min :: Int Source #

Constants for the default algorithm | Minimum output length for key derivation (16 (128 bits)).

pwhash_memlimit_interactive :: Int Source #

Constant for currently 64MB memory

pwhash_memlimit_moderate :: Int Source #

Constant for currently 256MB memory

pwhash_memlimit_sensitive :: Int Source #

Constant for currently 1024MB memory

pwhash_memlimit_min :: Int Source #

Minimum allowed memory limit for password hashing

pwhash_memlimit_max :: Int Source #

Maximum allowed memory limit for password hashing

pwhash_opslimit_interactive :: Int Source #

Constant for relatively fast hashing

pwhash_opslimit_moderate :: Int Source #

Constant for moderately fast hashing

pwhash_opslimit_sensitive :: Int Source #

Constant for relatively slow hashing

pwhash_opslimit_min :: Int Source #

Minimum allowed number of computations for password hashing

pwhash_opslimit_max :: Int Source #

Maximum allowed number of computations for password hashing

pwhash_passwd_min :: Int Source #

Minimum number of characters in password for key derivation

pwhash_passwd_max :: Int Source #

Maximum number of characters in password for key derivation

pwhash_saltbytes :: Int Source #

Size of salt

pwhash_strbytes :: Int Source #

(Maximum) size of password hashing output

pwhash_argon2i_bytes_max :: Int Source #

Maximum output length for key derivation.

pwhash_argon2i_bytes_min :: Int Source #

Constants for ARGON2I | Minimum output length for key derivation (= 16 (128 bits)).

pwhash_argon2i_memlimit_interactive :: Int Source #

Constant for currently 64MB memory

pwhash_argon2i_memlimit_moderate :: Int Source #

Constant for currently 256MB memory

pwhash_argon2i_memlimit_sensitive :: Int Source #

Constant for currently 1024MB memory

pwhash_argon2i_memlimit_min :: Int Source #

Minimum allowed memory limit for password hashing

pwhash_argon2i_memlimit_max :: Int Source #

Maximum allowed memory limit for password hashing

pwhash_argon2i_opslimit_interactive :: Int Source #

Constant for relatively fast hashing

pwhash_argon2i_opslimit_moderate :: Int Source #

Constant for moderately fast hashing

pwhash_argon2i_opslimit_sensitive :: Int Source #

Constant for relatively slow hashing

pwhash_argon2i_opslimit_min :: Int Source #

Minimum allowed number of computations for password hashing

pwhash_argon2i_opslimit_max :: Int Source #

Maximum allowed number of computations for password hashing

pwhash_argon2i_passwd_min :: Int Source #

Minimum number of characters in password for key derivation

pwhash_argon2i_passwd_max :: Int Source #

Maximum number of characters in password for key derivation

pwhash_argon2i_strbytes :: Int Source #

(Maximum) size of password hashing output

pwhash_argon2id_bytes_max :: Int Source #

Maximum output length for key derivation.

pwhash_argon2id_bytes_min :: Int Source #

Constants for Argon2ID | Minimum output length for key derivation (= 16 (128 bits)).

pwhash_argon2id_memlimit_interactive :: Int Source #

Constant for currently 64MB memory

pwhash_argon2id_memlimit_moderate :: Int Source #

Constant for currently 256MB memory

pwhash_argon2id_memlimit_sensitive :: Int Source #

Constant for currently 1024MB memory

pwhash_argon2id_memlimit_min :: Int Source #

Minimum allowed memory limit for password hashing

pwhash_argon2id_memlimit_max :: Int Source #

Maximum allowed memory limit for password hashing

pwhash_argon2id_opslimit_interactive :: Int Source #

Constant for relatively fast hashing

pwhash_argon2id_opslimit_moderate :: Int Source #

Constant for moderately fast hashing

pwhash_argon2id_opslimit_sensitive :: Int Source #

Constant for relatively slow hashing

pwhash_argon2id_opslimit_min :: Int Source #

Minimum allowed number of computations for password hashing

pwhash_argon2id_opslimit_max :: Int Source #

Maximum allowed number of computations for password hashing

pwhash_argon2id_passwd_min :: Int Source #

Minimum number of characters in password for key derivation

pwhash_argon2id_passwd_max :: Int Source #

Maximum number of characters in password for key derivation

pwhash_argon2id_strbytes :: Int Source #

(Maximum) size of password hashing output

newtype Salt Source #

Salt for deriving keys from passwords

Constructors

Salt 

Fields

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)))

newtype PasswordHash Source #

Verification string for stored passwords This hash contains only printable characters, hence we can just derive Show.

Constructors

PasswordHash 

Fields

Instances

Instances details
Data PasswordHash 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) -> PasswordHash -> c PasswordHash #

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

toConstr :: PasswordHash -> Constr #

dataTypeOf :: PasswordHash -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Associated Types

type Rep PasswordHash :: Type -> Type #

Show PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

NFData PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Methods

rnf :: PasswordHash -> () #

Eq PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Ord PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

Hashable PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

type Rep PasswordHash Source # 
Instance details

Defined in Crypto.Saltine.Internal.Password

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

newtype Opslimit Source #

Wrapper type for the operations used by password hashing

Constructors

Opslimit 

Fields

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)))

newtype Memlimit Source #

Wrapper type for the memory used by password hashing

Constructors

Memlimit 

Fields

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)))

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))))

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)))