Hashable instance for vinyl records

Hi,

I would like to use Hashable (https://hackage.haskell.org/package/hashable) to generate a hash from a vinyl record. Right now I have sthg for a single field I think

type HashablePart = '[ "type1" :-> Word32 , "type2" :-> Word32 ]
...
deriving instance  (KnownSymbol s, Hashable a) => Hashable(ElField '(s, a))

but HashablePart contains several fields . I tried to copy the instance for storable from hoogle https://hackage.haskell.org/package/vinyl-0.13.0/docs/Data-Vinyl-Core.html#t:Rec

deriving instance (Hashable (f r), Generic (Rec f rs), Hashable (Rec f rs)) => Hashable(Rec f (r ': rs))
triggers

  • Could not deduce (hashable-1.3.0.0:Data.Hashable.Class.GHashable
                          hashable-1.3.0.0:Data.Hashable.Class.Zero (Rep (Rec f rs)))
        arising from a use of ‘hashable-1.3.0.0:Data.Hashable.Class.$dmhashWithSalt’
      from the context: (Hashable (f r), Generic (Rec f rs),
                         Hashable (Rec f rs))
        bound by the instance declaration

I am not sure what to do ? My actual HashablePart type has actually a dozen field so I could write a function to hash them manually but I would prefer to have a generic elegant solution first.

Chhers

1 Like

I’m having a hard time figuring out where :-> is being imported from.

1 Like

Maybe something like:


 
-- | This is only here so we can use hash maps for the grouping step.  This should properly be in Vinyl itself.
instance Hash.Hashable (F.Record '[]) where
  hash = const 0
  {-# INLINABLE hash #-}
  hashWithSalt s = const s
  {-# INLINABLE hashWithSalt #-}
instance (V.KnownField t, Hash.Hashable (V.Snd t), Hash.Hashable (F.Record rs), rs F.⊆ (t ': rs)) => Hash.Hashable (F.Record (t ': rs)) where
  hashWithSalt s r = s `Hash.hashWithSalt` (F.rgetField @t r) `Hash.hashWithSalt` (F.rcast @rs r)
  {-# INLINABLE hashWithSalt #-}

2 Likes

thanks a lot that did it ! Wy the inlinable if I may ask ?

I sort of put inlineable (or inline) on everything. :slight_smile:

Glad it worked for you!