module Text.Password.Strength.Internal.Sequence (
Delta,
isSequence,
estimateSequence
) where
import Data.Char (ord, isDigit)
import Data.Text (Text)
import qualified Data.Text as Text
type Delta = Int
isSequence :: Text -> Maybe Delta
isSequence :: Text -> Maybe Delta
isSequence Text
t =
case forall a b. (a -> b) -> [a] -> [b]
map (Char, Char) -> Delta
measure [(Char, Char)]
offset of
[] -> forall a. Maybe a
Nothing
Delta
x:[Delta]
xs -> if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall a. Eq a => a -> a -> Bool
== Delta
x) [Delta]
xs
then forall a. a -> Maybe a
Just Delta
x
else forall a. Maybe a
Nothing
where
offset :: [(Char, Char)]
offset :: [(Char, Char)]
offset = Text -> Text -> [(Char, Char)]
Text.zip Text
t (Delta -> Text -> Text
Text.drop Delta
1 Text
t)
measure :: (Char, Char) -> Delta
measure :: (Char, Char) -> Delta
measure (Char
x, Char
y) = Char -> Delta
ord Char
y forall a. Num a => a -> a -> a
- Char -> Delta
ord Char
x
estimateSequence :: (Char -> Bool) -> Text -> Delta -> Integer
estimateSequence :: (Char -> Bool) -> Text -> Delta -> Integer
estimateSequence Char -> Bool
f Text
t Delta
d =
let len :: Integer
len = forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ Text -> Delta
Text.length Text
t
start :: Char
start = if Integer
len forall a. Ord a => a -> a -> Bool
> Integer
0 then Text -> Char
Text.head Text
t else Char
'\0'
delta :: Integer
delta = forall a. Integral a => a -> Integer
toInteger (if Delta
d forall a. Eq a => a -> a -> Bool
== Delta
0 then Delta
1 else forall a. Num a => a -> a
abs Delta
d)
base :: Integer
base = case () of
() | Char -> Bool
f Char
start -> Integer
4
| Char -> Bool
isDigit Char
start -> Integer
10
| Bool
otherwise -> Integer
26
in Integer
base forall a. Num a => a -> a -> a
* Integer
len forall a. Num a => a -> a -> a
* Integer
delta