Now I have....

module Main where

data SquareType numberType = Num numberType => SquareConstructor
numberType

data RectangleType = RectangleConstructor Int Int

class ShapeInterface shape where
        area :: shape->Int

data ShapeType = forall a. ShapeInterface a => ShapeType a

instance ShapeInterface (SquareType numberType) where
        area (SquareConstructor sideLength) = sideLength * sideLength
                 
main = do 
        putStrLn (show (area (SquareConstructor 4)))
        name <- getLine
        putStrLn ""


but get the errors....

In the expression: sideLength * sideLength In the definition of `area':
area (SquareConstructor sideLength) = sideLength * sideLength In the
definition for method `area'    

And

Couldn't match expected type `Int' against inferred type `numberType'
`numberType' is a rigid type variable bound by  


But to be fair....I almost understand the errors....which is not bad for
me.....surely 

"class ShapeInterface shape where
        area :: shape->Int"

now looks dubious....I want it to be something like

"class ShapeInterface shape where
        area :: Num numberType => shape->Int" ?

but my instance declaration still complains with the errors above and I
now get an error in the class declaration

`numberType1' is a rigid type variable bound by....

It's slightly doing my head in....and reminds me of trying to learn C++
once....not a pleasant experience....though I did eventually
succeed....to a degree.

-----Original Message-----
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: 21 December 2007 15:33
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling....

Nicholls, Mark wrote:
> *instance* ShapeInterface SquareType *where*
> 
>       area (SquareConstructor sideLength) = sideLength * sideLength


> *data* SquareType a = Num a => SquareConstructor a


Now you have changed your type from SquareType to SquareType a, you need

to change the instance to:

instance ShapeInterface (SquareType a) where...


Jules
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to