Using associated data types to create unpacked data structures

Jean-Marie Gaillourdet jmg at gaillourdet.net
Thu Aug 12 08:44:11 EDT 2010


Hi,

On 12.08.2010, at 12:25, Simon Marlow wrote:

> On 12/08/2010 11:13, Johan Tibell wrote:
> 
>> There needs to be some amount of code generation, but much of the
>> implementation can still be shared. I previously tried to defined the
>> type class as
>> 
>>     {-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
>>     module Ex2 where
>> 
>>     import Prelude hiding (lookup)
>> 
>>     data MapView k v = TipView
>>                      | BinView {-# UNPACK #-} !Size !k !v !(Map k v)
>> !(Map k v)
>> 
>>     class Unbox k v where
>>         data Map k v :: *
>>         tip :: Map k v
>>         bin :: Size -> k -> v -> Map k v -> Map k v -> Map k v
>>         view :: Map k v -> MapView k v
>> 
>>     type Size = Int
>> 
>>     lookup :: (Ord k, Unbox k v) => k -> Map k v -> Maybe v
>>     lookup k m = case view m of
>>         TipView -> Nothing
>>         BinView _ kx x l r -> case compare k kx of
>>             LT -> lookup k l
>>             GT -> lookup k r
>>             EQ -> Just x
>>     {-# INLINE lookup #-}
>> 
>> Calling lookup from a different module at a know type gives exactly the
>> Core you'd like to see (unpacked types, no MapView constructors).
> 
> I'm not sure I want lookup (and other operations) to be inlined at every call site though.

Wouldn't it be better to enable specialize pragmas from outside the defining module. Then a user of the Ex2 could declare his need for an optimized version of lookup for his particular type. Of course, that would require the inclusion of lookup into the .hi file.

-- Jean


More information about the Glasgow-haskell-users mailing list