Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes

> I would use a simpler interface:
>
>    arithSequence :: Num a => a{-start-} -> a{-step-} -> [a]
>    
>    take 300 (arithSequence (-3.0) 0.02)
>    arithSequence (-3.0) 0.02
>    takeWhile (<3.01) (arithSequence (-3.0) 0.02)


Yes, this is better.
Generally, the idea was that the domains like  T = Float  hardly ever
need Enum, because  fromTo, succ  look counter-intuitive there.
Probably, what the users wanted was the arithmetic sequences inside 
T.  And the latters are achieved independently of  Enum.

-----------------------
But what  Enum  is for?
Maybe, it worth to consider the following.

1. Finitely-enumerated domain `a'

- the doubtless Enum instance. There fit

  toEnum     :: Integer -> Maybe a
  fromEnum   :: a -> Integer
  succ, pred :: a -> Maybe a

For example:   toEnum 0 :: Maybe Bool  = Just True
               toEnum 1 :: Maybe Bool  = Just False
               toEnum 2 :: Maybe Bool  = Nothing
               fromEnum False = 1
               succ True  = Just False
               succ False = Nothing

And we put that the numeration domain is  [0..h] :: [Integer],
toEnum, fromEnum  should be the reciprocally inverse bijections 
                                                      a <--> [0..h].
toEnum n  returns  Nothing  for  n  out of  [0..h].
This reflects that  toEnum  is a partial map.
These maps induce the ordering independent of  Ord; 
Ord  is not a superclass of  Enum;
succ, pred  are defined according to  fromEnum.


2. Countably-enumerated domain `a'

  toEnum, toEnum'     :: Integer -> a
  fromEnum, fromEnum' :: a -> Integer
  succ, pred, pred'   :: a -> a

toEnum, fromEnum  should be the reciprocally inverse bijections
between
                    a <--> [0..]

toEnum n         to break with error for  n < 0;
pred (toEnum 0)  to break with error.

toEnum', fromEnum'  should be the reciprocally inverse bijections
between
                                     a <--> Integer
I doubt how to eliminate these '-s.
For  Integer  looks better when mapped with  Integer,  rather than 
with  [0..],  and  NonNegativeInteger  looks better with  [0..] ...

What domains should be standardly countably-enumerated?
For example, any
                  data C a = C a deriving (Enum)

has to induce standardly  Enum  from  a  to  C a.

Should  Float  be standardly enumerated?
I suggest - it should not. 
Because  Float  is close ideologically to  RealNumber,  
and there does not exist a bijection  Integer <--> RealNumber:
there are too few of integers to enumerate the reals.
Nother reason is as follows for  Rational.

Should  Rational  be standardly enumerated?
I suggest - it should not.
Rational  can be enumerated bijectively with  [0..] :: [Integer].
But any such enumeration would be too "deliberate". 
There is only one definition of `compare' on Rational that agrees 
with the arithmetic. Therefore  Rational  is very naturally a 
*standard* instance of  Ord.
With the enumeration, the situation is different. 
It brings another ordering to  Rational,  which does not agree with
the arithmetic;  succ, pred  are considered in the sense of this 
Enum  ordering.
There are too many such enumerations. For each particular task 
exploiting some enumeration, the user has to choose its own 
enumeration for  Rational,  to make the solution efficient. Usually,
changing the enumeration changes many times the cost of solution.
Therefore, it is better to define the user instance rather than the 
standard one.

Similarly,  (a,b), [a]  should not have the standard Enum instances.

It remains, maybe, to unify the operation types for the 
finitely-enumerated and countably-enumerated domains.


------------------
Sergey Mechveliani
[EMAIL PROTECTED]






Reply via email to