Dear Haskellers,

I am using multi parameter typeclasses to represent images consisting of
pixels (e.g. bitmap images).

{-# OPTIONS_GHC -XMultiParamTypeClasses #-}
module Bitmap where

      -- | a pixel could be a Word8 (e.g. a graysclale image)
      -- | or a 3-tuple for RGB images
      class Pixel p where
            .... <pixel related functions go here>


      -- | an image could be a UArray or a list of lists of pixels
      class Pixel p => Image a p where
            width  :: a -> Int
            height :: a -> Int
            dims   :: a -> (Int, Int)
            dims img = (height img, width img)


If I try to load this module into ghci I get:

      Could not deduce (Image a p) from the context (Image a p2)
      arising from a use of 'height' at .....

      and

      Could not deduce (Image a p1) from the context (Image a p2)
      arising from a use of 'width' at ......

where both errors originate from the 'dims' function.
Eventually I figured out that I could remedy the situattion by using
functional dependencies like this:

      class Pixel p => Image a p | a -> p where
            ...

However, I do not really understand the cause of the original problem. Why
do I need the functional dependency to make this work ?
Any help is appreciated.

Thanks

Harald.



" Ce courriel et les documents qui y sont attaches peuvent contenir des 
informations confidentielles. Si vous n'etes  pas le destinataire escompte, 
merci d'en informer l'expediteur immediatement et de detruire ce courriel  
ainsi que tous les documents attaches de votre systeme informatique. Toute 
divulgation, distribution ou copie du present courriel et des documents 
attaches sans autorisation prealable de son emetteur est interdite." 

" This e-mail and any attached documents may contain confidential or 
proprietary information. If you are not the intended recipient, please advise 
the sender immediately and delete this e-mail and all attached documents from 
your computer system. Any unauthorised disclosure, distribution or copying 
hereof is prohibited."
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to