* Playing around, learning the basics, reinventing the wheel...

I had been playing around with some classes, primarily to learn for
myself, being new to the Haskell language, when I got the report on
the current status of Haskell 1.3. The classes I had played with had
some similarities to some of the proposals for the new prelude, yet I
had made it in a quite different way. Trying to combine the two
styles, I ran into an unexpected problem. This problem I am naive
enough to believe could be solved by a simple language extension. 

Using Gofer, I had made some classes that could be used for
implementing ordering and other things for enumeration (data T=T1 |
T2 | T3) types but not restricted to those. I made 4 minimal classes
with just 1 function in each.  (I thought this would be most general.
Something having a minimum value, in my view, didn't necessarily
imply it would have a maximum value.) So:

class FromInt a where
        fromInt:: Int->a

class ToInt a where
        toInt:: a->Int

class MaxVal a where
        maxVal:: a

class MinVal a where
        minVal:: a

-- I then used this as follows:

data T = T1 | T2 | T3

instance ToInt T where
        toInt e = case e of
                T1 -> 1
                T2 -> 2
                T3 -> 3

instance Eq T where
        a == b = toInt a == toInt b

instance Ord T where
        a <= b = toInt a <= toInt b

-- And so on. The MaxVal and MinVal classes also where used to make a generic
-- implementation of a bounded Enum class, generalizing how it was made in the
-- Gofer prelude for Char:

instance (FromInt a, ToInt a, MinVal a, MaxVal a) => Enum a where
    enumFrom c          = map fromInt [toInt c .. toInt (maxVal `asTypeOf` c)]
    enumFromThen c c'   = map fromInt [toInt c, 
                                       toInt c' .. toInt (lastVal `asTypeOf` c)]
                          where lastVal = if c' < c then minVal else maxVal


-- This worked to my great delight! And I had began to learn the basics
-- of the type system in Haskell. My only problem was that I had to use
-- (maxVal `asTypeOf` c) instead of (maxVal::a). I believe the reason
-- for this might be clear when I learn more. Somebody have a clue?

*       Running into a problem: type class synonyms are not synonymous?

Then, I got the report on the developments of Haskell 1.3 and began to read
it with great curiosity. I then found the Bounded class, containing
corresponding functions to MinVal and MaxVal. A question then occured to me:
Why not have separate classes as I had done? Would not that perhaps be more
general, increasing the possibilities for reuse? (Without having to stub out
one of minBound or maxBound if you use it for a type without one of them.)
On the other hand, I saw the convenience of having both minBound and maxBound
in the same class, decreasing the number of classes that have to be mentioned
in various cases. But I thought, then, why not derive the Bounded class
>from MinVal and MaxVal - would not that then be equivalent? So I tried

class (MinVal a, MaxVal a)=>Bounded a   -- This was allowed, but then...

instance Bounded T where
        maxVal = T3
        minVal = T1

-- That didn't work! (Gofer said: ERROR "tst.gs" (line 45): No member
 "maxVal" in class "Bounded") Maybe I had done something wrong, or Gofer
does not allow something that would be allowed in Haskell? I suspect
however that I am simply not supposed to do this in either Haskell or Gofer...

Instead I had to use two separate instantiaions, exactly as before
I declared the Bounded class:

instance MinVal T where
        minVal = T1
instance MaxVal T where
        maxVal = T3

This seems to be somewhat unnecessary, wouldn't it be quite possible
for a compiler to transform the instantiation of Bounded to the two
instantiations of MinVal and MaxVal?

Maybe this would be a useful development of Haskell?

*       Should Bounded be derived from Ord?

The Bounded class that was suggested for Haskell 1.3 was derived from
Ord. Myself playing with similar things I derived MinVal and MaxVal
>from nothing - I thought this more general. Maybe the reason for
having Bounded derived from Ord was to imply that its functions shall
satisfy certain laws, probably as being min/max as defined by the
ordering functions in Ord. But as I don't see how this can be
guaranteed by deriving Bounded from Ord, I would think that it could
as well be standalone (or derived from something like MinBound and
MaxBound if possible); for more generality and less dependency between
the classes in the system.

For example, the new proposal says:

> ...
> Programmers are free to define a class for partial orderings; here, we
> simply state that Ord is reserved for total orderings.

That seems to imply also that a programmer should not use Bounded on
types that have no total ordering. I believe this might be an unnecessary
restriction.

*       Can toInt be fromEnum and toEnum fromInt?

New functions fromEnum and toEnum were proposed to be added to Haskell 1.3
prelude as follows:

> * Replace the functions ord and chr with the functions:
>
> fromEnum :: (Bounded a, Enum a) => a -> Int
> fromEnum x = diff x (minBound x)
>
> toEnum :: (Bounded a, Enum a) => Int -> a
> toEnum x = succ (minBound x) x

It was further mentioned in Notes that: 

> The names fromEnum and toEnum are misleading since
> their types involve both Enum and Bounded.  We couldn't face writing 
> fromBoundedEnum and toBoundedEnum.  Suggestions
> welcome. 

Maybe names like ToInt and FromInt could be used for this?
How about the following, assuming the proposed diff and succ functions:

instance (Bounded a, Enum a) => ToInt a where
        toInt x = diff x (minBound x)
        
instance (Bounded a, Enum a) => FromInt a where
        fromInt x = succ (minBound x) x

---

I would be very interested and grateful for any comments on these and related
subjects. (Please try to be polite about my ignorance, though, if possible...)

Sverker Nilsson
-------------------------------
S. Nilsson Computer System AB
Ekholmsv. 28B
S-582 61 LINKOPING


Reply via email to