<div dir="ltr">Hi,<br><br>I've been playing around with `System.Mem.StableName` and `hashStableName` and<br>stumbled across a behavior that seems to be rather weird.<br><br>First of all the documentation of `hashStableName` says the following:<br><br>The Int returned is not necessarily unique; several StableNames may map to the<br>same Int (in practice however, the chances of this are small, so the result of<br>hashStableName makes a good hash key).<br><br>OK, sounds fine, let's put this to the test. So I wrote a little program.<br><br><br>    module Main where<br><br>    import Control.Monad<br><br>    import System.Mem.StableName<br>    import System.Environment<br><br>    main :: IO ()<br>    main = do<br>      args <- getArgs<br>      res <- forM [0..10000] $ \i -> do<br>        x <- makeStableName i<br>        let h' = hashStableName x<br>        unless (null args) $<br>          print h'<br>        return h'<br><br>      putStrLn "---------------------------"<br>      print $ minimum res<br>      print $ maximum res<br><br>Running this program without an argument only prints aus the minimum and maximum<br>hash values that where produced. So surprises here:<br><br>    $ ./Test<br>    ---------------------------<br>    1<br>    10000<br><br>Here is how things get a bit weird when I make the progam print out the hash<br>values while they are being produced I get a completely different result. Not<br>only that but I get a whole lot of hash collisions, since the hashes produced<br>only seem to be within the range of 1 and 260.<br><br>    $ ./Test print<br>    [...]<br>    128<br>    127<br>    126<br>    125<br>    124<br>    123<br>    122<br>    121<br>    120<br>    119<br>    118<br>    117<br>    116<br>    115<br>    114<br>    ---------------------------<br>    1<br>    260<br><br>Am I missing something fundamental here, because this behavior seems to be<br>rather confusing.<br><br>Kind regards,<br>raichoo<br><br></div>