[Haskell-cafe] Inheritance and Wrappers

Steffen Schuldenzucker sschuldenzucker at uni-bonn.de
Mon Jan 31 21:22:06 CET 2011


On 01/31/2011 08:58 PM, MattMan wrote:
> [...]
>
> data Wrapper a = Wrap a
> instance (Num a) =>  AbGroup (Wrapper a) where
>       add (Wrap i) (Wrap j) = Wrap(i+j)
>
> However, this is clumsy.  Is there something else I can do?  Thanks
This is the normal approach. You can do funny things with the 
OverlappingInstances extension, but it is probably not what you want.

The problem is that the compiler only considers the heads of the 
instance declarations when determining which instance to use for a 
specific type. So an instance like this:

 > instance (Num a) => AbGroup a where ...

means: Some type matching 'a' (that is, any type) is an instance of 
'AbGroup' if and only if it is an instance of 'Num'.

An additional instance like

 > instance AbGroup SomeData where ...

would then conflict with the instance above: As 'SomeData' in particular 
matches the type 'a', the compiler does not know which one to choose. 
You could argue that the latter is "more specific" than the former, so 
the compiler should choose that one. This is exactly what 
OverlappingInstances does, but it can have more, unwanted effects.

You can make your wrapper code less clumsy by deriving some instances 
such as

 > {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 > data Wrapper a = Wrap a deriving (Eq, Ord, Read, Show, Num)

-- Steffen





More information about the Haskell-Cafe mailing list