I have three small (and late) prelude/library proposals to add:

1.  The Show class
~~~~~~~~~~~~~~~~~~
One of the first things proposed when StdHaskell started
was to make it possible to make a type an instance of Show
by defining 'show' rather than by defining 'showsPrec'.  More
elaborate things were also proposed, but I think the following
change gets the main benefit without falling into the major-change
tarpit:

        * remove the current definition of show, which is
                show x = showsPrec 0 x ""

        * Add 'show' as a class method of class Show, to give:

                class  Show a  where
                        showsPrec :: Int -> a -> ShowS
                        show        :: a -> String              -- NEW
                        showList  :: [a] -> ShowS

                        showsPrec _ x s = show x ++ s
                        show x      = showsPrec 0 x ""
                        showList        = ...existing default declaration

This breaks nothing (show has the same type as before), but it allows
someone to say

                instance Show T where
                   show x = ...

to make T an instance of Show.   Thanks to Richard Bird for pointing
out this omission.


2.  Maybe.unfoldr
~~~~~~~~~~~~~~~~~
Erik Meijer points out that the definition of 'unfoldr' in
Maybe is very non-standard:

        unfoldr                :: (a -> Maybe (b,a)) -> a -> (a,[b])
        unfoldr f x =
         case f x of
           Just (x',y) -> let (ys,x'') = unfoldr f x' in (x'',y:ys)
           Nothing     -> (x,[])

The standard (and efficient) definition of unfold 
(e.g. Gibbons, ICFP'98)  is:

        unfoldr :: (b -> Maybe (a,b)) -> b -> [a]
        unfoldr f b = case (f b) of
                        Nothing    -> []
                                Just (a,b) -> a : unfoldr f b

(I call it unfoldr, not unfold, because we use foldr, not fold.)
Notice that the final value of 'b' isn't returned.

We still have the identity:

        unfoldr f' (foldr f z xs) == xs

if the following holds: 

        f' (f x y) = Just (x,y)
        f' z       = Nothing

Perhaps the current version of unfoldr is useful, but it should
not be called unfold(r).

I propose to replace the current unfoldr with the standard one.
I doubt that'll hurt anyone.


3.  Enumeration of rationals
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
At present, Haskell doesn't allow
        [1..10 :: Rational]
even though it does allow
        [1..10 :: Float] and [1..10 :: Double]

Personally, I don't think Float and Double should be in Enum,
but they are and I don't propose to fiddle with that.  But it's then
clearly totally bizarre that Rational is not.

The reason is that the fromEnum method is not defined for Ratio.
The obvious thing to do is to define the Enum methods for Ratio
in *exactly* the way we do for Float and Double:

instance  (Integral a)  => Enum (Ratio a)  where
    toEnum           =  fromIntegral
    fromEnum         =  fromInteger . truncate   -- may overflow
    enumFrom         =  numericEnumFrom
    enumFromThen     =  numericEnumFromThen
    enumFromTo       =  numericEnumFromTo
    enumFromThenTo   =  numericEnumFromThenTo

Now it is nicely uniform.  Thanks to Alastair Reid for pointing this out.


Comments welcome, as ever.

Simon


Reply via email to