Inferred type less polymorphic than expected

Folks, How do I fix this? data Prop = forall a b.(Eq a, Show a) => Attr a := a data Attr a = Attr String (a -> Dynamic, Dynamic -> Maybe a) (PU a) type Props = M.Map String (Int, Prop) instance Ord (Int, Prop) where compare (a, _) (b, _) | a == b = EQ | a > b = GT | otherwise = LT makeAttr :: Typeable a => String -> PU a -> Attr a makeAttr name pickler = Attr name (toDyn, fromDynamic) pickler ... props :: Props -> PU Props props m = props' $ sort $ M.toList m where props' [] = lift [] props' ((_, (Attr _ _ pp := _)):xs) = wrap (\(a, b) -> a : b, \(a : b) -> (a, b)) (pair pp (props' xs)) ./Script/Prop.hs:80:10: Inferred type is less polymorphic than expected Quantified type variable `a' is mentioned in the environment: props' :: [(a1, Prop)] -> PU [a] (bound at ./Script/Prop.hs: 79:10) When checking an existential match that binds $dEq :: {Eq a} $dShow :: {Show a} pp :: PU a The pattern(s) have type(s): [(a1, Prop)] The body has type: PU [a] In the definition of `props'': props' ((_, (Attr _ _ pp := _)) : xs) = wrap (\ (a, b) -> a : b, \ (a : b) -> (a, b)) (pair pp (props' xs)) In the definition of `props': props m = props' $ (sort $ (Data.Map.toList m)) where props' [] = lift [] props' ((_, (Attr _ _ pp := _)) : xs) = wrap (\ (a, b) -> a : b, \ (a : b) -> (a, b)) (pair pp (props' xs)) Thanks, Joel -- http://wagerlabs.com/

Joel Reymont wrote:
Folks,
How do I fix this?
data Prop = forall a b.(Eq a, Show a) => Attr a := a
data Attr a = Attr String (a -> Dynamic, Dynamic -> Maybe a) (PU a)
type Props = M.Map String (Int, Prop)
instance Ord (Int, Prop) where compare (a, _) (b, _) | a == b = EQ | a > b = GT | otherwise = LT
makeAttr :: Typeable a => String -> PU a -> Attr a makeAttr name pickler = Attr name (toDyn, fromDynamic) pickler ... props :: Props -> PU Props props m = props' $ sort $ M.toList m where props' [] = lift [] props' ((_, (Attr _ _ pp := _)):xs) = wrap (\(a, b) -> a : b, \(a : b) -> (a, b)) (pair pp (props' xs))
This doesn't give you a (PU Props), but a (PU [exists a . a]) or something, which is bogus syntax, since the idea is already nonsensical. You have to dismantle and create 'Prop's if you want to put them into a list, and you forgot a M.fromList somewhere, too. You probably want something like this (untested, in order not to spoil the fun for you):
props :: Props -> PU Props props m = wrap M.toAscList M.fromAscList props' where props' [] = lift [] props' ((key, (Attr str casts pp := val)):xs) = wrap (\_ -> val : xs, \(val' : xs) -> ((key, Attr str casts pp := val'), b)) (pair pp (props' xs))
If you create the pickler from one concrete instance of Props, then use it to (un-)pickle another, you will get bogus results and propably a pattern match failure. Basically you have thrown all static type checking out the window when you create the Attr type, and it will come back to haunt you. You probably also want to ask yourself if you need this heavy machinery or if putting the properties into records is the more sensible thing to do. Udo.

The road to hell is paved with good intentions. I sold this to the client as a "simple scripting language" and I have to deliver now, lest I loose my credibility. This were working quite well ... except the program is spending 50% of the time collecting garbage and is shuffling a few Gb of memory while at it. All in the span of, say, 5 minutes. I decided to rewrite the pickling and the way I manage properties. I need dynamic records since I don't want the customer to deal with Haskell constructors, etc. What I want is described quite nicely in the HList library under extensible records. Problem is that I don't have the time to learn the library and convert everything. I think I don't but I'll give it another look. I already reinvented the wheel quite badly with prior pickling. My records are formerly property lists and now maps. This lets me supply default values and let the customer pass in "keyword arguments". On Nov 8, 2005, at 5:56 PM, Udo Stenzel wrote:
This doesn't give you a (PU Props), but a (PU [exists a . a]) or something, which is bogus syntax, since the idea is already nonsensical. You have to dismantle and create 'Prop's if you want to put them into a list, and you forgot a M.fromList somewhere, too.
I did forgot the fromList somewhere but the idea makes a lot of sense to me. I'm storing the pickler when making the attribute. Let me know if I missed something! data Attr a = Attr String (a -> Dynamic, Dynamic -> Maybe a) (PU a) and playersFlop :: Attr Word8 = makeAttr "playersFlop" byte So at the time of unpickling I'm using exactly the pickler that was stored when creating the attribute. Thanks, Joel -- http://wagerlabs.com/
participants (2)
-
Joel Reymont
-
Udo Stenzel