[Haskell-cafe] Re: Using classes for a heterogeneous graph structure

ChrisK haskell at list.mightyreason.com
Mon Dec 29 12:53:25 EST 2008


I think the below code which compiles with ghc-6.10.1 should compile with 
ghc-6.8.3 as well.  My preference is to define a GADT such as ThingMap below.

Conceptually ThingMap contains two pieces of information.  There is a Map to an 
unknown type "thing" and there is a dictionary which implements a Thing instance 
for this unknown type "thing".  By pattern matching (ThingMap map) in update the 
rest of update gets access to both pieces of information.  You are guaranteed 
that each element of the map is the SAME type.

To be able to do more stuff with it you need to add classes either as a context 
to the definition of class Thing or in addition to the "(Thing thing)" context 
in the ThingMap definition.

Or you could use the slightly different strategy of MapTW.  Here each element of 
the map might be a DIFFERENT underlying type (underneath ThingWrapper).

The "data MapThing" is the older style of existential data and is, in my 
opinion, superseded by the GADT style used in ThingMap.

> {-# OPTIONS_GHC -fglasgow-exts #-}
> module Sample where
> 
> import Data.Map(Map)
> import qualified Data.Map as Map
> 
> class Thing thing where
>       set_int :: thing -> Integer -> thing
> 
>       -- for wrapper
>       wrapper :: thing -> ThingWrapper
>       wrapper thing = ThingWrapper thing
> 
> instance Thing Integer where
> 	 set_int me i = i -- in the generic case, this actually does something
> 
> -- This really has to change
> -- type ThingsByString = (Thing thing) => Map.Map Integer thing
> -- Look at http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html
> data ThingMap where ThingMap :: forall thing . (Thing thing) => Map Integer thing -> ThingMap -- New GADT goodness
> data MapThing = forall thingish . (Thing thingish) => MapThing (Map Integer thingish) -- Old style, not as good
> type MapTW = Map Integer ThingWrapper
> 
> update :: Integer -> Integer -> ThingMap -> ThingMap
> update key value (ThingMap map) =
>        let (Just thing) = Map.lookup key map
>        in ThingMap $ Map.insert key (set_int thing value) map
> 
> update' :: Integer -> Integer -> MapThing -> MapThing
> update' key value (MapThing map) =
>        let (Just thingie) = Map.lookup key map
>        in MapThing $ Map.insert key (set_int thingie value) map
> 
> update'' :: Integer -> Integer -> MapTW -> MapTW
> update'' key value map =
>        let (Just thingie) = Map.lookup key map
>        in Map.insert key (set_int thingie value) map
> 
> test1 =
>      let my_map = Map.empty :: Map Integer Integer
>          map1 = ThingMap (Map.insert 0 1 my_map)
>          map2 = update 0 8 map1
>      in map2
> 
> test2 =
>      let my_map = Map.empty :: Map Integer ThingWrapper
>          map1 = ThingMap (Map.insert 0 (ThingWrapper (1::Integer)) my_map)
>          map2 = update 0 8 map1
>      in map2
> 
> test3 =
>      let my_map = Map.empty :: Map Integer Integer
>          map1 = MapThing (Map.insert 0 1 my_map)
>          map2 = update' 0 8 map1
>      in map2
> 
> test4 =
>      let my_map = Map.empty :: Map Integer ThingWrapper
>          map1 = MapThing (Map.insert 0 (ThingWrapper (1::Integer)) my_map)
>          map2 = update' 0 8 map1
>      in map2
> 
> test5 =
>      let my_map = Map.empty :: MapTW
>          map1 = Map.insert 0 (ThingWrapper (1::Integer)) my_map
>          map2 = update'' 0 8 map1
>      in map2
> 
> data ThingWrapper = forall t. (Thing t) => ThingWrapper t
> 
> instance Thing ThingWrapper where
> 	 set_int (ThingWrapper thing) i = wrapper $ set_int thing i
> 	 wrapper thing_wrapper = thing_wrapper
> 



More information about the Haskell-Cafe mailing list