Skip to content

Instantly share code, notes, and snippets.

@twopoint718
Created June 3, 2018 18:05
Show Gist options
  • Select an option

  • Save twopoint718/f398cf6a3bcfb6ad5ce8bd58525c5261 to your computer and use it in GitHub Desktop.

Select an option

Save twopoint718/f398cf6a3bcfb6ad5ce8bd58525c5261 to your computer and use it in GitHub Desktop.
Select a random element of a bounded, enumerable datatype. If you know that a datatype has a way to generate a list of items, a way to determine the minimum and maximum values, then you should be able to select a random element from that datatype.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module RandomEnum where
import System.Random
enumRandomR :: (RandomGen g, Enum e) => (e, e) -> g -> (e, g)
enumRandomR (lo,hi) gen =
let
(int, gen') = randomR (fromEnum lo, fromEnum hi) gen
in
(toEnum int, gen')
enumRandom :: forall g e. (RandomGen g, Enum e) => g -> (e, g)
enumRandom gen =
let
randomInt :: RandomGen g => g -> (Int, g)
randomInt = random
(int, gen') = randomInt gen
int' = int `mod` length ([toEnum 0 ..] :: [e])
in
(toEnum int', gen')
newtype Enum' a = Enum' a
deriving (Bounded, Enum, Show)
instance (Enum a, Bounded a) => Random (Enum' a) where
random = enumRandom
randomR = enumRandomR
@twopoint718
Copy link
Author

twopoint718 commented Jun 3, 2018

Using this is as simple as:

module Main where

import System.Random (randomIO)
import RandomEnum (Enum'(..))

data Direction = North | East | South | West
  deriving (Enum, Bounded, Show)
  
showDirection :: Direction -> String
showDirection direction = case direction of
  North -> "North"
  East -> "East"
  South -> "South"
  West -> "West"

main :: IO ()
main = do
  Enum' direction <- randomIO
  putStrLn (showDirection direction)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment