[Haskell-cafe] represent data sturcture using function

Ryan Ingram ryani.spam at gmail.com
Mon Dec 29 04:48:50 EST 2008


On Sun, Dec 28, 2008 at 10:13 PM, David Menendez <dave at zednenem.com> wrote:
> 2008/12/29 Raeck chiu <raeck at msn.com>:
>> It seems to be very difficult to change the number of Male or Female if a
>> concrete data structure is not used. Is it possible change the number of Male in classA
>> when represent classA using function?
>
> Here's the simplest way:
>
>    update k v map = \k' -> if k' == k then v else map k'
>
> Note that it requires an Eq instance for Sex.
>
>    let classA' = update Male 150 classA
>    in (classA' Male, classA' Female)
> =
>    (150,200)

Of course this version of update leaks crazy amounts of memory:

> let bigmap = iterate (update Male 150) classA !! 100000
> bigmap Male

"bigmap" leaves a huge chain of thunks pointing at each other, which
can never be freed.

Using functions is mathematically more elegant than some concrete data
structure (which might require Eq or Ord or other constraints, and
have multiple observable representations for the same map, or have
maps that don't include every element).

However, "generic maps" have been improving a lot recently, especially
with data families in the new GHC.   You use an abstract type (k :->
v) to represent the map; this type is semantically equivalent to (k ->
v) via some observation function for generic maps, but has a compact
representation.  For example:

> class MapKey k where
>    data k :-> v
>    newMap :: (k -> v) -> (k :-> v)
>    fetch :: (k :-> v) -> (k -> v)
>    update :: (k,v) -> (k :-> v) -> (k :-> v)
>    empty :: v -> (k :-> v)
>    empty = newMap (const v)

> instance MapKey Bool where
>    data Bool :-> v = BoolMap v v
>    newMap f = BoolMap (f False) (f True)
>    fetch (Boolmap t f) v = if v then t else f
>    update (True, t) (BoolMap _ f) = Boolmap t f
>    update (False, f) (BoolMap t _) = Boolmap t f

"fetch" converts this representation of a total function over k, into
an actual function.  The representation of k :-> v might vary
depending on k; Int might use IntMap, (k1,k2) can compose maps:

> instance (MapKey k1, MapKey k2) => MapKey (k1,k2) where
>    newtype (k1,k2) :-> v = PairMap (k1 :-> (k2 :-> v))
>    ...

> instance (MapKey k1, MapKey k2) => MapKey (Either k1 k2) where
>    data (Either k1 k2) :-> v = EitherMap (k1 :-> v) (k2 :-> v)
>    ...

This gives you the same benefits as the function approach but without
the terrible performance issues.  You do need to write instances for
your types, though, although most can be easily derived from the
instances for pairs, Either, and Integer.

See http://www.haskell.org/haskellwiki/GHC/Indexed_types for more.

  -- ryan


More information about the Haskell-Cafe mailing list