Having trouble with instance context

I am trying to create an instance of a class for data types deriving from Enum. When I try to specify this through a context on the instance definition, I get an error. When I do something similar with a function, it seems to work fine. Why does the instance not work? {------------ Example: ---------------} class Test t where func :: t -> Int -- This instance does not compile instance (Enum e) => Test e where func x = fromEnum x -- This function does work newfunc :: (Enum e) => e -> Int newfunc x = fromEnum x Thanks, Kurt

On 23 February 2011 13:10, Kurt Stutsman
I am trying to create an instance of a class for data types deriving from Enum. When I try to specify this through a context on the instance definition, I get an error. When I do something similar with a function, it seems to work fine. Why does the instance not work?
What's the error? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ivan Lazar Miljenovic wrote:
On 23 February 2011 13:10, Kurt Stutsman
wrote: I am trying to create an instance of a class for data types deriving from Enum. When I try to specify this through a context on the instance definition, I get an error. When I do something similar with a function, it seems to work fine. Why does the instance not work?
What's the error?
Illegal instance declaration for `Test e' (All instance types must be of the form (T a1 ... an) where a1 ... an are type *variables*, and each type variable appears at most once in the instance head. Use -XFlexibleInstances if you want to disable this.) In the instance declaration for `Test e'

On Tue, Feb 22, 2011 at 8:37 PM, Kurt Stutsman
Ivan Lazar Miljenovic wrote:
On 23 February 2011 13:10, Kurt Stutsman
wrote: I am trying to create an instance of a class for data types deriving from Enum. When I try to specify this through a context on the instance definition, I get an error. When I do something similar with a function, it seems to work fine. Why does the instance not work?
What's the error?
Illegal instance declaration for `Test e' (All instance types must be of the form (T a1 ... an) where a1 ... an are type *variables*, and each type variable appears at most once in the instance head. Use -XFlexibleInstances if you want to disable this.) In the instance declaration for `Test e'
As the error says, compiling with the flag '-XFlexibleInstances' will make the message go away. You can also add a language pragma to the top of your source file: {-# LANGUAGE FlexibleInstances #-} Antoine
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Antoine Latter wrote:
As the error says, compiling with the flag '-XFlexibleInstances' will make the message go away.
You can also add a language pragma to the top of your source file:
{-# LANGUAGE FlexibleInstances #-}
Antoine
When I enable that flag, I then also have to enable -XUndecidableInstances. It does work with those extensions enabled. When I was reviewing the Haskell language specification on haskell.org, it certainly looked like what I was doing was supported by the language. I found some comments on GHC's site about the reasoning behind these flags, but I couldn't tell if they were restrictions GHC had added to their implementation or if they derive from the language spec. Is this kind of instance allowed by the spec? Thanks again, Kurt

On Wed, 2011-02-23 at 08:42 -0600, Kurt Stutsman wrote:
When I was reviewing the Haskell language specification on haskell.org, it certainly looked like what I was doing was supported by the language. I found some comments on GHC's site about the reasoning behind these flags, but I couldn't tell if they were restrictions GHC had added to their implementation or if they derive from the language spec. Is this kind of instance allowed by the spec?
FlexibleInstances and UndecidableInstances are language extensions that relax the rules in the Haskell Report. If they are needed, then the instances you are writing are not allowed by the spec. -- Chris

On Wednesday 23 February 2011 15:42:46, Kurt Stutsman wrote:
Antoine Latter wrote:
As the error says, compiling with the flag '-XFlexibleInstances' will make the message go away.
You can also add a language pragma to the top of your source file:
{-# LANGUAGE FlexibleInstances #-}
Antoine
When I enable that flag, I then also have to enable -XUndecidableInstances. It does work with those extensions enabled.
When I was reviewing the Haskell language specification on haskell.org, it certainly looked like what I was doing was supported by the language.
No, it's not. The language report says an instance head must have the form (tyCon a1 ... an), where tyCon is a type constructor and a1 ... an are *distinct* type variables (appropriate in number so that the head has the correct kind). In instance (Enum e) => Test e where ..., the tyCon is not present. Since this is too restrictive for many cases, most implementations have extensions allowing more liberal instance declarations (omitting the tyCon part, allowing repeated type variables, ...). Note however, that the above instance means "all types are instances of Test, and using a Test method on a type which doesn't belong to Enum is a static error" in GHC [because the instance selection in GHC doesn't take the part before the '=>' into account, so it sees 'instance Test e where']. If you want to declare any other instances of Test, you need to enable OverlappingInstances, which is a whole 'nother can of worms.
I found some comments on GHC's site about the reasoning behind these flags, but I couldn't tell if they were restrictions GHC had added to their implementation or if they derive from the language spec.
They're not restrictions but extensions.
Is this kind of instance allowed by the spec?
Thanks again, Kurt

Daniel Fischer wrote:
No, it's not. The language report says an instance head must have the form
(tyCon a1 ... an),
where tyCon is a type constructor and a1 ... an are *distinct* type variables (appropriate in number so that the head has the correct kind).
In instance (Enum e) => Test e where ..., the tyCon is not present.
Since this is too restrictive for many cases, most implementations have extensions allowing more liberal instance declarations (omitting the tyCon part, allowing repeated type variables, ...).
Note however, that the above instance means "all types are instances of Test, and using a Test method on a type which doesn't belong to Enum is a static error" in GHC [because the instance selection in GHC doesn't take the part before the '=>' into account, so it sees 'instance Test e where']. If you want to declare any other instances of Test, you need to enable OverlappingInstances, which is a whole 'nother can of worms.
Excellent! That was just the kind of information I was looking for. Thanks. Going back to my original problem then, I am encoding and decoding from a file that contains many bitsets. In my Haskell code, I am using Data.BitSet in conjunction with Enums I am creating for each kind of bitset. I thought the syntax I was using before would be perfect for using the same code to transcode between the bitmask integer and the internal representation. 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 -} Thanks, Kurt

On 23 February 2011 15:40, Kurt Stutsman
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 -}
I looks like all you need is for objects to be enumerable, i.e have instances of Enum. So instead of the above class, can you manage with these two functions? get :: Enum e => e -> Int put :: BitSet -> String Type classes give you type-based dispatch - *but* they are overkill if you don't actually need type-base dispatch.

Stephen Tetley wrote:
On 23 February 2011 15:40, Kurt Stutsman
wrote: 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 -}
I looks like all you need is for objects to be enumerable, i.e have instances of Enum. So instead of the above class, can you manage with these two functions?
get :: Enum e => e -> Int
put :: BitSet -> String
Type classes give you type-based dispatch - *but* they are overkill if you don't actually need type-base dispatch.
I need to support non-enumerable data types as well. That's why I wanted the Serializable class. For those non-enumerable types, I can create a custom instance of the Serializable class. But for Enums, I will always do the same thing, so implementing Serializable for all Enum types is really overkill.

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

From Kurt Stutsman
on Wed, February 23, 2011 9:40:09 AM
No, it's not. The language report says an instance head must have the form
(tyCon a1 ... an),
where tyCon is a type constructor and a1 ... an are *distinct* type variables (appropriate in number so that the head has the correct kind).
In instance (Enum e) => Test e where ..., the tyCon is not present.
Since this is too restrictive for many cases, most implementations have extensions allowing more liberal instance declarations (omitting the tyCon part, allowing repeated type variables, ...).
Note however, that the above instance means "all types are instances of Test, and using a Test method on a type which doesn't belong to Enum is a static error" in GHC [because the instance selection in GHC doesn't take the
Daniel Fischer wrote: part before the '=>' into account, so it sees 'instance Test e where'].
If you want to declare any other instances of Test, you need to enable OverlappingInstances, which is a whole 'nother can of worms.
Excellent! That was just the kind of information I was looking for. Thanks.
Going back to my original problem then, I am encoding and decoding from a file that contains many bitsets. In my Haskell code, I am using Data.BitSet in conjunction with Enums I am creating for each kind of bitset. I thought the syntax I was using before would be perfect for using the same code to transcode between the bitmask integer and the internal representation. 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?
Overall, I think the best solution for this case is to explicitly indicate the types that you want to have a Serializable instance based on an Enum instance. In the most straightforward way, you indicate this for a type T with a phrase like instance Binary T where {get=getEnum,put=putEnum} after defining once and for all the generic getEnum :: (Enum a) => Get a putEnum :: (Enum a) => a -> Put () If you find this is still too long, you can use Template Haskell to abbreviate it to something like binaryFromEnum [''T1, ''T2, ''T3, ''T4] Splicing identifiers seems not to work properly, but if it did this could be defined like serializeFromEnum ts = liftM concat $ mapM (\tyName -> [d| instance Binary $(conT tyName) where {get=getEnum;set=setEnum} |]) ts instead, I get errors like "Illegal instance declaration for `Binary t_tr' (All instance types must be of the form (T a1 ... an) ..." It seems there's some attempt at freshness that interferes with using the provided names. Defining it directly in terms of InstanceD and such is straightforward, but tedious. Brandon
participants (8)
-
Antoine Latter
-
Brandon Moore
-
Chris Smith
-
Daniel Fischer
-
Ivan Lazar Miljenovic
-
Kurt Stutsman
-
Steffen Schuldenzucker
-
Stephen Tetley