Overlapping instances with "instance F a => G a"

Hi cafe! Happy New Year. I'm writing a version of the Binary typeclass that encodes values with host endianness, and I have the code at the bottom of the message. HostBinary provides the encoding/decoding interface, and with HostBinaryNum I want to be able to write only e.g. "instance HostBinaryNum Int32" for numeric types. I had the manual HostBinary Word8 and HostBinary Int8 instances before I wrote HostBinaryNum. What I can't see is why I get this error at all: Binary.hs:21:29: Overlapping instances for HostBinary Word8 arising from a use of ‘hget’ Matching instances: instance HostBinary Word8 -- Defined at Binary.hs:16:10 instance HostBinaryNum a => HostBinary a -- Defined at Binary.hs:26:10 In the second argument of ‘fmap’, namely ‘(hget :: Get Word8)’ In the expression: fmap fromIntegral (hget :: Get Word8) In an equation for ‘hget’: hget = fmap fromIntegral (hget :: Get Word8) and also why commenting out either the HostBinary Int8 or the HostBinaryNum a => HostBinary a instances fixes the problem; and yet, the HostBinaryNum Word8 is accepted! Doesn't "HostBinaryNum a => HostBinary a" create a HostBinary instance for all instances of HostBinaryNum only? So why would it cause problems with an Int8 instance, and why isn't the HostBinaryNum Word8 instance needed to trigger a collision with the explicit HostBinary Word8? GHC 7.8.3, if it matters. Thanks for any clarifiation you can provide, Bryan Binary.hs: {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} module Binary where import Data.Binary.Get import Data.Binary.Put import Data.Bits import Data.Int import Data.Word import Foreign.Storable class HostBinary a where hget :: Get a hput :: a -> Put instance HostBinary Word8 where hget = getWord8 hput = putWord8 instance HostBinary Int8 where hget = fmap fromIntegral (hget :: Get Word8) hput = hput . (fromIntegral :: Int8 -> Word8) class (Bits a, Integral a, Storable a) => HostBinaryNum a instance HostBinaryNum a => HostBinary a where hget = getNum hput = putNum --instance HostBinaryNum Word8 getNum :: (Bits a, Integral a, Storable a) => Get a getNum = undefined putNum :: (Bits a, Integral a, Storable a) => a -> Put putNum = undefined

On Thu, Jan 01, 2015 at 01:29:59PM -0800, Bryan Gardiner wrote:
Overlapping instances for HostBinary Word8
[..]
Doesn't "HostBinaryNum a => HostBinary a" create a HostBinary instance for all instances of HostBinaryNum only? [..] instance HostBinary Word8 where [..] instance HostBinaryNum a => HostBinary a where
AIUI `instance HostBinaryNum a => HostBinary a` means "Every instance of the form `HostBinary a` arises from an instance for `HostBinaryNum a`", so provding an additional instance `HostBinary Word8` creates (potential) overlap. Tom

On Thu, Jan 1, 2015 at 4:29 PM, Bryan Gardiner
Doesn't "HostBinaryNum a => HostBinary a" create a HostBinary instance for all instances of HostBinaryNum only? So why would it cause
No, it creates an instance for all types, then checks for HostBinaryNum at the point where it tries to use the instance. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Thu, 1 Jan 2015 17:15:31 -0500
Brandon Allbery
On Thu, Jan 1, 2015 at 4:29 PM, Bryan Gardiner
wrote: Doesn't "HostBinaryNum a => HostBinary a" create a HostBinary instance for all instances of HostBinaryNum only? So why would it cause
No, it creates an instance for all types, then checks for HostBinaryNum at the point where it tries to use the instance.
Brandon, Tom, thanks for the reponses. I can only claim rudimentary typeclass knowledge but I find it odd for the instance statement to create instances for all types if it's going to only be usable for types with HostBinaryNum instances. From my reading of the GHC manual, it's generally only an error when a conflict actually occurs, not if a conflict might occur. Is there a benefit to having it this way? Many thanks, Bryan
participants (3)
-
Brandon Allbery
-
Bryan Gardiner
-
Tom Ellis