Data.Generics and Abstract Data Types

Samuel Bronson naesten at gmail.com
Sat Dec 16 19:32:56 EST 2006


Today, I was playing with Stefan O'Rear's genericserialize package
when I noticed that Data.Map doesn't play well with Data.Generics.
Specifically, here is its instance for Data:

-- This instance preserves data abstraction at the cost of inefficiency.
-- We omit reflection services for the sake of data abstraction.

instance (Data k, Data a, Ord k) => Data (Map k a) where
  gfoldl f z map = z fromList `f` (toList map)
  toConstr _     = error "toConstr"
  gunfold _ _    = error "gunfold"
  dataTypeOf _   = mkNorepType "Data.Map.Map"
  dataCast2 f    = gcast2 f

The gfoldl and dataCast2 methods are okay, but I'm not sure about all
the others.

Now, I can understand why whoever wrote Data.Map doesn't want to
expose the internals, but couldn't we at least have a nice way to
deconstruct one and a nice way to build one,without having to write
hard-coded Map code? I particularly don't like the fact that toConstr
doesn't work on it.

Multiply this times four to account for the fact that Data.Set,
Data.IntMap, and Data.IntSet have the same problem.

I also noticed that Data.ByteString.Word8 has a rather silly instance
(it exposes the innards instead of doing something usefull), and that
Data.Array has the same problem as Data.Map -- presumably the other
IArray instances do too.

I think the best way might be to add a few constructors to the DataRep
and ConstrRep types, which I reproduce here:

data DataRep
  = AlgRep [Constr] | IntRep | FloatRep | StringRep | NoRep

data ConstrRep
  = AlgConstr ConIndex
  | IntConstr Integer
  | FloatConstr Double
  | StringConstr String

(I must also marvel at how strangely named the StringRep/StringConstr
constructors are -- they seem to be used exclusively for the Char
type.)

Please discuss! Oh, and by the way, I'd like my nuclear power plant
painted red, thank you ;-).


More information about the Libraries mailing list