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/
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe