module Text.Password.Strength.Internal.Dictionary (
Dictionary,
Rank,
rank
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe (mapMaybe)
import Data.Text (Text)
import Text.Password.Strength.Internal.Config
type Rank = Int
rank :: Config -> (a -> Text) -> a -> Maybe Rank
rank :: Config -> (a -> Text) -> a -> Maybe Rank
rank Config
c a -> Text
f a
a =
case [Dictionary] -> [Rank]
check (Config -> [Dictionary]
dictionaries Config
c) of
[] -> Maybe Rank
forall a. Maybe a
Nothing
[Rank]
xs -> Rank -> Maybe Rank
forall a. a -> Maybe a
Just ([Rank] -> Rank
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Rank]
xs)
where
check :: [Dictionary] -> [Rank]
check :: [Dictionary] -> [Rank]
check = (Dictionary -> Maybe Rank) -> [Dictionary] -> [Rank]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Text -> Dictionary -> Maybe Rank
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
key)
key :: Text
key :: Text
key = a -> Text
f a
a