[Haskell-cafe] Problem on using class as type.
Steffen Schuldenzucker
sschuldenzucker at uni-bonn.de
Mon Oct 3 17:18:28 CEST 2011
On 10/03/2011 10:42 PM, Magicloud Magiclouds wrote:
> Hi,
> I have a function:
> post :: (ToJson p, FromJson q) => String -> String -> String ->
> Map.Map String p -> IO q
> Now I'd like to call it like:
> r<- post site token "user.addMedia" (Map.fromList [ ("users", users :: ToJson)
> , ("medias", medias
> :: ToJson) ])
> So I got the problem. If I used things like "users :: ToJson", then
> class used as a type error occurred. But if I did not use them, since
> users and medias were actually different types, then fromList failed,
> required the type of medias the same with users.
>
> How to resolve the conflict?
If 'users' and 'medias' are actually of a general type (like "for all a
with ToJson a, users describes a value of type a"), use Jesse's
suggestion. Otherwise ("there is an a with ToJson a such that users
describes a value of type a"), you might want to use existentials:
{-# LANGUAGE ExistentialQuantification #-}
data SomeToJson = forall a. (ToJson a) => SomeToJson a
instance ToJson SomeToJson where
toJson (SomeToJson x) = toJson x -- I guess your class looks like
this?
And then:
r <- post site token "user.addMedia" $ Map.fromList
[("users", SomeToJson users), ("medias", SomeToJson medias)]
As a last remark, I needed this pattern exactly once, namely for dealing
with rank 2 types in rendering functions using takusen. I can conclude
that requiring it is often an indicator for a major design flaw in your
program. In this case:
Why not:
-- assuming that there is an
-- instance ToJson Json where toJson = id
r <- post site token "user.addMedia" $ Map.fromList
[("users", toJson users), ("medias", toJson medias)]
Cheers!
More information about the Haskell-Cafe
mailing list