> So the other question is whether this is useful. How often do people write 
> stuff like this?
>        f :: Ord [a] => a -> a -> Bool
>        f x y = x>y

> Nevertheless, I hadn't realised it was possible before, and now I can see it 
> is.

A closer example to what I was actually doing was this:

{-# LANGUAGE GADTs #-}
module Foo where

data Foo a where
   Foo1 :: a -> Foo a
   Foo2 :: Foo a -> Foo b -> Foo (a, b)

unFoo :: Ord a => Foo a -> a
unFoo (Foo1 a) = a
unFoo (Foo2 x y) = (unFoo x, unFoo y)

[in the real code I did actually use the Ord constraint in the base case]

The error I get is this:

Foo.hs:10:20:
    Could not deduce (Ord a2) from the context ()
      arising from a use of `unFoo' at Foo.hs:10:20-26
    Possible fix: add (Ord a2) to the context of the constructor `Foo2'
    In the expression: unFoo x
    In the expression: (unFoo x, unFoo y)
    In the definition of `unFoo': unFoo (Foo2 x y) = (unFoo x, unFoo y)

Foo.hs:10:29:
    Could not deduce (Ord b1) from the context ()
      arising from a use of `unFoo' at Foo.hs:10:29-35
    Possible fix: add (Ord b1) to the context of the constructor `Foo2'
    In the expression: unFoo y
    In the expression: (unFoo x, unFoo y)
    In the definition of `unFoo': unFoo (Foo2 x y) = (unFoo x, unFoo y)

Which suggests that GHC has also lost track of the fact that Ord (a, b) is 
true. But 
it would certainly be necessary to get from Ord (a, b) to (Ord a, Ord b) to get 
that
to work.

Ganesh

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

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

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to