{-# LANGUAGE OverloadedStrings #-} -- | Diceware dictionary interface module Alea.Diceware where import Data.Monoid ((<>)) import Data.List (intersect, elemIndex) import Data.Text (Text, pack) import System.Random import qualified Data.Text as T -- | Diceware dictionary alias type Diceware = [Text] -- | @Randindices n k@ produces @k@ random indices of words -- to be extracted from a 'Diceware' of @n@ words randIndices :: Int -> Int -> IO [Int] randIndices n k = take k <$> randomRs (0, n-1) <$> newStdGen -- | Parse file content to a Diceware parseDiceware :: Text -> Diceware parseDiceware = map (last . T.splitOn " ") . T.lines -- | Lookup word with dice index readDiceware :: Diceware -> Int -> Text readDiceware d n = pack (show n) <> " -> " <> maybe "Does not exists" (d !!) (fromDice n) -- | Lookup word with linear index readDiceware' :: Diceware -> Int -> Text readDiceware' d n = d !! n -- | Dice numbers to numbers -- -- > fromDice 11121 == Just 6 fromDice :: Int -> Maybe Int fromDice n = elemIndex n (filter isDice [11111..66666]) where isDice = null . (intersect "0789") . show