[Haskell-cafe] Having trouble with instance context
Brandon Moore
brandon_m_moore at yahoo.com
Wed Feb 23 18:14:27 CET 2011
> From Kurt Stutsman <kstutsman at gmail.com> on Wed, February 23, 2011 9:40:09 AM
>
> 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?
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
More information about the Haskell-Cafe
mailing list