flexible contexts and context reduction

Sittampalam, Ganesh ganesh.sittampalam at credit-suisse.com
Thu Mar 27 05:00:25 EDT 2008


Tom Schrijvers wrote:

> On Wed, 26 Mar 2008, Ganesh Sittampalam wrote:

>> On Wed, 26 Mar 2008, Ross Paterson wrote:
>>
>>> On Wed, Mar 26, 2008 at 08:52:43PM +0000, Ganesh Sittampalam wrote:
>>>> I'm a bit confused about why the following program doesn't compile 
>>>> (in any of 6.6.1, 6.8.1 and 6.9.20080316). Shouldn't the Ord (a, b) 
>>>> context be reduced?
>>> 
>>> To use bar, you need (Ord a, Ord b).  You're assuming that Ord (a, b) 
>>> implies that, but it's the other way round.

> Logically, the implication holds. There's an equivalence:
>
> 	Ord a /\ Ord b <=> Ord (a,b)

Unfortunately, GHC accepts the following:

{-# LANGUAGE FlexibleInstances #-}
module Foo2 where

data Foo = Foo
  deriving Eq

instance Ord (Foo, Foo) where
  (Foo, Foo) < (Foo, Foo) = False

Cheers,

Ganesh

==============================================================================
Please access the attached hyperlink for an important electronic communications disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==============================================================================



More information about the Glasgow-haskell-users mailing list