Hi,<br><br>I&#39;m trying to create a data type for maps where both keys and values are unpacked into the data type constructors (see code at the end of this email). I achieve this using an associated data type of two arguments (`Map` in the code below). The problem I have is that this definition requires O(n^2) instances. I use a CPP macro to make it easier to create these instances but it doesn&#39;t address the real problem that the number of instances grows quadratically.<br>

<br>Is there a better way to have GHC unpack the keys and values into the data constructors?<br><br>Cheers,<br>Johan<br><br>\begin{code}<br>{-# LANGUAGE CPP, MultiParamTypeClasses, TypeFamilies #-}<br><br>-- | This module defines a type for maps of unboxed keys and values.<br>

module Data.AdaptMap (Unbox()) where<br><br>-- | The size of the map.<br>type Size = Int<br><br>-- | A map of unboxed keys and values.<br>class Unbox k a where<br>    data Map k a :: *<br>         <br>    -- Constructors/destructors used to implement functions on the map<br>

    -- in a generic manner.<br>    tipCon :: Map k a<br>    binCon :: Size -&gt; k -&gt; a -&gt; Map k a -&gt; Map k a -&gt; Map k a<br>    unMap :: Map k a -&gt; b -&gt; (Size -&gt; k -&gt; a -&gt; Map k a -&gt; Map k a -&gt; b) -&gt; b<br>

<br>#define primMap(map,key,val,tipcon,bincon)         \<br>instance Unbox key val where {                     \<br>    data Map key val = tipcon                      \<br>                     | bincon {-# UNPACK #-} !Size \<br>

                              {-# UNPACK #-} !key  \<br>                              {-# UNPACK #-} !val  \<br>                              !(Map key val)       \<br>                              !(Map key val)       \<br>

;    tipCon = tipcon                               \<br>;    {-# INLINE tipCon #-}                         \<br>;    binCon = bincon                               \<br>;    {-# INLINE binCon #-}                         \<br>

;    unMap t tk bk = case t of {                   \<br>         tipcon -&gt; tk                              \<br>;        bincon sz k v l r -&gt; bk sz k v l r }      \<br>;    {-# INLINE unMap #-}                          \<br>

}<br><br>-- Example instance with keys and values of type Int.<br>primMap(IntIntMap,Int,Int,IntIntTip,IntIntBin)<br><br>------------------------------------------------------------------------<br>-- Construction<br><br>empty :: Unbox k a =&gt; Map k a<br>

empty = tipCon<br><br>singleton :: Unbox k a =&gt; k -&gt; a -&gt; Map k a<br>singleton k x = binCon 1 k x tipCon tipCon<br>\end{code}<br><br>