[Haskell-cafe] Natural keys in Haskell data structures

Edward Z. Yang ezyang at mit.edu
Fri Jul 8 13:40:46 UTC 2016


Hello Lian,

I recently wrote a module for just this purpose.  Here is the approach
that I (and Edward Kmett) like to take:

1. Create a type class with an associated type representing elements
whic have keys:

    {-# LANGUAGE TypeFamilies #-}
    {-# LANGUAGE UndecidableInstances #-}
    class Ord (Key a) => HasKey a where
        type Key a :: *
        getKey :: a -> Key a

2. Write new data structures which utilize this type-class.

    import qualified Data.Map as OldMap
    data Map a = OldMap.Map (Key a) a
    insert :: HasKey a => a -> Map a -> Map a

  These structures are responsible for maintaining the key-value
  invariants (which can be tricky at times; be careful!)

There are other approaches too; for example you can use a multiparameter
type class with a functional dependency. "HasKey k a | a -> k"

Unfortunately I am not aware of any standardized naming scheme
for HasKey/getKey.

Edward

Excerpts from Lian Hung Hon's message of 2016-07-08 09:35:53 -0400:
> Dear cafe,
> 
> What is the idiomatic way to "split" records into their natural keys and
> content in a data structure? For example, given a user:
> 
> data User = { username :: ByteString, hash :: ByteString, address :: Text,
> ... }
> 
> Using map, a first choice would be Map ByteString User, but this leads to
> duplication of the username. And it is possible to make mistakes, such as
> 
> insert "John" (User "Jane" ...
> 
> What does cafe think? Is there any pattern for this? This is probably just
> a small nit in the overall architecture, but I'm curious to know the clean
> way to do it.
> 
> 
> Regards,
> Hon


More information about the Haskell-Cafe mailing list