2
votes

I'm something of a Haskell beginner. I'd like to know why the following isn't working:

import System.Random

simulator :: (RandomGen g) => g -> Double -> (Bool, g)
simulator gen p = (x <= p, gen2)
    where (x, gen2) = random gen :: (Double, g)

The error I get is:

• Couldn't match type ‘g’ with ‘g1’
  ‘g’ is a rigid type variable bound by
    the type signature for:
      simulator :: forall g. RandomGen g => g -> Double -> (Bool, g)
    at simulate.hs:10:1-54
  ‘g1’ is a rigid type variable bound by
    an expression type signature:
      forall g1. (Double, g1)
    at simulate.hs:12:37-47
  Expected type: (Double, g1)
    Actual type: (Double, g)
• In the expression: random gen :: (Double, g)
  In a pattern binding: (x, gen2) = random gen :: (Double, g)
  In an equation for ‘simulator’:
      simulator gen p
        = (x <= p, gen2)
        where
            (x, gen2) = random gen :: (Double, g)
• Relevant bindings include
    gen :: g (bound at simulate.hs:11:11)
    simulator :: g -> Double -> (Bool, g) (bound at simulate.hs:11:1)

     where (x, gen2) = random gen :: (Double, g)

It seems Haskell is unable to match the separate instances of the type variable g. Any clues?

1

1 Answers

5
votes

The issue with your code is on the last line, the one with the :: (Double, g) type annotation. As written, you clearly expect the g in that annotation to refer to the same g as the one in your type signature for simulator. This is a completely reasonable expectation, but unfortunately, it isn’t true—by default, two type variables with the same name in different type annotations are distinct. (This is why, in the error message, GHC implicitly renames your second g to g1.)

Fortunately, you can fix this. GHC comes with a language extension you can turn on called ScopedTypeVariables. If you add {-# LANGUAGE ScopedTypeVariables #-} to the top of your module, this will enable the extension. However, this still won’t fix your program, since ScopedTypeVariables only applies to variables explicitly bound using forall. Therefore, you need to both add the LANGUAGE pragma and introduce an explicit use of forall:

{-# LANGUAGE ScopedTypeVariables #-}

import System.Random

simulator :: forall g. (RandomGen g) => g -> Double -> (Bool, g)
simulator gen p = (x <= p, gen2)
  where (x, gen2) = random gen :: (Double, g)

These incantations are enough to get GHC to do what you initially intended.

That said, your original program would actually also compile if you just dropped the second type signature and left ScopedTypeVariables disabled, since GHC would infer the appropriate type for gen2 based on how it’s used. Whether you want the type signature or not is personal preference, but it’s still useful to understand what’s going on and how to fix it for situations where you decide you really do want the signature, or where the signature is actually necessary.