[Haskell-cafe] Newbie Q: Deriving MyOrd from Eq problem

Daniel Fischer daniel.is.fischer at web.de
Wed Jul 26 13:24:10 EDT 2006


Am Mittwoch, 26. Juli 2006 16:20 schrieb Dmitri O.Kondratiev:
> On 7/25/06, Jared Updike <jupdike at gmail.com> wrote:
> > > I am trying to derive MyOrd class from Eq (Prelude):
> > >
> > > class Eq a => MyOrd a where
> > >         (%<=), (%>), (%>=) :: a -> a -> Bool
> > >         x %<= y = (x < y || x == y)
> > >         x %> y =  y < x
> > >         x %>= y = (y < x || x == y)
> > >
> > > Q: What's wrong?  Why 'Ord' gets into play here?
> >
> > You are using < which is a function on types that instance the class
> > Ord, so the compiler is telling you to add (Ord a) to the same place
> > you have (Eq a) or don't use < or > or any function in the class Ord.
> > You can the prelude and thus the Ord class and make your own < and >
> > functions but you can't make them refer to the "real" < and >
> > functions without Ord because that is where they live.
> >
> >   Jared.
> > --
> > http://www.updike.org/~jared/
> > reverse ")-:"
>
> -- Ok,  then I can derive MyOrd class directly from Ord:
>
> class Ord a => MyOrd a where
> 	(%<), (%<=), (%>), (%>=) :: a -> a -> Bool
> 	x %< y = x < y
> 	x %<= y = (x < y || x == y)
> 	x %> y =  y < x
> 	x %>= y = (y < x || x == y)
>
> instance (MyOrd a, MyOrd b) => MyOrd (a,b) where
> 	(x1, y1) %< (x2, y2) = (x1 %< x2) && (y1 %< y2)
> 	(x1, y1) %> (x2, y2) = (x1 %> x2) && (y1 %> y2)
> 	(x1, y1) %<= (x2, y2) = (x1 %<= x2) && (y1 %<= y2)
> 	(x1, y1) %>= (x2, y2) = (x1 %>= x2) && (y1 %>= y2)
>
> greaterMyOrd :: (MyOrd (a, b)) => (a, b) -> (a, b) -> Bool

The Haskell98 way to give the type is
greaterMyOrd :: (MyOrd a, MyOrd b) => (a,b) -> (a,b) -> Bool

> greaterMyOrd (x,y) (z,t) = (x,y) %> (z,t)
>
> -- This should work, right? Yet I get this error message:
>
> ClassTest.hs:39:0:
>     Non-type variables in constraint: MyOrd (a, b)
>     (Use -fglasgow-exts to permit this)
>     In the type signature:
>       greaterMyOrd :: (MyOrd (a, b)) => (a, b) -> (a, b) -> Bool
> Failed, modules loaded: none.

As Janis Voigt mentioned, this sort of constraint needs extensions because 
it's not Haskell98

>
> -- Notwithstanding :) when i comment out declaration:
>
> -- greaterMyOrd :: (MyOrd (a, b)) => (a, b) -> (a, b) -> Bool
>
> -- program gets compiled and checking type of  'greaterMyOrd' gives:
>
> *ClassTest> :t greaterMyOrd
> greaterMyOrd :: (MyOrd (a, b)) => (a, b) -> (a, b) -> Bool
>
> -- which is the same as I tried to declare in the program source.
> What is hapenning here?

hugs infers
MyOrd> :t greaterMyOrd
greaterMyOrd :: (MyOrd a, MyOrd b) => (b,a) -> (b,a) -> Bool

as Janis pointed out, ghc doesn't do complete context reduction, I don't know 
why either. It also happens for standard classes, e.g.
Prelude> let equ xs@(_:_) ys = xs == ys; equ [] ys = null ys
Prelude> :t equ
equ :: (Eq [a]) => [a] -> [a] -> Bool


>
> -- Now, when trying to use function 'greaterMyOrd' I get:
>
> *ClassTest> greaterMyOrd (2, 3) (1, 2)
>
> <interactive>:1:0:
>     Ambiguous type variable `a' in the constraints:
>       `MyOrd a' arising from use of `greaterMyOrd' at <interactive>:1:0-11
>       `Num a' arising from the literal `2' at <interactive>:1:14
>     Probable fix: add a type signature that fixes these type variable(s)
>
> <interactive>:1:0:
>     Ambiguous type variable `b' in the constraints:
>       `MyOrd b' arising from use of `greaterMyOrd' at <interactive>:1:0-11
>       `Num b' arising from the literal `3' at <interactive>:1:17
>     Probable fix: add a type signature that fixes these type variable(s)
>
> -- Then I try to declare argument types explicitely and get this:
>
> *ClassTest> greaterMyOrd (2::MyOrd, 3::MyOrd) (1::MyOrd, 2::MyOrd)
>
> <interactive>:1:17:
>     Class `MyOrd' used as a type
>     In an expression type signature: MyOrd
>     In the expression: 2 :: MyOrd
>     In the first argument of `greaterMyOrd', namely `(2 :: MyOrd, 3 ::
> MyOrd)' *ClassTest>

Janis already answered that
>
> -- I am lost. Please enlight me, what am I doing wrong trying to
> create my own class, its instance and then using it.
> Thanks !

another problem is that you did not specify any instances of MyOrd, so up to 
now there aren't any:
*MyOrd> greaterMyOrd (True, 'b') (False, 'c')

<interactive>:1:0:
    No instances for (MyOrd Bool, MyOrd Char)
      arising from use of `greaterMyOrd' at <interactive>:1:0-11
    Probable fix: add an instance declaration for (MyOrd Bool, MyOrd Char)
    In the definition of `it': it = greaterMyOrd (True, 'b') (False, 'c')

note that here ghci doesn't ask for an instance MyOrd (Bool, Char), but for 
separate instances MyOrd Bool and MyOrd Char

and even if you provide an instance MyOrd Integer (or Int, ...), you'll still 
need to give expression type signatures, because defaulting does only work 
with standard classes (cf. the Haskell-Report, sect. 4.3.4)
*MyOrd> greaterMyOrd (2,3) (1,2)

<interactive>:1:0:
    Ambiguous type variable `a' in the constraints:
      `MyOrd a' arising from use of `greaterMyOrd' at <interactive>:1:0-11
      `Num a' arising from the literal `2' at <interactive>:1:14
    Probable fix: add a type signature that fixes these type variable(s)

<interactive>:1:0:
    Ambiguous type variable `b' in the constraints:
      `MyOrd b' arising from use of `greaterMyOrd' at <interactive>:1:0-11
      `Num b' arising from the literal `3' at <interactive>:1:16
    Probable fix: add a type signature that fixes these type variable(s)
*MyOrd> greaterMyOrd (2 :: Integer,3 :: Integer) (1,2)
True

Cheers,
Daniel

-- 

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
	-- Blair P. Houghton



More information about the Haskell-Cafe mailing list