On Jul 27, 2010, at 1:16 AM, Angel de Vicente wrote: > data JValue = JString String > | JNumber Double > | JBool Bool > | JNull > | JObject [(String, JValue)] > | JArray [JValue] > deriving (Eq, Ord, Show) > > type JSONError = String > > class JSON a where > toJValue :: a -> JValue > fromJValue :: JValue -> Either JSONError a
The type class JSON is the class of types (a) that have been provided with functions functions to convert between (a) and JValue. toJValue converts an (a) to a JValue. fromJValue tries to convert a JValue to an (a), returning Right x if it succeeds, or Left ".." if it fails, for some error message. So the JSON type class is useful when every value of type (a) can be faithfully represented by some JValue, but not every JValue represents an (a). For example, we might say instance (JSON a, JSON b) => JSON (a,b) where toJValue (x,y) = JArray [toJValue x, toJValue y] fromJValue (JArray [u,v]) = case (fromJValue u, fromJValue v) of (Right x, Right y) -> Right (x,y) (Right _, Left er) -> Left er (Left er, _) -> Left er fromJValue _ = Left "not a 2-element array" > instance JSON JValue where > toJValue = id > fromJValue = Right A JValue can be converted to a JValue by doing nothing. A JValue can be converted back to a JValue again by doing nothing, BUT we must say that the conversion succeeded by wrapping the result in Right. > > instance JSON Bool where > toJValue = JBool > fromJValue (JBool b) = Right b > fromJValue _ = Left "not a JSON boolean" A Bool can be converted to a JValue by wrapping it in JBool. A JBool can be converted back to a Bool by unwrapping it and then wrapping the result in Right. But any JValue other than a JBool cannot be converted to a Bool. (Actually, this is was a choice; other choices could have been made.) Since we can't do it, we have to say _that_ we didn't (Left) and _why_ ("not a JSON boolean"). > I don't understand how the JSON typeclass is defined, in particular the > fromJValue definition. There's a simple pattern for "communication" types like XML or JSON or UBF or for that matter byte strings. Roughly speaking class Communicable t where to_exchange_format :: t -> Maybe Exchange from_exchange_format :: Exchange -> Maybe t Variations on this are - where one direction of conversion must never fail, so the "Maybe" disappears - where the designer chose to require reasons for failure, so that Maybe is replaced by Either String. > For instance, when defining the instance for Bool types, then I > understand that both functions (toJValue and fromJValue) will be called > upon when we supply a Bool type, but then the (JBool b) type in function > fromJValue doesn't match.... Ah. What you may be missing here is that Haskell resolves the types of functions taking into account ALL information about them, >>> INCLUDING THE RESULT <<< So if we do let boo = True jay = toJValue boo lea = fromJValue jay ... then the call of toJValue is resolved thanks to the type of its *argument* and the call to fromJValue is not resolved. But if we do let boo = True jay = toJValue boo lea :: Bool lea = fromJValue jay then the call of fromJValue is resolved thanks to the (now!) known type of its *result*. > toJValue is no problem, but I cannot understand how fromJValue is > supposed to work, and the comments in the online book > (http://book.realworldhaskell.org/read/using-typeclasses.html) don't > help with this either. > > *Main> :load ch6 > [1 of 1] Compiling Main ( ch6.hs, interpreted ) > Ok, modules loaded: Main. > *Main> toJValue False > JBool False > *Main> :type it > it :: JValue > *Main> fromJValue False > > <interactive>:1:11: > Couldn't match expected type `JValue' against inferred type `Bool' > In the first argument of `fromJValue', namely `False' This is hardly surprising, because you have an explicit declaration that says fromJValue :: JValue -> Either JSONError a so the argument of fromJValue may only be a JValue, and False is not a JValue. > *Main> fromJValue (JBool False) > > <interactive>:1:0: > Ambiguous type variable `a' in the constraint: > `JSON a' arising from a use of `fromJValue' at <interactive>:1:0-23 > Probable fix: add a type signature that fixes these type variable(s) > *Main> > > > > Any pointers? Yes. That last error message you quoted told you exactly what to do. It said, in effect, that the only thing wrong with fromJValue (JBool False) is that it doesn't know what the result type (a) should be, except that it must involve *some* instance of JSON, and it recommended that you add a type signature (:: t for some t) to something that might tell it. *Main> (fromJValue (JBool False)) :: (Either JSONError Bool) Right False Or you could have asked whether *Main> fromJValue (JBool False) == Right False True _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe