[Haskell-cafe] deriving Data.HashTable - stack overflow

David Thomas davidleothomas at gmail.com
Thu Aug 8 20:11:25 CEST 2013


I do wish there was a compiler-checked way of specifying a minimum complete
definition.


On Thu, Aug 8, 2013 at 11:02 AM, Joey Adams <joeyadams3.14159 at gmail.com>wrote:

> On Thu, Aug 8, 2013 at 12:22 PM, Lyle Kopnicky <lists at qseep.net> wrote:
>
>> ...
>>
>>
>> So I went to the Data.Hashable page and looked up examples on how to
>> derive a Hashable instance for my datatype:
>>
>> http://hackage.haskell.org/packages/archive/hashable/latest/doc/html/Data-Hashable.html
>>
>> The problem occurs even when using the sample code on the page:
>>
>>
>> {-# LANGUAGE DeriveGeneric #-}
>>
>>  import GHC.Generics (Generic)
>>  import Data.Hashable
>>
>>  data Colour = Red | Green | Blue
>>                deriving Generic
>>
>>  instance Hashable Colour
>>
>> If I then type `hash Red` I get a stack overflow.
>>
>> I am using the Haskell Platform, so I have hashable-1.1.2.5, but I notice
>> the docs are for hashable-1.2.0.10. If I install 1.2.0.10 though, other
>> code in my project breaks - seems like one part doesn't recognize the
>> instances from another part. So I'll stick with the platform version.
>>
>> ...
>>
>
> Generic support was added in hashable-1.2.  Before then, the default
> implementations for `hash` and `hashWithSalt` were written in terms of each
> other:
>
>     hash = hashWithSalt defaultSalt
>     hashWithSalt salt x = salt `combine` hash x
>
> Because you did not give an implementation for either of these, both
> default implementations were used, leading to a loop.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130808/9bd3352a/attachment.htm>


More information about the Haskell-Cafe mailing list