{-# LANGUAGE OverloadedStrings #-}

{-|

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

This is a native Haskell implementation of
the [zxcvbn](https://github.com/dropbox/zxcvbn) password strength
estimation algorithm as it appears in the 2016 USENIX
Security [paper and presentation](https://www.usenix.org/conference/usenixsecurity16/technical-sessions/presentation/wheeler)
(with some small modifications).

-}
module Text.Password.Strength (
  -- * Estimating Guesses
  score,
  Score(..),

  -- * Calculating Password Strength
  strength,
  Strength(..),

  -- * Default Configuration
  en_US

  ) where

--------------------------------------------------------------------------------
-- Library Imports:
import Data.Text (Text)
import Data.Time.Calendar (Day)
import Data.Aeson (ToJSON(..), (.=))
import qualified Data.Aeson as Aeson

--------------------------------------------------------------------------------
-- Project Imports:
import Text.Password.Strength.Internal.Config
import qualified Text.Password.Strength.Internal.Search as Search

--------------------------------------------------------------------------------
-- | A score is an estimate of the number of guesses it would take to
-- crack a password.
newtype Score = Score { Score -> Integer
getScore :: Integer }
  deriving (Int -> Score -> ShowS
[Score] -> ShowS
Score -> String
(Int -> Score -> ShowS)
-> (Score -> String) -> ([Score] -> ShowS) -> Show Score
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
(Score -> Score -> Bool) -> (Score -> Score -> Bool) -> Eq Score
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
Eq Score
-> (Score -> Score -> Ordering)
-> (Score -> Score -> Bool)
-> (Score -> Score -> Bool)
-> (Score -> Score -> Bool)
-> (Score -> Score -> Bool)
-> (Score -> Score -> Score)
-> (Score -> Score -> Score)
-> Ord 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
$cp1Ord :: Eq Score
Ord)

instance ToJSON Score where
  toJSON :: Score -> Value
toJSON Score
s = [Pair] -> Value
Aeson.object
    [ Text
"score"    Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Score -> Integer
getScore Score
s
    , Text
"strength" Text -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Strength -> String
forall a. Show a => a -> String
show (Score -> Strength
strength Score
s)
    ]

--------------------------------------------------------------------------------
-- | Estimate the number of guesses an attacker would need to make to
-- crack the given password.
score :: Config -- ^ Which dictionaries, keyboards, etc. to use.
      -> Day    -- ^ Reference day for date matches (should be current day).
      -> Text   -- ^ The password to score.
      -> Score  -- ^ Estimate.
score :: Config -> Day -> Text -> Score
score Config
c Day
d Text
p = Integer -> Score
Score (Integer -> Score) -> Integer -> Score
forall a b. (a -> b) -> a -> b
$ Graph -> Integer
Search.score (Config -> Day -> Text -> Graph
Search.graph Config
c Day
d Text
p)

--------------------------------------------------------------------------------
-- | Measurement of password strength.
data Strength
  = Risky
    -- ^ Too guessable: risky password. (guesses < \(10^{3}\))

  | Weak
    -- ^ Very guessable: protection from throttled online
    -- attacks. (guesses < \(10^{6}\))

  | Moderate
    -- ^ Somewhat guessable: protection from unthrottled online
    -- attacks. (guesses < \(10^{8}\))

  | Safe
    -- ^ Safely unguessable: moderate protection from offline
    -- slow-hash scenario. (guesses < \(10^{10}\))

  | Strong
    -- ^ Very unguessable: strong protection from offline slow-hash
    -- scenario. (guesses >= \(10^{10}\))

  deriving (Int -> Strength -> ShowS
[Strength] -> ShowS
Strength -> String
(Int -> Strength -> ShowS)
-> (Strength -> String) -> ([Strength] -> ShowS) -> Show Strength
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]
(Int -> ReadS Strength)
-> ReadS [Strength]
-> ReadPrec Strength
-> ReadPrec [Strength]
-> Read 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
(Strength -> Strength -> Bool)
-> (Strength -> Strength -> Bool) -> Eq Strength
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
Eq Strength
-> (Strength -> Strength -> Ordering)
-> (Strength -> Strength -> Bool)
-> (Strength -> Strength -> Bool)
-> (Strength -> Strength -> Bool)
-> (Strength -> Strength -> Bool)
-> (Strength -> Strength -> Strength)
-> (Strength -> Strength -> Strength)
-> Ord 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
$cp1Ord :: Eq Strength
Ord, Int -> Strength
Strength -> Int
Strength -> [Strength]
Strength -> Strength
Strength -> Strength -> [Strength]
Strength -> Strength -> Strength -> [Strength]
(Strength -> Strength)
-> (Strength -> Strength)
-> (Int -> Strength)
-> (Strength -> Int)
-> (Strength -> [Strength])
-> (Strength -> Strength -> [Strength])
-> (Strength -> Strength -> [Strength])
-> (Strength -> Strength -> Strength -> [Strength])
-> Enum 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
Strength -> Strength -> Bounded Strength
forall a. a -> a -> Bounded a
maxBound :: Strength
$cmaxBound :: Strength
minBound :: Strength
$cminBound :: Strength
Bounded)

--------------------------------------------------------------------------------
-- | Calculate the strength of a password given its score.
strength :: Score -> Strength
strength :: Score -> Strength
strength (Score Integer
n)
  | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ ( Int
3 :: Int) = Strength
Risky
  | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ ( Int
6 :: Int) = Strength
Weak
  | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ ( Int
8 :: Int) = Strength
Moderate
  | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
10 :: Int) = Strength
Safe
  | Bool
otherwise            = Strength
Strong