Password Generator

Posted on November 10, 2024
{- |
Module      : PassGen
Description : DoD-compliant password generator
Copyright   : (c) 2024 Travis Montoya
License     : MIT

This module generates secure passwords that comply with DoD standards,
ensuring minimum length and character type requirements.

You will need: random and random-shuffle
cabal install random random-shuffle
-}
module Main where
import System.Random
import System.Random.Shuffle
import System.Environment (getArgs)

To help with abstraction we create two type synonyms Password, Length.

type Password = String
type Length   = Int

According to the DoD standards we need at minimum a 15 character password that includes 1 lowercase, 1 uppercase, 1 numeric and 1 special character.

minPassLen :: Length
minPassLen  = 15

We need at least 1 special character from here when we generate the password. This is cleaner having it outside of our genPassword function as it is a bit long to make it readable.

specialList     :: [Char]
specialList      = ['.', ',', '~', '!', '@', '#', '$', '%', '^', '&', '*', 
                    '(', ')', '_', '+', '=', '-', '[', ']', '/', '?', '>', '<']

To help abstract our our strategy we will create separate lists for each of the required character sets. The strategy is: Generate 1 numeric, 1 special, 1 uppercase, 1 lowercase (each random) and then have a combined list that we will generate the rest of the password from.

alphaLower      :: [Char]
alphaLower       = ['a'..'z']
alphaUpper      :: [Char]
alphaUpper       = ['A'..'Z']
numeric         :: [Char]
numeric          = ['1'..'9']

This is our full character set that we will randomly pull X amount of digits from where X is password length - 4 (our required items). We utilize shuffle’ to shuffle the fullList once it is all appended together. Its type is RandomGen gen => [a] -> Int -> gen -> [a] so all we have to do is pass in our list, length and a random generator and we will have a randomly shuffled list.

combinedList    :: IO [Char]
combinedList     = let fullList = alphaLower ++ alphaUpper ++ numeric ++ specialList
                       len          = length fullList
                   in shuffle' fullList len <$> newStdGen

To generate a password all we have to do is pass in a length > 15 if we pass in a length < 15 then it generates the minPassLen that we have set above.

genPassword     :: Length -> IO Password
genPassword len  = do shuffled <- combinedList
                      gen      <- newStdGen

We have bound our list combinedList which returned IO [Char] of a shuffled list to shuffled and a new random number generator to gen. Below is where we create the password we take the max of our minimum (default: 15) and whatever value we pass in to our genPassword function.

                      let len'     = max minPassLen len

The required list could use some improvement as using the same generator could reduce randomness, but for the sake of what we are using it for I think we are fine. We shuffle each list and take 1 from it, in this instance we use head to take the first shuffled item from each list.

                          required = [
                              head (shuffle' alphaLower (length alphaLower) gen),
                              head (shuffle' alphaUpper (length alphaUpper) gen),
                              head (shuffle' numeric (length numeric) gen),
                              head (shuffle' specialList (length specialList) gen)
                              ]

Now that we have our 4 required items we create a list called remaining which takes the length of our password - 4 (our required items) and the shuffled list. Then we combine our required set plus our remaning set and shuffle them to return our final password.

                          remaining = take (len' - 4) shuffled
                      return $ shuffle' (required ++ remaining) len' gen
main            :: IO ()
main             = do args <- getArgs
                      case args of
                           (len:_) -> do

Attempt to parse the command line argument as a number. If we succeed we will generate a password else we fail.

                               case reads len of
                                    [(n, "")] -> genPassword n >>= putStrLn
                                    _         -> putStrLn "Please provide a valid number"
                           []      -> putStrLn "Please provide a password length"