Avoiding O(n^2) instances when using associated data types to unpack values into constructors

Hi, I'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't address the real problem that the number of instances grows quadratically. Is there a better way to have GHC unpack the keys and values into the data constructors? Cheers, Johan \begin{code} {-# LANGUAGE CPP, MultiParamTypeClasses, TypeFamilies #-} -- | This module defines a type for maps of unboxed keys and values. module Data.AdaptMap (Unbox()) where -- | The size of the map. type Size = Int -- | A map of unboxed keys and values. class Unbox k a where data Map k a :: * -- Constructors/destructors used to implement functions on the map -- in a generic manner. tipCon :: Map k a binCon :: Size -> k -> a -> Map k a -> Map k a -> Map k a unMap :: Map k a -> b -> (Size -> k -> a -> Map k a -> Map k a -> b) -> b #define primMap(map,key,val,tipcon,bincon) \ instance Unbox key val where { \ data Map key val = tipcon \ | bincon {-# UNPACK #-} !Size \ {-# UNPACK #-} !key \ {-# UNPACK #-} !val \ !(Map key val) \ !(Map key val) \ ; tipCon = tipcon \ ; {-# INLINE tipCon #-} \ ; binCon = bincon \ ; {-# INLINE binCon #-} \ ; unMap t tk bk = case t of { \ tipcon -> tk \ ; bincon sz k v l r -> bk sz k v l r } \ ; {-# INLINE unMap #-} \ } -- Example instance with keys and values of type Int. primMap(IntIntMap,Int,Int,IntIntTip,IntIntBin) ------------------------------------------------------------------------ -- Construction empty :: Unbox k a => Map k a empty = tipCon singleton :: Unbox k a => k -> a -> Map k a singleton k x = binCon 1 k x tipCon tipCon \end{code}

johan.tibell:
Hi,
I'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't address the real problem that the number of instances grows quadratically.
I've a TH macro in the adaptive-containers package you might use as well.
Is there a better way to have GHC unpack the keys and values into the data constructors?
Not that I know of, other than reusing some of the primitive types where possible (Int/Word). -- Don
participants (2)
-
Don Stewart
-
Johan Tibell