Use Data.Text

This commit is contained in:
rnhmjoj 2016-04-28 18:33:54 +02:00
parent 88864d4998
commit a2fe959036
No known key found for this signature in database
GPG Key ID: 362BB82B7E496B7C
3 changed files with 35 additions and 31 deletions

View File

@ -1,28 +1,42 @@
{-# LANGUAGE OverloadedStrings #-}
module Alea.Diceware where
import Data.Monoid ((<>))
import Data.List (intersect, elemIndex)
import Alea.List
import Data.Text (Text, pack)
import System.Random
import qualified Data.Text as T
-- Diceware dictionary type
type Diceware = [String]
-- Parse file content to a Diceware
parseDiceware :: String -> Diceware
parseDiceware x = map (last . split ' ') $ lines x
-- | Diceware dictionary alias
type Diceware = [Text]
-- Lookup word with dice index
readDiceware :: Diceware -> Int -> String
readDiceware d n = show n ++ " -> " ++
case (undice n) of
Just x -> d !! x
Nothing -> "Does not exist"
-- Lookup word with linear index
readDiceware' :: Diceware -> Int -> String
-- | Produces k random indices to be extracted
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
-- Ex. undice 11121 == Just 6
undice :: Int -> Maybe Int
undice n = elemIndex n . filter
(null . (intersect "0789") . show) $ [11111..66666]
-- | 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

View File

@ -1,10 +0,0 @@
module Alea.List where
-- Split a list into a list of lists
-- ex. split ',' "ab,cd,ef" == ["ab","cd","ef"]
split :: (Eq a) => a -> [a] -> [[a]]
split _ [] = [[]]
split delim (c:cs)
| c == delim = [] : rest
| otherwise = (c : head rest) : tail rest
where rest = split delim cs

View File

@ -61,7 +61,7 @@ diceware args@ProgArgs{..} = do
if interactive
then forever (fmap dice I.getLine >>= I.putStrLn)
else do
indices <- genIndex size phraseLength
indices <- randIndices size phraseLength
I.putStrLn $ T.unwords (map dice' indices)
when (phrases > 1) $
diceware args {phrases = phrases - 1}