{-# LANGUAGE DeriveDataTypeable, RecordWildCards #-} import System.IO import System.Console.CmdArgs import Control.Monad (when) import Paths_alea (getDataFileName) import Alea.Diceware import Alea.Random _NAME = "Alea" _VERSION = "0.3.0" _INFO = _NAME ++ " version " ++ _VERSION _ABOUT = "a diceware passphrase generator" _COPYRIGHT = "(C) Michele Guerini Rocco 2014" data Args = Args { interactive :: Bool , dictionary :: FilePath , phraseLength :: Int , phrases :: Int } deriving (Data, Typeable, Show, Eq) progArgs :: Args progArgs = Args { interactive = def &= help "Manually insert numbers" , dictionary = def &= help "Specify dictionary file path" , phraseLength = def &= help "Number of words in a passphrase" , phrases = def &= help "Number of passphrases to generate" } getProgArgs :: IO Args getProgArgs = cmdArgs $ progArgs &= versionArg [explicit, name "version", name "v", summary _INFO] &= summary (_INFO ++ ", " ++ _COPYRIGHT) &= help _ABOUT &= helpArg [explicit, name "help", name "h"] &= program _NAME main :: IO () main = getProgArgs >>= defaults >>= exec -- Assign default values to unspecified args defaults :: Args -> IO Args defaults args@Args{..} = do dictionary' <- if null dictionary then getDataFileName "dict/diceware" >>= readFile else readFile dictionary let phraseLength' = if phraseLength == 0 then 6 else phraseLength return args { dictionary = dictionary', phraseLength = phraseLength'} -- Main function exec :: Args -> IO () exec args@Args{..} = if interactive then interact (unlines . map dice . lines) else do randWords dictSize phraseLength >>= putStrLn . unwords . map dice' when (phrases > 1) $ exec args {phrases = phrases - 1} where (dict, dictSize) = (parseDiceware dictionary, length dict) dice n = readDiceware dict (read n :: Int) dice' n = readDiceware' dict n