Ara Vartanian
Ara Vartanian

Reputation: 1563

Is there some way to define an Enum in haskell that wraps around?

Consider I was designing a Monopoly game:

data Board = GO | A1 | CC1 | A2 | T1 | R1 | B1 | CH1 | B2 | B3 | 
  JAIL | C1 | U1 | C2 | C3 | R2 | D1 | CC2 | D2 | D3 | 
  FP | E1 | CH2 | E2 | E3 | R3 | F1 | F2 | U2 | F3 | 
  G2J | G1 | G2 | CC3 | G3 | R4 | CH3 | H1 | T2 | H2
  deriving (Show, Enum, Eq)

I want:

succ H2 == GO

But instead:

*** Exception: succ{Board}: tried to take `succ' of last tag in enumeration

Is there a typeclass for expressing an enumeration that wraps around?

Upvotes: 26

Views: 5388

Answers (6)

senjin.hajrulahovic
senjin.hajrulahovic

Reputation: 3191

You could define the typeclass and instance below. You would just need to also derive Bounded

class (Eq a, Enum a, Bounded a) => CyclicEnum a where
  cpred :: a -> a
  cpred d
    | d == minBound = maxBound
    | otherwise = pred d
  
  csucc :: a -> a
  csucc d
    | d == maxBound = minBound
    | otherwise = succ d
    

instance CyclicEnum Board

The example is from the amazing book: Haskell in Depth

Upvotes: 1

Vito Canadi
Vito Canadi

Reputation: 101

With Eq you can check if it's the last element.

next :: (Eq a, Enum a, Bounded a) => a -> a
next = bool minBound <$> succ <*> (/= maxBound)

Upvotes: 2

dfeuer
dfeuer

Reputation: 48601

There is a disgusting way to define an efficient wrapping Enum instance without doing much by hand.

{-# LANGUAGE MagicHash #-}

import GHC.Exts (Int (..), tagToEnum#, dataToTag# )

-- dataToTag# :: a -> Int#
-- tagToEnum# :: Int# -> a

Now you can write

data Board = ... deriving (Eq, Ord, Bounded)

instance Enum Board where
  fromEnum a = I# (dataToTag# a)

  toEnum x | x < 0 || x > fromEnum (maxBound :: Board) =
    error "Out of range"
  toEnum (I# t) = tagToEnum# t
  succ x | x == maxBound = minBound
         | otherwise == toEnum (fromEnum x + 1)
  pred x ....

Upvotes: 4

T_S_
T_S_

Reputation: 173

I know this is an old question but I just had this problem and I solved it this way.

data SomeEnum = E0 | E1 | E2 | E3
               deriving (Enum, Bounded, Eq)

-- | a `succ` that wraps 
succB :: (Bounded a, Enum a, Eq a) => a -> a 
succB en | en == maxBound = minBound
         | otherwise = succ en

-- | a `pred` that wraps
predB :: (Bounded a, Enum a, Eq a) => a -> a
predB en | en == minBound = maxBound
         | otherwise = pred en  

The solution derives both Enum and Bounded but avoids abusing pred and succ as suggested.

Incidently, I found that having

allSomeEnum = [minBound..maxBound] :: [SomeEnum] 

can be useful. That requires Bounded.

Upvotes: 7

David Miani
David Miani

Reputation: 14668

The simplest option is to make Board an instance of Bounded (can be auto derived as well), and use the following helper functions:

next :: (Enum a, Bounded a) => a -> a
next = turn 1

prev :: (Enum a, Bounded a) => a -> a
prev = turn (-1)

turn :: (Enum a, Bounded a) => Int -> a -> a
turn n e = toEnum (add (fromEnum (maxBound `asTypeOf` e) + 1) (fromEnum e) n)
    where
      add mod x y = (x + y + mod) `rem` mod

Example Use:

> next H2
G0
> prev G0
H2
> next F1
F2

(inspired by the the thread at http://www.mail-archive.com/[email protected]/msg37258.html ).

If you really need to use succ and pred instead, I don't believe there is any laws regarding implementations of Enum such that succ (succ x) /= x for all x (even though that is how most work). Therefore you could just write a custom implementation of Enum for your type that exhibits the wraparound you desire:

instance Enum Board where
  toEnum 0 = G0
  toEnum 1 = A1
  ...
  toEnum 40 = H2
  toEnum x = toEnum (x `mod` 40)

  fromEnum G0 = 0
  fromEnum A1 = 1
  ...
  fromEnum H2 = 40

That is very tedious to implement though. Also, the type shouldn't also implement Bounded when using a circular definition of Enum, as that breaks a rule regarding Bounded that succ maxBound should result in a runtime error.

Upvotes: 22

Neil Brown
Neil Brown

Reputation: 3558

A simpler solution than nanothief:

nextBoard :: Board -> Board
nextBoard H2 = GO
nextBoard t = succ t

I don't think you'll be able to use Enum directly for what you want, but this solution quickly wraps it to form the behaviour you want.

Upvotes: 30

Related Questions