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-