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