{-# LANGUAGE OverloadedStrings #-}
module Text.Password.Strength (
score,
Score(..),
strength,
Strength(..),
en_US
) where
import Data.Text (Text)
import Data.Time.Calendar (Day)
import Data.Aeson (ToJSON(..), (.=))
import qualified Data.Aeson as Aeson
import Text.Password.Strength.Internal.Config
import qualified Text.Password.Strength.Internal.Search as Search
newtype Score = Score { Score -> Integer
getScore :: Integer }
deriving (Int -> Score -> ShowS
[Score] -> ShowS
Score -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Score] -> ShowS
$cshowList :: [Score] -> ShowS
show :: Score -> String
$cshow :: Score -> String
showsPrec :: Int -> Score -> ShowS
$cshowsPrec :: Int -> Score -> ShowS
Show, Score -> Score -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Score -> Score -> Bool
$c/= :: Score -> Score -> Bool
== :: Score -> Score -> Bool
$c== :: Score -> Score -> Bool
Eq, Eq Score
Score -> Score -> Bool
Score -> Score -> Ordering
Score -> Score -> Score
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Score -> Score -> Score
$cmin :: Score -> Score -> Score
max :: Score -> Score -> Score
$cmax :: Score -> Score -> Score
>= :: Score -> Score -> Bool
$c>= :: Score -> Score -> Bool
> :: Score -> Score -> Bool
$c> :: Score -> Score -> Bool
<= :: Score -> Score -> Bool
$c<= :: Score -> Score -> Bool
< :: Score -> Score -> Bool
$c< :: Score -> Score -> Bool
compare :: Score -> Score -> Ordering
$ccompare :: Score -> Score -> Ordering
Ord)
instance ToJSON Score where
toJSON :: Score -> Value
toJSON Score
s = [Pair] -> Value
Aeson.object
[ Key
"score" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Score -> Integer
getScore Score
s
, Key
"strength" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. Show a => a -> String
show (Score -> Strength
strength Score
s)
]
score :: Config
-> Day
-> Text
-> Score
score :: Config -> Day -> Text -> Score
score Config
c Day
d Text
p = Integer -> Score
Score forall a b. (a -> b) -> a -> b
$ Graph -> Integer
Search.score (Config -> Day -> Text -> Graph
Search.graph Config
c Day
d Text
p)
data Strength
= Risky
| Weak
| Moderate
| Safe
| Strong
deriving (Int -> Strength -> ShowS
[Strength] -> ShowS
Strength -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Strength] -> ShowS
$cshowList :: [Strength] -> ShowS
show :: Strength -> String
$cshow :: Strength -> String
showsPrec :: Int -> Strength -> ShowS
$cshowsPrec :: Int -> Strength -> ShowS
Show, ReadPrec [Strength]
ReadPrec Strength
Int -> ReadS Strength
ReadS [Strength]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Strength]
$creadListPrec :: ReadPrec [Strength]
readPrec :: ReadPrec Strength
$creadPrec :: ReadPrec Strength
readList :: ReadS [Strength]
$creadList :: ReadS [Strength]
readsPrec :: Int -> ReadS Strength
$creadsPrec :: Int -> ReadS Strength
Read, Strength -> Strength -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Strength -> Strength -> Bool
$c/= :: Strength -> Strength -> Bool
== :: Strength -> Strength -> Bool
$c== :: Strength -> Strength -> Bool
Eq, Eq Strength
Strength -> Strength -> Bool
Strength -> Strength -> Ordering
Strength -> Strength -> Strength
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Strength -> Strength -> Strength
$cmin :: Strength -> Strength -> Strength
max :: Strength -> Strength -> Strength
$cmax :: Strength -> Strength -> Strength
>= :: Strength -> Strength -> Bool
$c>= :: Strength -> Strength -> Bool
> :: Strength -> Strength -> Bool
$c> :: Strength -> Strength -> Bool
<= :: Strength -> Strength -> Bool
$c<= :: Strength -> Strength -> Bool
< :: Strength -> Strength -> Bool
$c< :: Strength -> Strength -> Bool
compare :: Strength -> Strength -> Ordering
$ccompare :: Strength -> Strength -> Ordering
Ord, Int -> Strength
Strength -> Int
Strength -> [Strength]
Strength -> Strength
Strength -> Strength -> [Strength]
Strength -> Strength -> Strength -> [Strength]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Strength -> Strength -> Strength -> [Strength]
$cenumFromThenTo :: Strength -> Strength -> Strength -> [Strength]
enumFromTo :: Strength -> Strength -> [Strength]
$cenumFromTo :: Strength -> Strength -> [Strength]
enumFromThen :: Strength -> Strength -> [Strength]
$cenumFromThen :: Strength -> Strength -> [Strength]
enumFrom :: Strength -> [Strength]
$cenumFrom :: Strength -> [Strength]
fromEnum :: Strength -> Int
$cfromEnum :: Strength -> Int
toEnum :: Int -> Strength
$ctoEnum :: Int -> Strength
pred :: Strength -> Strength
$cpred :: Strength -> Strength
succ :: Strength -> Strength
$csucc :: Strength -> Strength
Enum, Strength
forall a. a -> a -> Bounded a
maxBound :: Strength
$cmaxBound :: Strength
minBound :: Strength
$cminBound :: Strength
Bounded)
strength :: Score -> Strength
strength :: Score -> Strength
strength (Score Integer
n)
| Integer
n forall a. Ord a => a -> a -> Bool
< Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ ( Int
3 :: Int) = Strength
Risky
| Integer
n forall a. Ord a => a -> a -> Bool
< Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ ( Int
6 :: Int) = Strength
Weak
| Integer
n forall a. Ord a => a -> a -> Bool
< Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ ( Int
8 :: Int) = Strength
Moderate
| Integer
n forall a. Ord a => a -> a -> Bool
< Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
10 :: Int) = Strength
Safe
| Bool
otherwise = Strength
Strong