Using classes for a heterogeneous graph structure

I'm trying to use a class to create a heterogeneous graph structure. Part of this involves holding things in a Data.Map identified only as "instances of some class", but then I can't figure out how to actually use these things. What is mystifying me is exemplified in the following code: ----------------- module Sample where 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 type ThingsByString = (Thing thing) => Map.Map Integer thing update :: Integer -> Integer -> ThingsByString -> ThingsByString update key value map = let (Just thing) = Map.lookup key map in Map.insert key (set_int thing value) map test = let my_map = Map.empty::ThingsByString map1 = Map.insert 0 1 my_map map2 = update 0 8 map1 in map1 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 ----------------- This gives an error message (in GHC 6.8 w/ -fglasgow-exts , and yeah, that's deprecated, I'm still in dev): Sample.hs:27:16: Inferred type is less polymorphic than expected Quantified type variable `thing' is mentioned in the environment: map1 :: Map.Map Integer thing (bound at Sample.hs:26:9) my_map :: Map.Map Integer thing (bound at Sample.hs:25:9) In the third argument of `update', namely `map1' In the expression: update 0 8 map1 In the definition of `map2': map2 = update 0 8 map1 Now, I sort of understand this message. What I don't understand is how to do what I want to do; I've rearranged things in a number of ways but this comes up every which way. It seems like once I have one of these "things" there's absolutely nothing I can do to it (or absolutely no way to do what update does, which is mutate it using only the defined class interface without ever knowing what's in there). What's annoying is that at least as a human, what I want seems well-defined to me. Moreover, as shown in the code above, I can create a "wrapper" structure, and if I do that and manipulate only the wrapper (not shown in this example), everything works as I'd like. (If that's the answer, that's OK with me, but it seems klunky, wasteful, and amenable to being automatically done by the compiler as I understand it, and I expect there's a reason it isn't.) My question is: How can I have this heterogeneous graph structure and actually be able to manipulate it solely through a class interface? Or, is it impossible? (I'm open to "you're doing it entirely wrong and you should do X", but in that case I'd like to know what using classes to specify the interface a node should conform to is the wrong thing, because it sure *seems* right, based on what the interface is and how classes are documented. And it would need to work for a heterogeneous graph structure, not my very-simplified example above.) ---------------------------------- Barracuda Networks makes the best spam firewalls and web filters. www.barracudanetworks.com

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... 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
participants (2)
-
ChrisK
-
Jeremy Bowers