{-# LANGUAGE RecordWildCards #-} import Control.Monad (when, forever) import Data.Text (unpack) import Options.Applicative import Alea.Diceware import Paths_alea (getDataFileName) import qualified Data.Text as T import qualified Data.Text.IO as I -- * Command line interface description -- | Program arguments record data Options = Options { interactive :: Bool , dictionary :: Maybe FilePath , phraseLength :: Int , phrases :: Int } -- | Argument parser options :: Parser Options options = Options <$> switch ( long "interactive" <> help "Manually insert numbers from a dice" ) <*> optional (option auto ( long "dictionary" <> metavar "FILEPATH" <> help "Specify dictionary filepath" )) <*> option auto ( long "length" <> value 6 <> metavar "N" <> help "Number of words in a passphrase") <*> option auto ( long "phrases" <> value 1 <> metavar "M" <> help "Number of passphrases to generate" ) -- | Program description description :: ParserInfo Options description = info (helper <*> options) ( fullDesc <> progDesc "A diceware passphrase generator" <> footer "Alea iacta est." ) -- * Program -- | Main function main :: IO () main = execParser description >>= diceware -- | Actual application diceware :: Options -> IO () diceware opts@Options{..} = do path <- case dictionary of Nothing -> getDataFileName "dict/diceware" Just x -> return x dict <- parseDiceware <$> I.readFile path let size = length dict-1 dice = readDiceware dict . read . unpack dice' = readDiceware' dict if interactive then forever (dice <$> I.getLine >>= I.putStrLn) else do indices <- randIndices size phraseLength I.putStrLn $ T.unwords (map dice' indices) when (phrases > 1) $ diceware opts {phrases = phrases - 1}