Reputation: 1434
In C, we define enum this way:
enum E {
E0,
E1,
E2 = 3,
E3
};
Note E2 = 3
expression, the enum type result in E0 == 0, E1 == 1, E2 == 3, E3 == 4
.
In Haskell, we have no way to specify the enumeration in the declaration. The only way to implement discontinuous enumeration is implementing Enum
class manually.
Is there any convenient way to do this?
I've write a demo using Template Haskell to generate the Enum
instance.
data E = E0
| E1
| E2_3
| E3
deriving Show
enum ''E
I wonder if there are libraries trying to fill this gap?
Upvotes: 4
Views: 558
Reputation: 27636
You can whip up something small & simple using Template Haskell's reifyAnnotations
feature.
First, we need to define an annotation type to hold enum values:
{-# LANGUAGE DeriveDataTypeable #-}
module Def where
import Data.Data
data EnumValue = EnumValue Int deriving (Typeable, Data)
Second, we need a bit of TH code to consume these annotations and turn them into Enum
instance definitions:
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module TH where
import Def
import Language.Haskell.TH.Syntax
import Language.Haskell.TH
import Control.Monad
import Data.List (mapAccumL)
import Data.Maybe
enumValues :: [(a, Maybe Int)] -> [(a, Int)]
enumValues = snd . mapAccumL (\next (x, mv) -> let v = fromMaybe next mv in (v+1, (x, v))) 0
enumFromAnns :: Name -> Q [Dec]
enumFromAnns name = do
TyConI (DataD _ _ _ cons _) <- reify name
eVals <- fmap enumValues $ forM cons $ \(NormalC conName []) -> do
anns <- reifyAnnotations (AnnLookupName conName)
let ev = case anns of
[EnumValue ev] -> Just ev
[] -> Nothing
return (conName, ev)
[d|
instance Enum $(conT name) where
fromEnum = $(lamCaseE [match (conP c []) (normalB $ lift v) [] | (c, v) <- eVals])
toEnum = $(lamCaseE [match (litP . IntegerL . fromIntegral $ v) (normalB $ conE c) [] | (c, v) <- eVals])|]
And then finally we can use it (via a small workaround to make sure the usage is in a new declaration group):
{-# LANGUAGE TemplateHaskell #-}
module AnnotatedEnumExample where
import Def
import TH
data E = E1
| E2
| E42
| E43
deriving Show
{-# ANN E1 (EnumValue 1) #-}
{-# ANN E42 (EnumValue 42) #-}
-- Force new declaration group
return []
enumFromAnns ''E
Example usage:
*AnnotatedEnumExample> map fromEnum [E1, E2, E42, E43] [1,2,42,43] *AnnotatedEnumExample> map toEnum [1, 2, 42, 43] :: [E] [E1,E2,E42,E43]
Upvotes: 6