zxcvbn-hs-0.2.1.0: Password strength estimation based on zxcvbn.

CopyrightThis file is part of the package zxcvbn-hs. It is subject to the
license terms in the LICENSE file found in the top-level directory
of this distribution and at:

https://code.devalot.com/sthenauth/zxcvbn-hs

No part of this package including this file may be copied
modified propagated or distributed except according to the terms
contained in the LICENSE file.
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

Text.Password.Strength.Internal

Contents

Description

These internals details are subject to change. Use at your own risk.

Synopsis

Splitting a Password into Tokens

data Token Source #

A token is a substring of a password.

Constructors

Token 
Instances
Eq Token Source # 
Instance details

Defined in Text.Password.Strength.Internal.Token

Methods

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

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

Ord Token Source # 
Instance details

Defined in Text.Password.Strength.Internal.Token

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Show Token Source # 
Instance details

Defined in Text.Password.Strength.Internal.Token

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

allTokens :: Text -> [Token] Source #

Extract all substrings from the input Text. A substring has a minimum character length of 3 for performance and to prevent false positives for matches such as sequences and repeats.

Examples:

>>> map _tokenChars (allTokens "abcdef")
["abc","abcd","abcde","abcdef","bcd","bcde","bcdef","cde","cdef","def"]

Lenses for the Token Type

Translate the Characters of a Password

translateMap :: (Char -> String) -> Text -> [Text] Source #

Translate the characters of a Text value.

Given a function that translates a character into one or more characters, return all possible translations.

Examples:

>>> translateMap l33t2Eng "p111
["piii","plii","pili","plli","piil","plil","pill","plll"]

Matching Tokens Against Known Patterns

data Match Source #

The known patterns we are searching for.

Constructors

DictionaryMatch Rank

The associated token was found in a frequency dictionary with the specified rank.

ReverseDictionaryMatch Rank

The associated token was found in a frequency dictionary, but only after its characters were reversed.

L33tMatch Rank L33t

The associated token was found in a frequency dictionary, but only after its characters were translated from l33t speak to English.

KeyboardMatch KeyboardPattern

The associated token is wholly made up of an adjacent sequence of characters that make a pattern on a keyboard.

SequenceMatch Delta

The characters of the associated token form a sequence because the delta between all the characters is the same.

Examples:

  • abc
DateMatch Date

The associated token wholly contains a date.

RepeatMatch Repeat Token

The associated token is an adjacent repeat of another token (the one given to this constructor). The number of times it repeats is given as Repeat.

Instances
Show Match Source # 
Instance details

Defined in Text.Password.Strength.Internal.Match

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

type Matches = Map Token [Match] Source #

Information about how a token matches a specific match pattern.

matches :: Config -> Day -> Text -> Matches Source #

All possible matches after various transformations.

Estimate Matched Tokens

type Guesses = Map Token Integer Source #

Final mapping of a token to its lowest score.

type Estimates = Map Token Estimate Source #

Map of partially applied estimates.

newtype Estimate Source #

A function that will produce an estimate once we know the estimates for other tokens. This is necessary to score repeat matches since they require looking up the score for a different token.

Constructors

Estimate 

estimateAll :: Config -> Matches -> Guesses Source #

Estimate all of the given matches.

estimate :: Config -> Token -> Match -> Estimates -> Integer Source #

Estimate a single match.

Searching for the Weakest Path Through a Password

data Graph Source #

A password and estimated guesses represented as a graph.

Constructors

Graph 
Instances
Show Graph Source # 
Instance details

Defined in Text.Password.Strength.Internal.Search

Methods

showsPrec :: Int -> Graph -> ShowS #

show :: Graph -> String #

showList :: [Graph] -> ShowS #

type Node = LNode () Source #

A node in a guessing graph.

type Edge = LEdge Integer Source #

An edge is a guessing graph.

edges :: Config -> Day -> Text -> Map (Int, Int) Integer Source #

Given a password and a user word list, produce graph edges that connect the characters of the password.

bfEdges :: Text -> Map (Int, Int) Integer -> [((Int, Int), Integer)] Source #

Brute force edges. In other words, the edges required to ensure there's a path in the graph from the start node to the end node.

graph :: Config -> Day -> Text -> Graph Source #

Generate a guessing graph from the given password and user word list. In the guessing graph the nodes are the characters in the password and the edges are the estimated guesses.

newtype Score Source #

A score is an estimate of the number of guesses it would take to crack a password.

Constructors

Score 

Fields

Instances
Eq Score Source # 
Instance details

Defined in Text.Password.Strength.Internal.Search

Methods

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

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

Ord Score Source # 
Instance details

Defined in Text.Password.Strength.Internal.Search

Methods

compare :: Score -> Score -> Ordering #

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

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

(>) :: Score -> Score -> Bool #

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

max :: Score -> Score -> Score #

min :: Score -> Score -> Score #

Show Score Source # 
Instance details

Defined in Text.Password.Strength.Internal.Search

Methods

showsPrec :: Int -> Score -> ShowS #

show :: Score -> String #

showList :: [Score] -> ShowS #

score :: Graph -> Score Source #

Collapse a graph down to a single score which represents the estimated number of guesses it would take to crack the password.

shortestPath :: Graph -> Maybe [Int] Source #

Calculate the shortest path through a guessing graph. In other words, the cheapest path for guessing a password.

Frequency Dictionary Matching

type Dictionary = HashMap Text Int Source #

Type alias for a frequency database.

type Rank = Int Source #

Type to represent a ranking.

rank :: Config -> (a -> Text) -> a -> Maybe Rank Source #

Look up the given value in all configured dictionaries, transforming each input with the given function. The lowest ranked score is return if it is found.

L33t Speak Substitution

data L33t Source #

Track a translated l33t speak token.

Instances
Show L33t Source # 
Instance details

Defined in Text.Password.Strength.Internal.L33t

Methods

showsPrec :: Int -> L33t -> ShowS #

show :: L33t -> String #

showList :: [L33t] -> ShowS #

l33t :: Token -> [L33t] Source #

Translate a token from l33t, counting l33t characters.

l33t2Eng :: Char -> String Source #

Convert l33t characters to their English character mappings.

Adjacency Matching (for Keyboard Patterns)

type Pattern = (Char, Char) Source #

A Pattern is two Unicode characters next to one another in a password.

data Direction Source #

Direction of movement for adjacent characters.

Constructors

N 
NE 
E 
SE 
S 
SW 
W 
NW 
Instances
Bounded Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Enum Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Eq Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Ord Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Show Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Generic Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Associated Types

type Rep Direction :: Type -> Type #

Binary Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

type Rep Direction Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

type Rep Direction = D1 (MetaData "Direction" "Text.Password.Strength.Internal.Adjacency" "zxcvbn-hs-0.2.1.0-JIz23TvjqM23C0otdfqBqr" False) (((C1 (MetaCons "N" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NE" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "E" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SE" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "S" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SW" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "W" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NW" PrefixI False) (U1 :: Type -> Type))))

data Move Source #

Movement between characters.

Constructors

Move Direction 
Stay 
Instances
Eq Move Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

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

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

Show Move Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

showsPrec :: Int -> Move -> ShowS #

show :: Move -> String #

showList :: [Move] -> ShowS #

Generic Move Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Associated Types

type Rep Move :: Type -> Type #

Methods

from :: Move -> Rep Move x #

to :: Rep Move x -> Move #

Binary Move Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

put :: Move -> Put #

get :: Get Move #

putList :: [Move] -> Put #

type Rep Move Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

type Rep Move = D1 (MetaData "Move" "Text.Password.Strength.Internal.Adjacency" "zxcvbn-hs-0.2.1.0-JIz23TvjqM23C0otdfqBqr" False) (C1 (MetaCons "Move" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Direction)) :+: C1 (MetaCons "Stay" PrefixI False) (U1 :: Type -> Type))

data Layer Source #

Keyboard layers.

Constructors

Primary 
Secondary 
Instances
Bounded Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Enum Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Eq Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

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

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

Ord Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

compare :: Layer -> Layer -> Ordering #

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

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

(>) :: Layer -> Layer -> Bool #

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

max :: Layer -> Layer -> Layer #

min :: Layer -> Layer -> Layer #

Show Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Generic Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Associated Types

type Rep Layer :: Type -> Type #

Methods

from :: Layer -> Rep Layer x #

to :: Rep Layer x -> Layer #

Binary Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Methods

put :: Layer -> Put #

get :: Get Layer #

putList :: [Layer] -> Put #

type Rep Layer Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

type Rep Layer = D1 (MetaData "Layer" "Text.Password.Strength.Internal.Adjacency" "zxcvbn-hs-0.2.1.0-JIz23TvjqM23C0otdfqBqr" False) (C1 (MetaCons "Primary" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Secondary" PrefixI False) (U1 :: Type -> Type))

data Adjacency Source #

Information about how two characters are related to one another.

Constructors

Adjacency 

Fields

Instances
Show Adjacency Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Generic Adjacency Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

Associated Types

type Rep Adjacency :: Type -> Type #

Binary Adjacency Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

type Rep Adjacency Source # 
Instance details

Defined in Text.Password.Strength.Internal.Adjacency

type Rep Adjacency = D1 (MetaData "Adjacency" "Text.Password.Strength.Internal.Adjacency" "zxcvbn-hs-0.2.1.0-JIz23TvjqM23C0otdfqBqr" False) (C1 (MetaCons "Adjacency" PrefixI True) (S1 (MetaSel (Just "_movement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Move) :*: (S1 (MetaSel (Just "_firstLayer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Layer) :*: S1 (MetaSel (Just "_secondLayer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Layer))))

data AdjacencyTable Source #

An adjacency graph (usually representing a single keyboard).

Constructors

AdjacencyTable 

Fields

findSequence :: Text -> AdjacencyTable -> Maybe (NonEmpty Adjacency) Source #

Find a pattern if it exists. If all characters in the given Text form a pattern in the given Graph then a list of matches will be returned.

data AdjacencyScore Source #

Scoring information for adjacent characters.

Constructors

AdjacencyScore 

Fields

scoreSequence :: AdjacencyScore -> Adjacency -> AdjacencyScore Source #

Calculate the score for two adjacent characters.

Keyboard Pattern Matching

data KeyboardPattern Source #

Information about a found pattern.

keyboardToken :: Lens KeyboardPattern KeyboardPattern Token Token Source #

Allow other code to access the token used in a pattern.

keyboardPattern :: AdjacencyTable -> Token -> Maybe KeyboardPattern Source #

Helper function to check if a token forms a keyboard pattern.

keyboardEstimate :: KeyboardPattern -> Integer Source #

Estimate the number of guesses needed for a keyboard pattern to be cracked.

Sequence Matches

type Delta = Int Source #

Type alias to represent the distance between characters.

isSequence :: Text -> Maybe Delta Source #

If the delta between all of the characters in the given text are the same, that delta is returned.

estimateSequence :: (Char -> Bool) -> Text -> Delta -> Integer Source #

Estimate a sequence.

Uses the scoring equation from the paper and not from the other implementations which don't even use the calculated delta. The only change from the paper is to compensated for a delta of 0, which isn't accounted for in the paper.

Date Matches

data Date Source #

A date as a triple.

Instances
Show Date Source # 
Instance details

Defined in Text.Password.Strength.Internal.Date

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

type YMD = (Int, Int, Int) Source #

Components of a found date (year, month, day).

isDate :: Day -> Text -> Maybe Date Source #

If the given text wholly contains a date, return it.

toYMD :: Date -> YMD Source #

Extract the date components of a Date record.

estimateDate :: Date -> Integer Source #

Estimate the number of guesses for a date match.

Deviations from the zxcvbn paper:

  1. The other implementations limit the year multiplier to 20 so we do the same here.
  2. The other implementations multiply by 4 when date separators are used in the token. We do the same.

Repeating Token Matches

data RepeatMap Source #

Internal mapping of repeating tokens.

type Repeat = Int Source #

Type alias for a count of repeating tokens.

mkRepeatMap :: Map Token a -> RepeatMap Source #

Generate a repeat map from an existing token map.

repeatMatch :: RepeatMap -> Token -> Maybe (Repeat, Token) Source #

Test to see if the given token is repeated.

If a repeat is found, the number of occurrences is returned along with the full token representing the repeating sequence.

In other words, if the token passed in is "word" and in the map we find that the original password contains "wordword", we return 2 to indicate 2 repeats and the token that represents the sequence "wordword".

Configuration

type Dictionary = HashMap Text Int Source #

Type alias for a frequency database.

en_US :: Config Source #

Default configuration for US English.

dictionaries :: Config -> [Dictionary] Source #

Access all configured dictionaries.

addCustomFrequencyList :: Vector Text -> Config -> Config Source #

Add a custom list of words for frequency lookup. The words should be ordered from most frequent to least frequent.