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
Synopsis
- data GenOptions = GenOptions {
- genCapitals :: Bool
- genDigits :: Bool
- genSpecials :: Bool
- genOptions :: GenOptions
- genPassword :: RandomGen g => Int -> GenOptions -> g -> (String, g)
- genPasswords :: RandomGen g => Int -> Int -> GenOptions -> g -> ([String], g)
- newPassword :: RandomGen g => Int -> GenOptions -> g -> String
- newPasswords :: RandomGen g => Int -> Int -> GenOptions -> g -> [String]
- mkPassword :: MonadRandom m => Int -> GenOptions -> m String
- mkPasswords :: MonadRandom m => Int -> Int -> GenOptions -> m [String]
- genPassphrase :: RandomGen g => Int -> Int -> Int -> GenOptions -> g -> ([String], g)
- newPassphrase :: RandomGen g => Int -> Int -> Int -> GenOptions -> g -> [String]
- mkPassphrase :: MonadRandom m => Int -> Int -> Int -> GenOptions -> m [String]
- first2 :: MonadRandom m => m String
- lastN :: MonadRandom m => Int -> String -> m String
- next :: MonadRandom m => String -> m Char
- capitalizeR :: MonadRandom m => Int -> String -> m String
- capitalize1 :: MonadRandom m => Int -> String -> m String
- numerizeR :: MonadRandom m => Int -> String -> m String
- numerize1 :: MonadRandom m => Int -> String -> m String
- specializeR :: MonadRandom m => Int -> String -> m String
- specialize1 :: MonadRandom m => Int -> String -> m String
Data Types
data GenOptions Source #
Options for generating passwords or passphrases. Do not use
this constructor directly. Instead use genOptions
to construct
an instance.
GenOptions | |
|
Instances
Eq GenOptions Source # | |
Defined in Data.Elocrypt (==) :: GenOptions -> GenOptions -> Bool # (/=) :: GenOptions -> GenOptions -> Bool # | |
Show GenOptions Source # | |
Defined in Data.Elocrypt showsPrec :: Int -> GenOptions -> ShowS # show :: GenOptions -> String # showList :: [GenOptions] -> ShowS # |
genOptions :: GenOptions Source #
Default options for generating passwords or passphrases. This is
the preferred way to construct GenOptions
.
Random password generators
:: RandomGen g | |
=> Int | password length |
-> GenOptions | options |
-> g | random generator |
-> (String, g) |
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 genOptions `liftM` getStdGen
:: RandomGen g | |
=> Int | password length |
-> Int | number of passwords |
-> GenOptions | options |
-> 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 genOptionsliftM
getStdGen
:: RandomGen g | |
=> Int | password length |
-> GenOptions | options |
-> g | random generator |
-> String |
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 genOptions `liftM` getStdGen
:: RandomGen g | |
=> Int | password length |
-> Int | number of passwords |
-> GenOptions | options |
-> 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 genOptions liftM
getStdGen
:: MonadRandom m | |
=> Int | password length |
-> GenOptions | options |
-> 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 genOptions) `liftM` getStdGen
:: MonadRandom m | |
=> Int | password length |
-> Int | number of passwords |
-> GenOptions | options |
-> 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 genOptions) `liftM` getStdGen
Random passphrase generators
:: RandomGen g | |
=> Int | number of words |
-> Int | minimum word length |
-> Int | maximum word length |
-> GenOptions | options |
-> 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 6 10 genOptions `liftM` getStdGen
:: RandomGen g | |
=> Int | number of words |
-> Int | minimum word length |
-> Int | maximum word length |
-> GenOptions | options |
-> 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 |
-> GenOptions | options |
-> 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.
lastN :: MonadRandom m => Int -> String -> m String Source #
Generate the last n characters using previous two characters
and their trigraph
:: MonadRandom m | |
=> String | the prefix |
-> m Char |
Generate a random character based on the previous two characters and
their trigraph
capitalizeR :: MonadRandom m => Int -> String -> m String Source #
Randomly capitalize at least 1 character. Additional characters capitalize at a probability of 1/12
capitalize1 :: MonadRandom m => Int -> String -> m String Source #
Randomly capitalize 1 character
numerizeR :: MonadRandom m => Int -> String -> m String Source #
Randomly numerize at least 1 character. Additional characters numerize at a probability of 1/6
specializeR :: MonadRandom m => Int -> String -> m String Source #
Randomly make at least 1 character a symbol. Additional characters specialize at a probability of 1/4
specialize1 :: MonadRandom m => Int -> String -> m String Source #