> I don't see much gain. It will break previously working code and the
> workaround to the breakage will likely be manually reimplementing enumFromTo
> in each instance.

As an aside, many years ago I did exactly that after being bit by Enum
infelicities, and while you could say it's a reimplementation, in my
opinion it's a better implementation:

-- | Enumerate an inclusive range.  Uses multiplication instead of successive
-- addition to avoid loss of precision.
--
-- Also it doesn't require an Enum instance.
range :: (Num a, Ord a) => a -> a -> a -> [a]
range start end step = go 0
    where
    go i
        | step >= 0 && val > end = []
        | step < 0 && val < end = []
        | otherwise = val : go (i+1)
        where val = start + (i*step)

-- | Enumerate a half-open range.
range' :: (Num a, Ord a) => a -> a -> a -> [a]
range' start end step = go 0
    where
    go i
        | step >= 0 && val >= end = []
        | step < 0 && val <= end = []
        | otherwise = val : go (i+1)
        where val = start + (i*step)

-- | Infinite range.
range_ :: (Num a) => a -> a -> [a]
range_ start step = go 0
    where go i = start + (i*step) : go (i+1)

_______________________________________________
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime

Reply via email to