akonsu
akonsu

Reputation: 29556

How does enumFromTo work?

I cannot add a number to a Char; the following will fail to compile 'a' + 1. But yet, ['a'..'z'] successfully creates a string in which each of the character value is incremented. Is there a special function that can increment a Char?

I know that I can do chr (ord c + 1).

How does the ['a'..'z'] or the underlying enumFromTo function increment the characters in the resulting String?

Upvotes: 8

Views: 1329

Answers (2)

ben_landau
ben_landau

Reputation: 11

I think you're after the pred and succ methods, which return the predecessor or successor of Enum a. The problem is that for a Bounded Enum, if you apply succ on the maximum member of the set you will get an error.

Bearing this in mind, you can define enumFromTo recursively as so (avoiding dangerous succ calls):

eftEnum :: (Enum a, Eq a, Ord a) => a -> a -> [a]
eftEnum a b 
    | a  > b = []
    | a == b = [a]
    | otherwise = a : rest 
        where rest = eftEnum (succ a) b

Upvotes: 1

Daniel Wagner
Daniel Wagner

Reputation: 152957

Yes, there is a special function that can add to a Char, from the same Enum class that enumFromTo is from, named succ. Beware that it is partial: succ maxBound is undefined, so take care to check the value of the character before you apply succ. succ is indeed the same as \c -> chr (ord c + 1), as you can verify with the universe package:

> let avoidMaxBound f x = if x == maxBound then Nothing else Just (f x)
> avoidMaxBound succ == avoidMaxBound (\c -> chr (ord c + 1))
True

In fact the implementation of succ in GHC is quite close to the function you suggested:

instance  Enum Char  where
    succ (C# c#)
       | isTrue# (ord# c# /=# 0x10FFFF#) = C# (chr# (ord# c# +# 1#))
       | otherwise             = error ("Prelude.Enum.Char.succ: bad argument")

However, succ is not used in the implementation of enumFromTo in GHC:

instance  Enum Char  where
    {-# INLINE enumFromTo #-}
    enumFromTo (C# x) (C# y) = eftChar (ord# x) (ord# y)
{-# RULES
"eftChar"       [~1] forall x y.        eftChar x y       = build (\c n -> eftCharFB c n x y)
#-}

-- We can do better than for Ints because we don't
-- have hassles about arithmetic overflow at maxBound
{-# INLINE [0] eftCharFB #-}
eftCharFB :: (Char -> a -> a) -> a -> Int# -> Int# -> a
eftCharFB c n x0 y = go x0
                 where
                    go x | isTrue# (x ># y) = n
                         | otherwise        = C# (chr# x) `c` go (x +# 1#)

{-# NOINLINE [1] eftChar #-}
eftChar :: Int# -> Int# -> String
eftChar x y | isTrue# (x ># y ) = []
            | otherwise         = C# (chr# x) : eftChar (x +# 1#) y

If you can squint past the nastiness that exists primarily for efficiency reasons, you can see that eftChar is essentially using succ, but an inlined version of it rather than an actual call to succ (here, to avoid boxing and re-boxing the Char being manipulated).

Upvotes: 5

Related Questions