Skip to content

Instantly share code, notes, and snippets.

@kritzcreek
Last active May 24, 2021 18:36
Show Gist options
  • Star 18 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save kritzcreek/ebc1a9340b946e68d32de880efe1f644 to your computer and use it in GitHub Desktop.
Save kritzcreek/ebc1a9340b946e68d32de880efe1f644 to your computer and use it in GitHub Desktop.
Collections of random numbers in PureScript

Generating collections of random numbers in PureScript

A problem that I've seen beginners run into in Haskell or PureScript a couple of times now is how to generate a List of random numbers. It's a common requirement for little games (which make for great first projects) to generate these, and it definitely seems to be a stumbling block.

Why are random numbers hard?

Randomness is considered a side effect in purely functional languages, which means that to generate them you usually need access to Eff/IO, which in turn means we need to deal with Monads. And while generating a single random number is usually pretty easy with do-notation, the typical intuition beginners have built when going from single values to a collection is to use map, but that fails.

Type-Directed-Search to the rescue

One of my favourite features of PureScript is Type-Directed-Search, and when the list of random numbers question appeared in Slack earlier this evening, I decided to see if it could help solve the problem:

First I want to generate a single random number in a given range (1 to 4). Now I could turn to Google or Pursuit and start searching, but in PureScript we can use typed holes. I used try.purescript.org to get quick feedback, and you can easily type all of the code in this Post into it.

module Main where

import Prelude
import Control.Monad.Eff.Console (logShow)
import TryPureScript (render, withConsole)

main = render =<< withConsole do
    n <- ?x 1 4
    pure unit

To which the compiler replies with:

  Hole 'x' has the inferred type

    Int
    -> Int
       -> Eff
            ( dom :: DOM
            | t0
            )
            t1

  You could substitute the hole with one of these values:

    Control.Monad.Eff.Random.randomInt      :: forall e.
                                                 Int
                                                 -> Int
                                                    -> Eff
                                                         ( random :: RANDOM
                                                         | e
                                                         )
                                                         Int
    Data.Generic.Rep.Bounded.genericBottom  :: forall a rep. Generic a rep => GenericBottom rep => a
    Data.Generic.Rep.Bounded.genericTop     :: forall a rep. Generic a rep => GenericTop rep => a
    Data.Generic.Rep.Monoid.genericMempty   :: forall a rep. Generic a rep => GenericMonoid rep => a
    Partial.crash                           :: forall a. Partial => a
    Unsafe.Coerce.unsafeCoerce              :: forall a b. a -> b


in value declaration main

where t0 is an unknown type
      t1 is an unknown type

I'll abbreviate the compiler messages from here on out. The compiler finds Control.Monad.Eff.Random.randomInt for us. That's not quite what we wanted though, we want a List of random numbers, so we'll put in a typed hole and apply 20 to it, since we want a function that repeats the given effect 20 times, to see if there is a function with the signature we're looking for.

module Main where

import Prelude
import Control.Monad.Eff.Random (randomInt)
import TryPureScript (render, withConsole)

main = render =<< withConsole do
    randoms <- ?x 20 (randomInt 1 4)
    pure unit

And the compiler finds

Data.Unfoldable.replicateA 
  :: forall m f a . Applicative m => Unfoldable f => Traversable f => Int -> m a -> m (f a)

for us (kind of a crazy type). If we put that in and print our results though, we end up with an error:

No type class instance was found for

    Data.Show.Show (t4 Int)

t4 is a type variable, which should be a hint for us that we need a provide a type annotation to decide which Unfoldable structure we want our random numbers to go into (the f in replicateA's type signature). This is actually one of PureScript's strengths, because it means we can use replicateA to generate Arrays, Lists, Trees, ... without having to duplicate any code.

Our final result

This prints an Array of 20 random numbers whenever you refresh the browser or make an edit to the source code.

module Main where

import Prelude
import Data.Unfoldable (replicateA)
import Control.Monad.Eff.Console (logShow)
import Control.Monad.Eff.Random (randomInt)
import TryPureScript (render, withConsole)

main = render =<< withConsole do
    randoms :: Array Int <- replicateA 20 (randomInt 1 4)
    logShow randoms
@arecvlohe
Copy link

Nice gist, this was very helpful and informative!

@simonolander
Copy link

simonolander commented Dec 23, 2019

Nice! You also inadvertently also thought me about type holes in purescript.

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