Skip to content

Instantly share code, notes, and snippets.

@sajith
Last active February 25, 2016 19:26
Show Gist options
  • Save sajith/fcab0146801c63647554 to your computer and use it in GitHub Desktop.
Save sajith/fcab0146801c63647554 to your computer and use it in GitHub Desktop.
make a random text token, using MonadRandom and friends
module RandomStr5 where
-- uses `MonadRandom` package
import Control.DeepSeq (force)
import Control.Monad (liftM)
import Control.Monad.Random (evalRandIO, getRandoms)
import Data.List (nub)
import Data.Text (Text, pack)
------------------------------------------------------------------------
-- TODO: Hard-coding length here (as opposed to passing length as a
-- parameter) seems to make this go ~10x faster, at least in ghci.
-- But why?
randomStr :: IO Text
randomStr = pack <$> liftM (map toChar) (makeStr 12)
where
makeStr :: Int -> IO String
makeStr len = evalRandIO $ liftM (take len) getRandoms
toChar :: Enum a => a -> Char
toChar i = chars !! (fromEnum i `mod` length chars)
chars :: String
chars = ['0'..'9'] ++ ['A'..'Z'] ++ ['a'..'z']
allUnique :: IO Bool
allUnique = do
xs <- mapM (const randomStr) [1..1000]
return (force(xs) == force(nub xs))
main :: IO ()
main = allUnique >>= print
------------------------------------------------------------------------
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment