Proposal: Allow gunfold for Data.Map, Data.IntMap, etc.

Milan Straka fox at ucw.cz
Wed Aug 29 21:24:53 CEST 2012


Hi Edward,

> I would like to propose improving the Data instances for a number of
> currently completely opaque data types in the containers package, by using
> virtual constructors.
> 
> The instance for Data.Map already uses fromList for gfoldl, it just stops
> there.
> 
> Extending it to be able to gunfold and mention the name of that constructor
> would enable generic traversal libraries like uniplate, etc. to work over
> the contents of the Map, rather than bailing out in fear or crashing at the
> sight of a mkNoRepType.
> 
> An example of the changes for Data.Map are highlighted below.
> 
> instance (Data k, Data a, Ord k) => Data (Map k a) where
>   gfoldl f z m   = z fromList `f` toList m
>   toConstr _     = fromListConstr
>   gunfold k z c  = case constrIndex c of
>     1 -> k (z fromList)
>     _ -> error "gunfold"
>   dataTypeOf _   = mapDataType
>   dataCast2 f    = gcast2 f
> 
> fromListConstr :: Constr
> fromListConstr = mkConstr mapDataType "fromList" [] Prefix
> 
> mapDataType :: DataType
> mapDataType = mkDataType "Data.Map.Map" [fromListConstr]
> 
> I've used this approach for years on my own libraries to great effect.

+1 here.

I am not very familiar with the Data instances -- is it true that the
parameter of the `fromList` in the Data instance will often be sorted
(i.e., result of `toList` or `filter . toList`)? If so, we could use
fromMaybeAscList which would look like
fromMaybeAscList list | isDistinctAsc list = fromDistinctAscList list
                      | otherwise = fromList list
There is a big gain in using a linear-time fromDistinctAscList over O(N
log N) fromList, but there is a linear-time check and the list must be
kept around until isDistinctAsc finishes.

Cheers,
Milan



More information about the Libraries mailing list