Make a typeclass instance automatically an instance of another

What I'd like to achieve is that any instance of the following class ( SampleSpace ) should automatically be an instance of Show , because SampleSpace contains the whole interface necessary to create a String representation and hence all possible instances of the class would be virtually identical.

{-# LANGUAGE FlexibleInstances #-}
import Data.Ratio (Rational)                                               

class SampleSpace space where                                               
    events          :: Ord a => space a -> [a]                              
    member          :: Ord a => a -> space a -> Bool                        
    probability     :: Ord a => a -> space a -> Rational                    

instance (Ord a, Show a, SampleSpace s) => Show (s a) where                 
    show s = showLines $ events s                                           
        where                                                               
        showLines [] = ""                                                   
        showLines (e:es) = show e ++ ":   " ++ (show $ probability e s)
                                  ++ "n" ++ showLines es

Since, as I found out already, while matching instance declarations GHC only looks at the head, and not at contraints, and so it believes Show (sa) is about Rational as well:

[1 of 1] Compiling Helpers.Probability ( Helpers/Probability.hs, interpreted )

Helpers/Probability.hs:21:49:
    Overlapping instances for Show Rational
      arising from a use of ‘show’
    Matching instances:
      instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
        -- Defined in ‘GHC.Real’
      instance (Ord a, Show a, SampleSpace s) => Show (s a)
        -- Defined at Helpers/Probability.hs:17:10
    In the expression: show
    In the first argument of ‘(++)’, namely ‘(show $ probability e s)’
    In the second argument of ‘(++)’, namely
      ‘(show $ probability e s) ++ "" ++ showLines es

Question: is it possible (otherwise than by enabling overlapping instances) to make any instance of a typeclass automatically an instance of another too?


tl;dr : don't do that, or, if you insist, use -XOverlappingInstances .

  • This is not what the Show class is there for. Show is for simply showing plain data, in a way that is actually Haskell code and can be used as such again, yielding the original value.
  • SampleSpace should perhaps not be a class in the first place. It seems to be basically the class of types that have something like Map a Rational associated with them. Why not just use that as a field in a plain data type?
  • Even if we accept the design... such a generic Show instance (or, indeed, generic instance for any single-parameter class) runs into problems when someone makes another instance for a concrete type – in the case of Show , there are of course already plenty of instances around. Then how should the compiler decide which of the two instances to use? GHC can do it, in fact: if you turn on the -XOverlappingInstances extension, it will select the more specific one (ie instance SampleSpace s => Show (sa) is “overridden” by any more specific instance), but really this isn't as trivial as may seem – what if somebody defined another such generic instance? Crucial to recall: Haskell type classes are always open, ie basically the compiler has to assume that all types could possibly in any class. Only when a specific instance is invoke will it actually need the proof for that, but it can never proove that a type isn't in some class.
  • What I'd recommend instead – since that Show instance doesn't merely show data, it should be made a different function. Either

    showDistribution :: (SampleSpace s, Show a, Ord a) => s a -> String
    

    or indeed

    showDistribution :: (Show a, Ord a) => SampleSpace a -> String
    

    where SampleSpace is a single concrete type, instead of a class.

    链接地址: http://www.djcxy.com/p/43514.html

    上一篇: Haskell:如何通过“无实例”?

    下一篇: 让一个typeclass实例自动成为另一个实例