I'm using StableNames to have a notion of function equality, and I'm running into problems when using monadic functions.

Consider the code below, file Test.hs

import System.Mem.StableName
import Control.Monad.State

eq :: a -> b -> IO Bool
eq a b = do
             pa <- makeStableName a
             pb <- makeStableName b
             return (hashStableName pa == hashStableName pb)

successor :: (Num a, Monad m) => a -> m a
successor n = return (n+1)

main :: IO () 
main = do 
       b1 <- eq (successor :: Int -> Maybe Int) (successor :: Int -> Maybe Int)       
       b2 <- eq (successor :: Int -> State Int Int) (successor :: Int -> State Int Int)
       print (show b1 ++ " " ++ show b2)

Running the code into ghci the result is "False False". There is some old post saying that this is due to the dictionary-passing style for typeclasses, and compiling with optimizations improves the situation.

Compiling with ghc --make -O Tests.hs and running the program, the result is "True True", which is what I expect.
However, if I change main to be like the following:

main :: IO () 
main = do        
       b2 <- eq (successor :: Int -> State Int Int) (successor :: Int -> State Int Int)
       b1 <- eq (successor :: Int -> Maybe Int) (successor :: Int -> Maybe Int)       
       print (show b1 ++ " " ++ show b2)

i.e. just changing the sequential order, and then compiling again with the same command, I get "True False", which is very confusing for me.
Similar situations happens when using the state monad transformer, and manually built variations of it. 

It sounds the problem is with hidden closures created somewhere that do not point to the same memory locations, so StableNames yields false for that cases, but it is not clear to me under what circumstances this situation happens. Is there other way to get some approximation of function equality? or a way to "configure" the behavior of StableNames in presence of class constraints?

I'm using the latests Haskell Platform on OS X Lion, btw.

Thanks

--
Ismael