sel-0.0.1.0: Cryptography for the casual user
Copyright(C) Hécate Moonlight 2022
LicenseBSD-3-Clause
MaintainerThe Haskell Cryptography Group
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sel.Hashing.Password

Description

 
Synopsis

Introduction

This API provides functions for password hashing, backed by the Argon2id algorithm.

If you need to deviate from the defaults enforced by this module, please use the underlying bindings at LibSodium.Bindings.PasswordHashing.

data PasswordHash Source #

A hashed password from the Argon2id algorithm.

Since: 0.0.1.0

Instances

Instances details
Generic PasswordHash Source # 
Instance details

Defined in Sel.Hashing.Password

Associated Types

type Rep PasswordHash :: Type -> Type #

Show PasswordHash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

Eq PasswordHash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

Ord PasswordHash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

Display PasswordHash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

type Rep PasswordHash Source # 
Instance details

Defined in Sel.Hashing.Password

type Rep PasswordHash = D1 ('MetaData "PasswordHash" "Sel.Hashing.Password" "sel-0.0.1.0-inplace" 'True) (C1 ('MetaCons "PasswordHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForeignPtr CChar))))

Password Hashing and Verifying

hashByteString :: StrictByteString -> IO PasswordHash Source #

Hash the password with the Argon2id algorithm and a set of pre-defined parameters.

The hash is encoded in a human-readable format that includes:

  • The result of a memory-hard, CPU-intensive hash function applied to the password;
  • The automatically generated salt used for the previous computation;
  • The other parameters required to verify the password, including the algorithm identifier, its version, opslimit, and memlimit.

Example output: $argon2id$v=19$m=262144,t=3,p=1$fpPdXj9mK7J4m…

Since: 0.0.1.0

hashText :: Text -> IO PasswordHash Source #

Hash a UTF8-encoded password with the Argon2id algorithm and a set of pre-defined parameters.

Since: 0.0.1.0

verifyByteString :: PasswordHash -> StrictByteString -> Bool Source #

Verify the password hash against a clear StrictByteString password

This function purposefully takes some time to complete, in order to alleviate bruteforce attacks.

Since: 0.0.1.0

verifyText :: PasswordHash -> Text -> Bool Source #

Verify the password hash against a clear Text password

This function purposefully takes some time to complete, in order to alleviate bruteforce attacks.

Since: 0.0.1.0

hashByteStringWithParams :: Argon2Params -> Salt -> StrictByteString -> IO PasswordHash Source #

Hash the password with the Argon2id algorithm.

The hash is not encoded in human-readable format.

Since: 0.0.1.0

Conversion

passwordHashToText :: PasswordHash -> Text Source #

Convert a PasswordHash to a strict Text.

Since: 0.0.1.0

passwordHashToHexText :: PasswordHash -> Text Source #

Convert a PasswordHash to a strict hexadecimal-encoded Text.

It is recommended to use this one on a PasswordHash produced by hashByteStringWithParams.

Since: 0.0.1.0

passwordHashToHexByteString :: PasswordHash -> StrictByteString Source #

Convert a PasswordHash to a hexadecimal-encoded StrictByteString.

It is recommended to use this one on a PasswordHash produced by hashByteStringWithParams.

Since: 0.0.1.0

asciiTextToPasswordHash :: Text -> PasswordHash Source #

Convert an ascii-encoded password hash to a PasswordHash

This function does not perform ASCII validation.

Since: 0.0.1.0

asciiByteStringToPasswordHash :: StrictByteString -> PasswordHash Source #

Convert an ascii-encoded password hash to a PasswordHash

This function does not perform ASCII validation.

Since: 0.0.1.0

Salt

data Salt Source #

The Salt is used in conjunction with hashByteStringWithParams when you want to manually provide the piece of data that will differentiate two fingerprints of the same password.

It is automatically taken care of for you when you use hashByteString or hashText.

Use genSalt to create a Salt of size equal to the constant cryptoPWHashSaltBytes.

Since: 0.0.1.0

Instances

Instances details
Show Salt Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

Methods

showsPrec :: Int -> Salt -> ShowS #

show :: Salt -> String #

showList :: [Salt] -> ShowS #

Eq Salt Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

Methods

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

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

Ord Salt Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.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 #

Display Salt Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing.Password

genSalt :: IO Salt Source #

Generate a random Salt for password hashing

Since: 0.0.1.0

Conversion

saltToBinary :: Salt -> StrictByteString Source #

Convert Salt to underlying StrictByteString binary.

Since: 0.0.2.0

saltToHexText :: Salt -> Text Source #

Convert Salt to a strict hexadecimal-encoded Text.

Since: 0.0.2.0

saltToHexByteString :: Salt -> StrictByteString Source #

Convert Salt to a hexadecimal-encoded StrictByteString.

Since: 0.0.2.0

binaryToSalt :: StrictByteString -> Maybe Salt Source #

Convert StrictByteString to Salt.

The input salt must be of length cryptoPWHashSaltBytes.

Since: 0.0.2.0

hexTextToSalt :: Text -> Maybe Salt Source #

Convert a strict hexadecimal-encoded Text to a Salt.

The input salt, once decoded from base16, must be of length cryptoPWHashSaltBytes.

Since: 0.0.1.0

hexByteStringToSalt :: StrictByteString -> Maybe Salt Source #

Convert a hexadecimal-encoded StrictByteString to a Salt.

The input salt, once decoded from base16, must be of length cryptoPWHashSaltBytes.

Since: 0.0.1.0

Argon2 Parameters

data Argon2Params Source #

Since: 0.0.1.0

Constructors

Argon2Params CULLong CSize 

defaultArgon2Params :: Argon2Params Source #

These are the default parameters with which hashByteStringWithParams can be invoked:

Since: 0.0.1.0