-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Generate easy-to-remember, hard-to-guess passwords -- -- Generates pronounceable, hard-to-guess passwords--as hard as Vince -- Carter's knee cartilage is. @package elocrypt @version 2.1.0 -- | Generate a letter frequency trigraph, based on a dictionary module Data.Elocrypt.Trigraph -- | Search for the character frequencies and return a weighted list findWeights :: String -> Maybe [(Char, Rational)] -- | Search for the character frequencies based on the first a two-letter -- string findFrequency :: String -> Maybe [Rational] -- | Fix frequencies if they are all 0, since MonadRandom prohibits this. -- In this case, use all 1s to give every item an equal weight defaultFrequencies :: [Rational] -> [Rational] -- | A map of character frequencies, based on a dictionary. The key is a -- two-letter string, and the value is a list of probabilities (a-z). -- It's form is: -- --
--   [("aa", [2,0,3,0,0,0,1,0,0,0,0,1,1,1,0,0,0,3,2,0,0,0,0,0,0,0]),
--   ...
--    ("zz", [7,0,0,0,1,0,0,0,7,0,0,17,0,0,2,0,0,0,0,0,0,0,1,0,5,0])]
--   
frequencies :: [(String, [Rational])] module Data.Elocrypt.Utils -- | A mapping from letters to numbers that look like them numeralConversions :: Map Char [Char] -- | A mapping from letters to symbols that look like them symbolConversions :: Map Char [Char] -- | Map a letter to one or more digits, if possible toDigit :: Char -> String -- | Map a letter to one or more symbols, if possible toSymbol :: Char -> String -- | Selects special characters isSymbol :: Char -> Bool -- | Randomly update characters at the specified probability updateR :: MonadRandom m => (Char -> m Char) -> Rational -> String -> m String -- | Update character at position pos update1 :: Monad m => (Char -> m Char) -> String -> Int -> m String -- | Generate easy-to-remember, hard-to-guess passwords module Data.Elocrypt -- | Options for generating passwords or passphrases. Do not use this -- constructor directly. Instead use genOptions to construct an -- instance. data GenOptions GenOptions :: Bool -> Bool -> Bool -> GenOptions [genCapitals] :: GenOptions -> Bool [genDigits] :: GenOptions -> Bool [genSpecials] :: GenOptions -> Bool -- | Default options for generating passwords or passphrases. This is the -- preferred way to construct GenOptions. genOptions :: GenOptions -- | 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
--   
--   
genPassword :: RandomGen g => Int -> GenOptions -> g -> (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 genOptions liftM getStdGen
--   
genPasswords :: RandomGen g => Int -> Int -> GenOptions -> g -> ([String], g) -- | 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
--   
--   
newPassword :: RandomGen g => Int -> GenOptions -> g -> 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
--   
newPasswords :: RandomGen g => Int -> Int -> GenOptions -> g -> [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
--   
--   
mkPassword :: MonadRandom m => Int -> GenOptions -> 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
--   
mkPasswords :: MonadRandom m => Int -> Int -> GenOptions -> m [String] -- | 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
--   
--   
genPassphrase :: RandomGen g => Int -> Int -> Int -> GenOptions -> g -> ([String], g) -- | 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
--   
--   
newPassphrase :: RandomGen g => Int -> Int -> Int -> GenOptions -> g -> [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
--   
--   
mkPassphrase :: MonadRandom m => Int -> Int -> Int -> GenOptions -> m [String] -- | Generate two random characters. Uses trigragh to generate a -- weighted list. first2 :: MonadRandom m => m String -- | Generate the last n characters using previous two characters and their -- trigraph lastN :: MonadRandom m => Int -> String -> m String -- | Generate a random character based on the previous two characters and -- their trigraph next :: MonadRandom m => String -> m Char -- | Randomly capitalize at least 1 character. Additional characters -- capitalize at a probability of 1/12 capitalizeR :: MonadRandom m => Int -> String -> m String -- | Randomly capitalize 1 character capitalize1 :: MonadRandom m => Int -> String -> m String -- | Randomly numerize at least 1 character. Additional characters numerize -- at a probability of 1/6 numerizeR :: MonadRandom m => Int -> String -> m String numerize1 :: MonadRandom m => Int -> String -> m String -- | Randomly make at least 1 character a symbol. Additional characters -- specialize at a probability of 1/4 specializeR :: MonadRandom m => Int -> String -> m String specialize1 :: MonadRandom m => Int -> String -> m String instance GHC.Show.Show Data.Elocrypt.GenOptions instance GHC.Classes.Eq Data.Elocrypt.GenOptions