| Copyright | This 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. | 
|---|---|
| License | MIT | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Text.Password.Strength.Internal
Contents
- Splitting a Password into Tokens
- Lenses for the TokenType
- Translate the Characters of a Password
- Matching Tokens Against Known Patterns
- Estimate Matched Tokens
- Searching for the Weakest Path Through a Password
- Frequency Dictionary Matching
- L33t Speak Substitution
- Adjacency Matching (for Keyboard Patterns)
- Keyboard Pattern Matching
- Sequence Matches
- Date Matches
- Repeating Token Matches
- Configuration
Description
These internals details are subject to change. Use at your own risk.
Synopsis
- data Token = Token {- _tokenChars :: Text
- _tokenLower :: Text
- _startIndex :: Int
- _endIndex :: Int
 
- allTokens :: Text -> [Token]
- tokenChars :: Lens' Token Text
- tokenLower :: Lens' Token Text
- startIndex :: Lens' Token Int
- endIndex :: Lens' Token Int
- translateMap :: (Char -> String) -> Text -> [Text]
- data Match
- type Matches = Map Token [Match]
- matches :: Config -> Day -> Text -> Matches
- type Guesses = Map Token Integer
- type Estimates = Map Token Estimate
- newtype Estimate = Estimate {- getEstimate :: Estimates -> Integer
 
- estimateAll :: Config -> Matches -> Guesses
- estimate :: Config -> Token -> Match -> Estimates -> Integer
- data Graph = Graph {- exitNode :: Int
- graphEdges :: Map (Int, Int) Integer
- scoreGraph :: Gr () Integer
 
- type Node = LNode ()
- type Edge = LEdge Integer
- edges :: Config -> Day -> Text -> Map (Int, Int) Integer
- bfEdges :: Text -> Map (Int, Int) Integer -> [((Int, Int), Integer)]
- graph :: Config -> Day -> Text -> Graph
- newtype Score = Score {}
- score :: Graph -> Score
- shortestPath :: Graph -> Maybe [Int]
- type Dictionary = HashMap Text Int
- type Rank = Int
- rank :: Config -> (a -> Text) -> a -> Maybe Rank
- data L33t
- l33t :: Token -> [L33t]
- l33tText :: Lens' L33t Text
- l33tSub :: Lens' L33t Int
- l33tUnsub :: Lens' L33t Int
- l33t2Eng :: Char -> String
- type Pattern = (Char, Char)
- data Direction
- data Move
- data Layer
- data Adjacency = Adjacency {- _movement :: Move
- _firstLayer :: Layer
- _secondLayer :: Layer
 
- data AdjacencyTable = AdjacencyTable {}
- totalChars :: Lens' AdjacencyTable Int
- averageNeighbors :: Lens' AdjacencyTable Int
- patterns :: Lens' AdjacencyTable (Map Pattern Adjacency)
- findSequence :: Text -> AdjacencyTable -> Maybe (NonEmpty Adjacency)
- data AdjacencyScore = AdjacencyScore {}
- patternLength :: Lens' AdjacencyScore Int
- totalTurns :: Lens' AdjacencyScore Int
- primaryLayer :: Lens' AdjacencyScore Int
- secondaryLayer :: Lens' AdjacencyScore Int
- scoreSequence :: AdjacencyScore -> Adjacency -> AdjacencyScore
- data KeyboardPattern
- keyboardToken :: Lens KeyboardPattern KeyboardPattern Token Token
- keyboardPattern :: AdjacencyTable -> Token -> Maybe KeyboardPattern
- keyboardEstimate :: KeyboardPattern -> Integer
- type Delta = Int
- isSequence :: Text -> Maybe Delta
- estimateSequence :: (Char -> Bool) -> Text -> Delta -> Integer
- data Date
- type YMD = (Int, Int, Int)
- isDate :: Day -> Text -> Maybe Date
- toYMD :: Date -> YMD
- estimateDate :: Date -> Integer
- data RepeatMap
- type Repeat = Int
- mkRepeatMap :: Map Token a -> RepeatMap
- repeatMatch :: RepeatMap -> Token -> Maybe (Repeat, Token)
- data Config
- class HasConfig c
- type Dictionary = HashMap Text Int
- en_US :: Config
- dictionaries :: Config -> [Dictionary]
- passwordLists :: HasConfig c => Lens' c [Dictionary]
- wordFrequencyLists :: HasConfig c => Lens' c [Dictionary]
- customFrequencyLists :: HasConfig c => Lens' c [Dictionary]
- keyboardGraphs :: HasConfig c => Lens' c [AdjacencyTable]
- obviousSequenceStart :: HasConfig c => Lens' c (Char -> Bool)
- addCustomFrequencyList :: Vector Text -> Config -> Config
Splitting a Password into Tokens
A token is a substring of a password.
Constructors
| Token | |
| Fields 
 | |
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
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: 
 | 
| 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  | 
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
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 | |
| Fields 
 | |
Searching for the Weakest Path Through a Password
A password and estimated guesses represented as a 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.
A score is an estimate of the number of guesses it would take to crack a password.
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
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
Track a translated l33t speak token.
Adjacency Matching (for Keyboard Patterns)
type Pattern = (Char, Char) Source #
A Pattern is two Unicode characters next to one another in a password.
Direction of movement for adjacent characters.
Instances
Movement between characters.
Instances
| Eq Move Source # | |
| Show Move Source # | |
| Generic Move Source # | |
| Binary Move Source # | |
| type Rep Move Source # | |
| Defined in Text.Password.Strength.Internal.Adjacency type Rep Move = D1 (MetaData "Move" "Text.Password.Strength.Internal.Adjacency" "zxcvbn-hs-0.2.0.0-2yq8vmeX9CmCD0uA0vJ0N3" False) (C1 (MetaCons "Move" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Direction)) :+: C1 (MetaCons "Stay" PrefixI False) (U1 :: Type -> Type)) | |
Keyboard layers.
Information about how two characters are related to one another.
Constructors
| Adjacency | |
| Fields 
 | |
Instances
| Show Adjacency Source # | |
| Generic Adjacency Source # | |
| Binary Adjacency Source # | |
| type Rep Adjacency Source # | |
| Defined in Text.Password.Strength.Internal.Adjacency type Rep Adjacency = D1 (MetaData "Adjacency" "Text.Password.Strength.Internal.Adjacency" "zxcvbn-hs-0.2.0.0-2yq8vmeX9CmCD0uA0vJ0N3" 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 
 | |
Instances
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 
 | |
Instances
| Eq AdjacencyScore Source # | |
| Defined in Text.Password.Strength.Internal.Adjacency Methods (==) :: AdjacencyScore -> AdjacencyScore -> Bool # (/=) :: AdjacencyScore -> AdjacencyScore -> Bool # | |
| Show AdjacencyScore Source # | |
| Defined in Text.Password.Strength.Internal.Adjacency Methods showsPrec :: Int -> AdjacencyScore -> ShowS # show :: AdjacencyScore -> String # showList :: [AdjacencyScore] -> ShowS # | |
| Semigroup AdjacencyScore Source # | |
| Defined in Text.Password.Strength.Internal.Adjacency Methods (<>) :: AdjacencyScore -> AdjacencyScore -> AdjacencyScore # sconcat :: NonEmpty AdjacencyScore -> AdjacencyScore # stimes :: Integral b => b -> AdjacencyScore -> AdjacencyScore # | |
| Monoid AdjacencyScore Source # | |
| Defined in Text.Password.Strength.Internal.Adjacency Methods mappend :: AdjacencyScore -> AdjacencyScore -> AdjacencyScore # mconcat :: [AdjacencyScore] -> AdjacencyScore # | |
scoreSequence :: AdjacencyScore -> Adjacency -> AdjacencyScore Source #
Calculate the score for two adjacent characters.
Keyboard Pattern Matching
data KeyboardPattern Source #
Information about a found pattern.
Instances
| Show KeyboardPattern Source # | |
| Defined in Text.Password.Strength.Internal.Keyboard Methods showsPrec :: Int -> KeyboardPattern -> ShowS # show :: KeyboardPattern -> String # showList :: [KeyboardPattern] -> ShowS # | |
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
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
A date as a triple.
estimateDate :: Date -> Integer Source #
Estimate the number of guesses for a date match.
Deviations from the zxcvbn paper:
- The other implementations limit the year multiplier to 20 so we do the same here.
- The other implementations multiply by 4 when date separators are used in the token. We do the same.
Repeating Token Matches
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
A type to control which dictionaries, keyboard layouts, etc. will be used when estimating guesses.
Instances
| Semigroup Config Source # | |
| Monoid Config Source # | |
| HasConfig Config Source # | |
| Defined in Text.Password.Strength.Internal.Config Methods customFrequencyLists :: Lens' Config [Dictionary] Source # keyboardGraphs :: Lens' Config [AdjacencyTable] Source # obviousSequenceStart :: Lens' Config (Char -> Bool) Source # | |
Minimal complete definition
config
Instances
| HasConfig Config Source # | |
| Defined in Text.Password.Strength.Internal.Config Methods customFrequencyLists :: Lens' Config [Dictionary] Source # keyboardGraphs :: Lens' Config [AdjacencyTable] Source # obviousSequenceStart :: Lens' Config (Char -> Bool) Source # | |
dictionaries :: Config -> [Dictionary] Source #
Access all configured dictionaries.
passwordLists :: HasConfig c => Lens' c [Dictionary] Source #
wordFrequencyLists :: HasConfig c => Lens' c [Dictionary] Source #
customFrequencyLists :: HasConfig c => Lens' c [Dictionary] Source #
keyboardGraphs :: HasConfig c => Lens' c [AdjacencyTable] Source #