Skip to content

Commit

Permalink
feature(src): Add genPasswords/genPasswords' functions
Browse files Browse the repository at this point in the history
  • Loading branch information
sgillespie committed Mar 18, 2024
1 parent 3f66cec commit 3df3473
Show file tree
Hide file tree
Showing 4 changed files with 66 additions and 9 deletions.
11 changes: 3 additions & 8 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,11 +97,8 @@ passwords (CommonOpts {..}) (WordOpts {..}) gen = do
optExactWords = Fmt.ExactNumberWords <$> optNumber
}

pure $ fst $ usingPass gen (genPasswords genOpts formatOpts)
(res, _) = usingPass gen (genPasswords genOpts)

genPasswords :: RandomGen gen => GenPasswordOpts -> Fmt.FormatOpts -> Pass gen Text
genPasswords genOpts formatOpts = do
res <- sequence $ repeat (genPassword genOpts)
pure (Fmt.formatWords formatOpts res)

passphrases :: RandomGen gen => CommonOpts -> PhraseOpts -> gen -> IO Text
Expand All @@ -125,11 +122,9 @@ passphrases (CommonOpts {..}) (PhraseOpts {..}) gen = do
optExactWords = Fmt.ExactNumberWords <$> optNumber
}

let (res, _) = usingPass gen $ do
words' <- genPassphrase genOpts
pure (Fmt.formatWords formatOpts words')
(res, _) = usingPass gen (genPassphrase genOpts)

pure res
pure (Fmt.formatWords formatOpts res)

execParser' :: ParserInfo a -> IO a
execParser' info' =
Expand Down
2 changes: 2 additions & 0 deletions src/Data/Gibberish.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,8 @@ module Data.Gibberish

-- * Password/phrase generation
genPassword,
genPasswords,
genPasswords',
genPassphrase,
genPassphrase',

Expand Down
10 changes: 10 additions & 0 deletions src/Data/Gibberish/Gen/Pass.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@

module Data.Gibberish.Gen.Pass
( genPassword,
genPasswords,
genPasswords',
genPassphrase,
genPassphrase',
) where
Expand Down Expand Up @@ -49,6 +51,14 @@ genPassword' opts@(GenPasswordOpts {..}) = do

Word <$> transform pass

-- | Generate passwords with the given options. /Warning:/ Do not use with the IO monad,
-- instead use `genPasswords'`
genPasswords :: MonadRandom m => GenPasswordOpts -> m [Word]
genPasswords = sequence . repeat . genPassword

genPasswords' :: MonadRandom m => GenPasswordOpts -> Int -> m [Word]
genPasswords' = flip replicateM . genPassword

-- | Generate a passphrase with the given options. /Warning:/ Do not use with the IO monad,
-- instead use `genPassphrash'`
genPassphrase :: MonadRandom m => GenPassphraseOpts -> m [Word]
Expand Down
52 changes: 51 additions & 1 deletion test/Data/Gibberish/Gen/PassSpec.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Data.Gibberish.Gen.PassSpec (spec) where

import Data.Gibberish.Gen.Pass (genPassphrase, genPassphrase', genPassword)
import Data.Gibberish.Gen.Pass
import Data.Gibberish.Gen.Trigraph (Language (..), loadTrigraph)
import Data.Gibberish.Monad.Pass (usingPass, usingPassT)
import Data.Gibberish.Types
Expand Down Expand Up @@ -183,6 +183,56 @@ spec = do
cover 10 "has at least one special" $
Text.length (Text.filter (`elem` allSymbols) pass) > 1

describe "genPasswords" $ do
it "passwords have the correct length" $ hedgehog $ do
trigraph <- forAll genTrigraph
opts <- forAll Gen.genPasswordOpts
randomGen <- forAll Gen.stdGen

let opts' = opts {woptsTrigraph = trigraph}

let (passes, _) = usingPass randomGen (genPasswords opts')
annotateShow passes

listSize <- forAll $ Gen.int (Range.linear 1 50)

let shouldHaveLength (Word w) = (Text.length w ==)

assert $
not (null passes)
&& all (`shouldHaveLength` woptsLength opts') (take listSize passes)

describe "genPasswords'" $ do
it "passwords have the correct length" $ hedgehog $ do
trigraph <- forAll genTrigraph
opts <- forAll Gen.genPasswordOpts
numberWords <- forAll $ Gen.int (Range.linear 1 100)
randomGen <- forAll Gen.stdGen

let opts' = opts {woptsTrigraph = trigraph}

(passes, _) <- liftIO $ usingPassT randomGen (genPasswords' opts' numberWords)
annotateShow passes

let shouldHaveLength (Word w) = (Text.length w ==)

assert $
not (null passes)
&& all (`shouldHaveLength` woptsLength opts') passes

it "has the correct number of passwords" $ hedgehog $ do
trigraph <- forAll genTrigraph
opts <- forAll Gen.genPasswordOpts
numberWords <- forAll $ Gen.int (Range.linear 1 100)
randomGen <- forAll Gen.stdGen

let opts' = opts {woptsTrigraph = trigraph}

(passes, _) <- liftIO $ usingPassT randomGen (genPasswords' opts' numberWords)
annotateShow passes

length passes === numberWords

describe "genPassphrase" $ do
it "words have correct length" $ hedgehog $ do
trigraph <- forAll genTrigraph
Expand Down

0 comments on commit 3df3473

Please sign in to comment.