where do I point the type annotations

I am playing with using SYB to make generic indexed collections. The current code is this: data Syb = Syb [Dynamic] -- list of [Map val (Set a)] empty item = Syb $ gmapQ (toDyn . emp item) item where emp::x->y->Map.Map y (Set.Set x) emp x y = Map.empty insert x (Syb indices) = Syb $ zipWith f indices (gmapQ toDyn x) where f dynIndex dynAttr = toDyn $ Map.insert attr (maybe (Set.singleton x) (Set.insert x) $ Map.lookup attr index) index where index = fromJust $ fromDynamic dynIndex attr = fromJust $ fromDynamic dynAttr e = empty i where i=i::Test t1 = Test "foo" 2 c1 = insert t1 e Which causes the following error (the line numbers are wrong because there was other code in the original): Ambiguous type variable `a' in the constraints: `Ord a' arising from use of `insert' at Main.hs:113:5-15 `Typeable a' arising from use of `insert' at Main.hs:113:5-15 Probable fix: add a type signature that fixes these type variable(s) What am I doing wrong? Is there a better way to define insert that does not have this problem? Note: I also tried doing this so that each attribute tried to find a matching index using fromDynamic, but that gave me an error involving gmapQ not have an Ord constraint. -Alex-

On Fri, May 18, 2007 at 02:39:48AM -0400, Alex Jacobson wrote:
I am playing with using SYB to make generic indexed collections. The current code is this:
data Syb = Syb [Dynamic] -- list of [Map val (Set a)]
empty item = Syb $ gmapQ (toDyn . emp item) item where emp::x->y->Map.Map y (Set.Set x) emp x y = Map.empty
insert x (Syb indices) = Syb $ zipWith f indices (gmapQ toDyn x) where f dynIndex dynAttr = toDyn $ Map.insert attr (maybe (Set.singleton x) (Set.insert x) $ Map.lookup attr index) index where index = fromJust $ fromDynamic dynIndex attr = fromJust $ fromDynamic dynAttr
e = empty i where i=i::Test t1 = Test "foo" 2 c1 = insert t1 e
The problem is that Dynamic just remembers that whatever type of value it holds, that type is Typeable. In particular it doesn't try to keep track of whether there is an Ord. If you are polymorphically processing the contents of a Dynamic you can't assume much - Dynamic could have been defined data Dynamic = forall t . (Typeable t) => Dynamic t You can make something like your code using a more informative existential:
data Ix a = forall key . (Typeable key, Ord key) => Ix (Map key (Set a))
(I'm adding the parameter a because it looks like your code would just explode if you tried to add values of several different types to a Syb).
data Syb a = Syb [Ix a]
insertIndex k v index = Map.insertWith Set.union k (Set.singleton v) index
insert indexes the argument by the subterms the index actually cares about.
insert :: (Data a, Ord a) => a -> Syb a -> Syb a insert x (Syb indices) = Syb $ update indices (gmapQ toDyn x) where update [] _ = [] update (Ix index:is) dyns = let (d: dyns') = dropWhile (\d -> dynTypeRep d /= keyType) dyns key = fromJust $ fromDynamic d keyType = typeOf ((undefined :: Map key (Set a) -> key) index) in (Ix (insertIndex key x index): update is dyns')
data Test = Test String Int deriving (Data,Typeable,Eq,Ord)
Unfortunately, you can't automatically build an empty index. gmapQ toDyn is great for getting subterms, but not checking if they are Ord.
e = Syb [Ix (Map.empty :: Map String (Set Test)), Ix (Map.empty :: Map Int (Set Test))]
At least the test works.
t1 = Test "foo" 2 c1 = insert t1 e
If it's enough to support types where every subterm is Ord, you could probably automte building the empty index with the strategy from "Scrap Your Boilerplate with Class" Brandon P.S. The existential definition of Dynamic suggests there could be withDynamic :: (forall t . (Typeable t) => t -> a) -> Dynamic -> a it takes an awful lot of black magic to define it for GHC, though.
participants (2)
-
Alex Jacobson
-
Brandon Michael Moore