[Haskell-cafe] Typeclasses question in "Real World Haskell" book

Daniel Fischer daniel.is.fischer at web.de
Mon Jul 26 16:49:42 EDT 2010


On Monday 26 July 2010 21:03:10, Angel de Vicente wrote:
> Hi,
>
> thanks for the answer. This is my first attempt at Typeclasses, and I
> think there is something "deep" that I don't understand...
>
> On 26/07/10 15:03, Daniel Fischer wrote:
> >> class JSON a where
> >>       toJValue :: a ->  JValue
> >>       fromJValue :: JValue ->  Either JSONError a
> >>
> >> instance JSON JValue where
> >>       toJValue = id
> >>       fromJValue = Right
> >>
> >> instance JSON Bool where
> >>       toJValue = JBool
> >>       fromJValue (JBool b) = Right b
> >>       fromJValue _ = Left "not a JSON boolean"
> >>
> >>
> >> I don't understand how the JSON typeclass is defined, in particular
> >> the fromJValue definition.
> >
> > Given a JValue and a type
> > (like Bool, JValue, String, Maybe [(Integer, ())]), fromJValue returns
> > either
>
> a JValue and a type???
>

Apparently not the best way to express it.

The function fromJValue has the type

fromJValue :: JSON a => JValue -> Either JSONError a

Read that as "for any type a being an instance of the JSON class, 
fromJValue can convert¹ a JValue to the type Either JSONError a".

For different types a, fromJValue does different things if applied to the 
same JValue, more precisely, different fromJValue functions are called.
Which version of fromJValue is called depends on the type the type variable 
a is instantiated to at the call site. (So, in some sense, fromJValue also 
takes a type as an argument.)

Perhaps looking at things in a more homely setting helps.
Consider the Enum class and the function

toEnum :: Enum a => Int -> a

What happens if you enter `toEnum 5' at the prompt?
In hugs:

Hugs> toEnum 5
ERROR - Unresolved overloading
*** Type       : Enum a => a
*** Expression : toEnum 5

you get an error, hugs complains that it doesn't know which type to choose 
for the result. And how could it, there are many types to choose from. If 
you tell hugs which type to choose, be it by an explicit type signature or 
by some calling context, it works:

Hugs> toEnum 5 :: Char
'\ENQ'
Hugs> [toEnum 42, 'k']
"*k"
Hugs> :set +t
Hugs> [toEnum 12, 42]
[12,42] :: [Integer]      -- Why Integer? ²
Hugs> [toEnum 12, 42] :: [Rational]
[12 % 1,42 % 1] :: [Rational]

¹ Actually, it doesn't 'convert' the value, rather it constructs a new 
value based on the provided one, but saying 'convert' is less cumbersome.

² [toEnum 12, 42] can have type [a] for every type a that belongs to the 
two classes Enum and Num, illustrated by the example with an explicit 
signature. hugs must choose one or it would have to throw an unresolved 
overloading error as above.
The Haskell report (in section 4.3.4) specifies that under certain 
circumstances ambiguous types [like (Enum a, Num a) => a] are defaulted.
The defaulting rules say that in this case, the ambiguous type is defaulted 
to Integer - and that's why I've used hugs here, and not ghci, because ghci 
uses extended defaulting rules and does something different:

Prelude> toEnum 5
*** Exception: Prelude.Enum.().toEnum: bad argument
Prelude> toEnum 0
()

as you can see, ghci chooses the unit type () as the default here [the 
other expressions work as in hugs] and doesn't complain about an ambiguous 
type variable as in the fromJValue example.

> >> 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....
> >
> > fromJValue always takes a JValue as argument. That JValue can be a
> > wrapped String, a wrapped Bool, a wrapped number (Double), ...
>
> so, fromJValue takes a JValue and a type, or only a JValue?

On the source code level, it takes only a JValue, but it needs some context 
to resolve which instance to choose. There, functions can only take values 
as arguments, not types.
On a lower implementation level, it is possible that overloaded functions 
[type class methods] take explicit type arguments, but let the compiler 
writers worry about such details :)

> I was assuming the second,

On the implementation level, in GHC, it takes a dictionary and a JValue as 
arguments, but again, that's a low-level detail you shouldn't care about.
On the Haskell code level, your assumption is correct.

> but then my misunderstanding kicks in, I guess.
> I'll try to explain myself. When defining
>
> class JSON a [...], then I thought that for an instance I would have to
> identify the type of that instance and that all functions would work on
> that type. Thus, when defining
>
> instan JSON Bool [...] I was expecting that all the function definitions
> would have as argument a Bool.

No, Bool may also appear in the result type of the functions and not in the 
argument type(s). Return ing to the Enum class, that contains

toEnum :: Enum a => Int -> a
fromEnum :: Enum a => a -> Int

in the former, the instance type is the result type of the function, in the 
latter it's the argument type.
In the JSON class, we have

toJValue :: JSON a => a -> JValue

where it's the argument type, and

fromJValue :: JSON a => JValue -> Either JSONError a

where it's a parameter of the result type.

> toJValue is no problem there, but I don't
> see the fromJValue definition, since this matches against either (JBool
> b) or _ , but not a Bool...
>
> Another misunderstading on my side: if I call fromJValue (JBool True),
> which instance ofr fromJValue should be used: instance JSON JValue or
> instance JSON Bool.

That depends on the context in which (fromJValue (JBool True)) is called.
If the context determines that the type of that expression is 
(Either JSONError Bool), the (instance JSON Bool) is used; if it determines 
the type is (Either JSONError JValue), the (instance JSON JValue) is used.
If it doesn't determine the type of the expression, as in

print (fromJValue (JBool True))

, it's a compile-time error (ambiguous type variable/unresoled 
overloading), since no defaulting takes place for the JSON class.

> If we only look at the signature of the fromJValue
> functions, then both could match?
>

Yes, both match (and potentially many others), so instance selection must 
be driven by other factors. If the expression is e.g. a subexpression of

list = [fromJValue (JBool True), Right JNull]

the context determines the instance. 
Since both expressions belong to the same list, they must have the same 
type t.
fromJValues type says t = Either JSONError a for some a (we don't know yet 
which, and it can be any type belonging to the JSON class).
The type of (Right JNull) is Either b JValue, where b can be any type 
whatsoever, thus we find t = Either b JValue.
Putting both together, we find t = Either JSONError JValue, whence
list = [Right (JBool True), Right JNull].

If the context in which the expression occurs doesn't determine its type 
(and the defaulting rules don't fix it), you must help the compiler by an 
explicit type annotation.

> >> *Main>  fromJValue False
> >>
> >> <interactive>:1:11:
> >>       Couldn't match expected type `JValue' against inferred type
> >> `Bool' In the first argument of `fromJValue', namely `False'
> >>       In the expression: fromJValue False
> >>       In the definition of `it': it = fromJValue False
> >
> > That one should be pretty clear, fromJValue expects a JValue as
> > argument and gets a Bool, it's like calling
>
> Yes, but I guess you see why I try this given my misunderstanding above?
>
> >> *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>
> >
> > That's less easy.
> > The compiler/interpreter doesn't know which result type to use.
> >
> > fromJValue :: JSON a =>  JValue ->  Either JSONError a
> >
> > with which type should a be instantiated, should it use
> > - JValue, in which case the result would be
> > Right (JBool False)
> >
> > - Bool, in which case the result would be
> > Right False
> >
> > - String, in which case the result woulde be something like
> >      No instance for (JValue [Char])
> >        arising from a use of `fromJValue' at ...
> >
> > (unless you have such an instance in scope, then it would be something
> > like Left "not a JSON string")
> >
> > - Int, in which case you'd get analogous behaviour
> > - ...
> >
> >> Any pointers?
> >
> > In an actual programme, there is usually enough context to fix the
> > type variable a, then the compiler/interpreter knows what to do.
> > At the prompt or when there isn't enough context otherwise, you need
> > to explicitly tell the compiler/interpreter which type to use,
> >
> > *Main>  fromJValue (JBool False) :: Either JSONError Bool
> > Right False
> > *Main>  fromJValue (JBool False) :: Either JSONError JValue
> > Right (JBool False)
>
> Ah... OK, I think with these two examples the whole thing starts to make
> sense.
>
> When defining
>
> instance JSON Bool
>
> then this doesn't mean that the functions need to work just on Bool's,
> but rather that wherever there is an "a" in the typeclass definition,
> then this should be instantiated to a Bool, correct?
>

Yes.

>
>
> And now that we are at it... In the next page, 152 there is the
> following instance definition, but no explanation is (I think) given of
> what it means:
>
> instance (JSON a) => JSON [a] where
>
> until then all instance definitions where of the type
>
> instance JSON Int where ...
>
> How should I read that definition?

As a first approximation, read it as

"for all types a which are instances of JSON, the type [a] is also an 
instance of JSON, with the following methods ..."

However, instance resolution in GHC is done without taking the context 
(JSON a) into account, so for GHC it reads more like

"I will view all list types as instances of the JSON class, but if you try 
to use the class instance for a list type where the element type is not an 
instance of JSON, the programme will not compile. Nor will it compile if 
you try to define another instance of JSON for any list type [e.g. String] 
- at least, if you don't turn on some language extension(s)."

That is the cause of many puzzlements and problems.

>
> Thanks for you help,
> Ángel de Vicente



More information about the Haskell-Cafe mailing list