Data.Hashable instance generation?

Hello, A practical question about getting hashing to work. Having used Data.Map before, I wanted to try Data.HashMap.Lazy instead: ---- {-# LANGUAGE DeriveGeneric #-} import Data.HashMap.Lazy as HM import GHC.Generics (Generic) import Data.Hashable data Colour = Red | Green | Blue deriving Generic instance Hashable Colour foo = HM.insert Red ---- The data and its instance definition are directly from the web page https://hackage.haskell.org/package/hashable-1.2.1.0/docs/Data-Hashable.html. However, I det the following error: ---- GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( htest.hs, interpreted ) htest.hs:13:8: No instance for (hashable-1.1.2.5:Data.Hashable.Hashable Colour) arising from a use of `insert' Possible fix: add an instance declaration for (hashable-1.1.2.5:Data.Hashable.Hashable Colour) In the expression: insert Red In an equation for `foo': foo = insert Red Failed, modules loaded: none. ---- I do not know what is wrong or how I could fix it. Note that my Haskell had originally the older hashable-1.0.0 package, but I cabal-installed this hashable-1.1.2.5 because surfing the net suggested that it would be much better. Could it be the case that the instance goes somehow in the wrong class? -- Matti Nykänen

Hi Matti,
This example relies on generic instance deriving, which was only added
in hashable 1.2.0.0, so you need that version or later. For older
versions, you'll have to write your own Hashable instance
implementation.
Regards,
Erik
On Mon, Jun 15, 2015 at 10:05 AM, Matti Nykänen
Hello,
A practical question about getting hashing to work.
Having used Data.Map before, I wanted to try Data.HashMap.Lazy instead: ---- {-# LANGUAGE DeriveGeneric #-}
import Data.HashMap.Lazy as HM
import GHC.Generics (Generic) import Data.Hashable
data Colour = Red | Green | Blue deriving Generic
instance Hashable Colour
foo = HM.insert Red ---- The data and its instance definition are directly from the web page https://hackage.haskell.org/package/hashable-1.2.1.0/docs/Data-Hashable.html.
However, I det the following error: ---- GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( htest.hs, interpreted )
htest.hs:13:8: No instance for (hashable-1.1.2.5:Data.Hashable.Hashable Colour) arising from a use of `insert' Possible fix: add an instance declaration for (hashable-1.1.2.5:Data.Hashable.Hashable Colour) In the expression: insert Red In an equation for `foo': foo = insert Red Failed, modules loaded: none. ---- I do not know what is wrong or how I could fix it.
Note that my Haskell had originally the older hashable-1.0.0 package, but I cabal-installed this hashable-1.1.2.5 because surfing the net suggested that it would be much better. Could it be the case that the instance goes somehow in the wrong class? -- Matti Nykänen _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hello again,
Thanks to Eric, I changed my problem from generic instance deriving to explicit instance writing. Now I could evoke a more specific - and alarming! - error message:
----
import Data.HashMap.Lazy as HM
import Data.Hashable
data Colour = Red | Green | Blue deriving Enum
instance Hashable Colour where
hashWithSalt = hashUsing fromEnum
----
GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude> :l htest
[1 of 1] Compiling Main ( htest.hs, interpreted )
Ok, modules loaded: Main.
*Main> hash Red
Loading package array-0.4.0.1 ... linking ... done.
Loading package deepseq-1.3.0.1 ... linking ... done.
Loading package bytestring-0.10.0.2 ... linking ... done.
Loading package text-0.11.3.1 ... linking ... done.
Loading package hashable-1.1.2.5 ... linking ... done.
Loading package hashable-1.2.3.2 ...
GHCi runtime linker: fatal error: I found a duplicate definition for symbol
hashable_fnv_hash_offset
whilst processing object file
/home/mnykanen/.cabal/lib/hashable-1.2.3.2/ghc-7.6.3/HShashable-1.2.3.2.o
This could be caused by:
* Loading two different object files which export the same symbol
* Specifying the same object file twice on the GHCi command line
* An incorrect `package.conf' entry, causing some object to be
loaded twice.
GHCi cannot safely continue in this situation. Exiting now. Sorry.
----
So my ghci *is* indeed loading two versions of the hashtable package.
How do I solve this problem?
Please note that I am a newbie regarding Cabal and GHC internals.
--
Matti Nykänen
________________________________________
From: Erik Hesselink
Hello,
A practical question about getting hashing to work.
Having used Data.Map before, I wanted to try Data.HashMap.Lazy instead: ---- {-# LANGUAGE DeriveGeneric #-}
import Data.HashMap.Lazy as HM
import GHC.Generics (Generic) import Data.Hashable
data Colour = Red | Green | Blue deriving Generic
instance Hashable Colour
foo = HM.insert Red ---- The data and its instance definition are directly from the web page https://hackage.haskell.org/package/hashable-1.2.1.0/docs/Data-Hashable.html.
However, I det the following error: ---- GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( htest.hs, interpreted )
htest.hs:13:8: No instance for (hashable-1.1.2.5:Data.Hashable.Hashable Colour) arising from a use of `insert' Possible fix: add an instance declaration for (hashable-1.1.2.5:Data.Hashable.Hashable Colour) In the expression: insert Red In an equation for `foo': foo = insert Red Failed, modules loaded: none. ---- I do not know what is wrong or how I could fix it.
Note that my Haskell had originally the older hashable-1.0.0 package, but I cabal-installed this hashable-1.1.2.5 because surfing the net suggested that it would be much better. Could it be the case that the instance goes somehow in the wrong class? -- Matti Nykänen _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
participants (2)
-
Erik Hesselink
-
Matti Nykänen