{-# LANGUAGE RecordWildCards #-}
module Text.Password.Strength.Internal.Search (
Graph(..),
Node,
Edge,
edges,
bfEdges,
graph,
Score(..),
score,
shortestPath
) where
import Control.Lens ((^.), _1, _2)
import Control.Monad (guard)
import qualified Data.Graph.Inductive.Graph as Graph
import Data.Graph.Inductive.PatriciaTree (Gr)
import Data.Graph.Inductive.Query.SP (sp)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe (listToMaybe, mapMaybe)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Time.Calendar (Day)
import Text.Password.Strength.Internal.Config
import Text.Password.Strength.Internal.Estimate
import Text.Password.Strength.Internal.Match
import Text.Password.Strength.Internal.Math
import Text.Password.Strength.Internal.Token
type Node = Graph.LNode ()
type Edge = Graph.LEdge Integer
data Graph = Graph
{ exitNode :: Int
, graphEdges :: Map (Int, Int) Integer
, scoreGraph :: Gr () Integer
} deriving Show
edges :: Config -> Day -> Text -> Map (Int, Int) Integer
edges c d p = Map.mapKeys loc (estimateAll c (matches c d p))
where
loc :: Token -> (Int, Int)
loc t = (t ^. startIndex, t ^. endIndex + 1)
bfEdges :: Text -> Map (Int, Int) Integer -> [((Int, Int), Integer)]
bfEdges p es = mapMaybe (fmap guesses . check) rows
where
rows :: [[(Int, Int)]]
rows = do
x <- 0:map (^. _2) (Map.keys es)
pure (pair x)
pair :: Int -> [(Int, Int)]
pair x = do
y <- map (^. _1) (Map.keys es) ++ [Text.length p]
guard (y > x)
pure (x, y)
check :: [(Int, Int)] -> Maybe (Int, Int)
check row =
if any (`Map.member` es) row
then Nothing
else listToMaybe row
guesses :: (Int, Int) -> ((Int, Int), Integer)
guesses (x, y) = ((x, y), bruteForce (y - x))
graph :: Config -> Day -> Text -> Graph
graph config day password =
Graph exit edges' (Graph.mkGraph nodes (flatten edges'))
where
exit :: Int
exit = Text.length password
nodes :: [Node]
nodes = zip [0..exit] (repeat ())
edges' :: Map (Int, Int) Integer
edges' =
let es = edges config day password
in es `Map.union` Map.fromList (bfEdges password es)
flatten :: Map (Int, Int) Integer -> [(Int, Int, Integer)]
flatten = map (\((x, y), z) -> (x, y, z)) . Map.assocs
newtype Score = Score { getScore :: Integer }
deriving (Show, Eq, Ord)
score :: Graph -> Score
score g@Graph{..} = Score $
case shortestPath g of
Nothing -> worstCase
Just path -> maybe worstCase product (scores (nodes path))
where
worstCase :: Integer
worstCase = bruteForce exitNode
nodes :: [Int] -> [(Int, Int)]
nodes xs = zip xs (drop 1 xs)
scores :: [(Int, Int)] -> Maybe [Integer]
scores = mapM (`Map.lookup` graphEdges)
shortestPath :: Graph -> Maybe [Int]
shortestPath Graph{..} = sp 0 exitNode scoreGraph