Hi,

On 02/23/2011 04:40 PM, Kurt Stutsman wrote:
> [...]
> Test is actually a kind of Serializable class. I don't want to restrict it to only working with Enums, which is what your OverlappingInstances seems to address. Is there a better way for doing what I am trying to do?

Example:

import Data.BitSet

data GroupA = A1 | A2 | A3 deriving (Enum, Show)

data GroupB = B1 | B2  deriving (Enum, Show)

class Serializable t where
   get :: String -> t
   put :: t -> String

instance Enum e => Serializable e where
   get mask = {- convert mask to Int and then to a BitSet -}
   put bitset = {- convert BitSet to Int and then to String -}

You might want to use a wrapper type: (instead of the Serializable instance above)

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

newtype ByEnum e = ByEnum { unByEnum :: e }
    deriving (Eq, Ord, Read, Show, Enum)  -- just for convenience

instance Enum e => Serializable (ByEnum e) where
    get = ByEnum . {- same code as above -}
    put = {- same code as above -} . unByEnum

To see why this can't be done as you tried above, say that you have another instance of Serialize for types that are an instance of both Show an Read, serializing to/from a string using the 'show' and 'read' functions.

Then consider a type which is an instance of all Show, Read, and Enum, for example:

data Food = Meat | Vegetables deriving (Show, Read, Enum)

Which instance of Serializable should be used? The first one that was declared? Rather not...

An instance like

"If (Enum t), then (Serializable t) via the Enum instance; else, if (Show t, Read t), then (Serializable t) via the Show and Read instances; otherwise not (Serializable t)"

would be perfect, but unfortunately Haskell doesn't have a way to express this (yet?). Some steps[1] in this direction can however be taken with the current state of the language.

-- Steffen

[1] http://haskell.org/haskellwiki/GHC/AdvancedOverlap


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

Reply via email to