Copyright | (c) Sean Gillespie 2015 |
---|---|
License | OtherLicense |
Maintainer | Sean Gillespie <sean@mistersg.net> |
Stability | Experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Generate easy-to-remember, hard-to-guess passwords
- genPassword :: RandomGen g => Int -> Bool -> g -> (String, g)
- genPasswords :: RandomGen g => Int -> Int -> Bool -> g -> ([String], g)
- newPassword :: RandomGen g => Int -> Bool -> g -> String
- newPasswords :: RandomGen g => Int -> Int -> Bool -> g -> [String]
- mkPassword :: MonadRandom m => Int -> Bool -> m String
- mkPasswords :: MonadRandom m => Int -> Int -> Bool -> m [String]
- genPassphrase :: RandomGen g => Int -> Int -> Int -> g -> ([String], g)
- newPassphrase :: RandomGen g => Int -> Int -> Int -> g -> [String]
- mkPassphrase :: MonadRandom m => Int -> Int -> Int -> m [String]
- alphabet :: [Char]
- first2 :: MonadRandom m => m String
- next :: MonadRandom m => String -> m Char
- lastN :: MonadRandom m => Int -> String -> m String
Random password generators
Generate a password using the generator g, returning the result and the updated generator.
-- Generate a password of length 10 using the system generator myGenPassword :: IO (String, StdGen) myGenPassword = genPassword 10 True `liftM` getStdGen
:: RandomGen g | |
=> Int | password length |
-> Int | number of passwords |
-> Bool | include capitals? |
-> g | random generator |
-> ([String], g) |
Plural version of genPassword. Generates an infinite list of passwords using the generator g, returning the result and the updated generator.
-- Generate 10 passwords of length 10 using the system generator myGenPasswords :: IO ([String], StdGen) myGenPasswords = ((ls, g) -> (ls, g)liftM
genPasswords 10 10 TrueliftM
getStdGen
Generate a password using the generator g, returning the result.
-- Generate a password of length 10 using the system generator myNewPassword :: IO String myNewPassword = newPassword 10 True `liftM` getStdGen
:: RandomGen g | |
=> Int | password length |
-> Int | number of passwords |
-> Bool | include capitals? |
-> g | random generator |
-> [String] |
Plural version of newPassword. Generates an infinite list of passwords using the generator g, returning the result
-- Generate 10 passwords of length 10 using the system generator
myNewPasswords :: IO [String]
myNewPasswords = genPasswords 10 10 True liftM
getStdGen
:: MonadRandom m | |
=> Int | password length |
-> Bool | include capitals? |
-> m String |
Generate a password using the MonadRandom m. MonadRandom is exposed here for extra control.
-- Generate a password of length 10 using the system generator myPassword :: IO String myPassword = evalRand (mkPassword 10 True) `liftM` getStdGen
:: MonadRandom m | |
=> Int | password length |
-> Int | number of passwords |
-> Bool | include capitals? |
-> m [String] |
Plural version of mkPassword. Generate an infinite list of passwords using the MonadRandom m. MonadRandom is exposed here for extra control.
-- Generate an list of length 20 with passwords of length 10 using the system generator myMkPasswords :: IO [String] myMkPasswords = evalRand (mkPasswords 10 20 True) `liftM` getStdGen
Random passphrase generators
:: RandomGen g | |
=> Int | number of words |
-> Int | minimum word length |
-> Int | maximum word length |
-> g | random generator |
-> ([String], g) |
Generate a passphrase using the generator g, returning the result and the updated generator.
-- Generate a passphrase of 10 words, each having a length between 6 and 12, -- using the system generator myGenPassphrase :: IO (String, StdGen) myGenPassphrase = genPassword 10 True `liftM` getStdGen
:: RandomGen g | |
=> Int | number of words |
-> Int | minimum word length |
-> Int | maximum word length |
-> g | random generator |
-> [String] |
Generate a passphrase using the generator g, returning the result.
-- Generate a passphrase of 10 words, each having a length between 6 an 12, -- using the system generator. myNewPassphrase :: IO String myNewPassphrase = newPassphrase 10 6 12 `liftM` getStdGen
:: MonadRandom m | |
=> Int | number of words |
-> Int | minimum word length |
-> Int | maximum word length |
-> m [String] |
Generate a finite number of words of random length (between min
and max
chars)
using the MonadRandom m. MonadRandom is exposed here for extra control.
-- Generate a passphrase of 10 words, each having a length between 6 and 12. myPassphrase :: IO String myPassphrase = evalRand (mkPassphrase 10 6 12) `liftM` getStdGen
Internal
first2 :: MonadRandom m => m String Source #
Generate two random characters. Uses trigragh
to generate a weighted list.