Question

I'm a Haskell newbie, so chances are I've missed something obvious...

I am trying to write a generic colour quantisation algorithm using ad hoc polymorphism. However, I'm having some trouble getting my data out with pattern matching (I've not actually got to the quantisation bit, yet).

I can't describe this succinctly, so here's a simplified version of my code which exhibits the problem:

{-# LANGUAGE FlexibleInstances #-}

import Data.Word

type ColourGrey = Word8

data ColourRGB = ColourRGB Word8 Word8 Word8
  deriving (Show)

data ColourStream = Greys   [ColourGrey]
                  | Colours [ColourRGB]
                    deriving (Show)

class Colour a where
  extractStreamData :: ColourStream -> [a]

instance Colour ColourGrey where
  extractStreamData (Greys x) = x

instance Colour ColourRGB where
  extractStreamData (Colours x) = x

someColours = Colours [ColourRGB 255 0 0, ColourRGB 0 255 0, ColourRGB 0 0 255]
someGreys   = Greys   [0, 127, 255]

main :: IO ()
main = do
  print $ extractStreamData someColours
  print $ extractStreamData someGreys

The calls to extractStreamData fail with the following:

No instance for (Colour a1)
  arising from a use of `extractStreamData'
The type variable `a1' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
  instance Colour ColourRGB -- Defined at test.hs:20:10
  instance Colour ColourGrey -- Defined at test.hs:17:10
In the second argument of `($)', namely
  `extractStreamData someGreys'
In a stmt of a 'do' block: print $ extractStreamData someGreys
In the expression:
  do { print $ extractStreamData (someColours :: ColourStream);
       print $ extractStreamData someGreys }

This implies, to me, that Haskell can't infer which instance to use (the one for colours or the one for greyscale). Would that be right? If so, how would I go about fixing this?


n.b. The definitions of ColourGrey and ColourRGB are outside my scope of influence (they're part of an external library). So any suggestions need to be modulo these two types. I'd prefer not to mess about with ColourStream, either, as it's used in lots of other places.

The reason I need to access the "raw" lists is so I can work with things like map, etc. If there's a neat trick I've yet to learn which will make ColourStream iterable, then I suppose that would work... </thinking aloud>

Was it helpful?

Solution

The problem is that Haskell sees extractStreamData and realizes it's going to return some Colour a => a, but then you pipe that into show so it also realizes that a is an instance of Show, but after that there's no mention of a.

This means that Haskell can't figure out which type a should be. The solution is just to help out the typechecker and add some signatures

print $ (extractStreamData someGreys :: [ColourGrey])

like that.

However your typeclass instances are a bit... worrisome. What would happen if you passed you passed a ColourGray to the ColourRGB instance? Blowing up at runtime with little to know information is a bad response.

Remember that typeclasses is just a way of doing [really souped up] type based overloading. Really it looks like you want like what Daniel Wagner has or something like

translateRGB :: ColourRGB -> ColourGrey
translateGrey  :: ColourGrey -> ColourRGB

And then make your instances more like

instance Colour ColourGrey where
  extractStreamData (Greys x) = x
  extractStreamData (Colours x) = map translateRGB x

so that you just choose whether you want to treat your stream as ColourGreys or ColourRGBs and work with that. Now when you use extractStreamData you're not trying to figure out what's in the stream first.

OTHER TIPS

I suspect, though I am not sure, that what you really want is something like this:

onColourStream ::
    ([ColourGrey] -> [ColourGrey]) ->
    ([ColourRGB ] -> [ColourRGB ]) ->
    (ColourStream -> ColourStream)
onColourStream onGreys onRGBs (Greys gs) = Greys (onGreys gs)
onColourStream onGreys onRGBs (Colours rgbs) = Colours (onRGBs rgbs)

If ColourGrey and ColourRGB share some operations -- say, a lightening operation -- and you want to use those operations on whichever thing you have, then you might make a type class and do something like this:

class Colour a where lighten :: Double -> a -> a
instance Colour ColourRGB  where lighten = ...
instance Colour ColourGrey where lighten = ...

onColourStreamPoly ::
    (forall a. Colour a => [a] -> [a]) ->
    (ColourStream -> ColourStream)
onColourStreamPoly f = onColourStream f f

Then you might be able to write something like onColourStreamPoly (map (lighten 0.5)) or so to lighten all the colours by a half.

Edit: To respond to "What I ultimately want to do is match a stream of image colour data (either RGB or grey) to a palette (another stream, which always matches the colourspace of the image)": In that case, I think the lightest thing to do is simply use pattern matching. Let's assume you have some functions like:

matchPalette :: Eq a => [a] -> [a] -> [Int]
myAlgorithm  :: [Int] -> [Int]
unmatchPalette :: [Int] -> [a] -> [a]

Then you can do something like this:

pipeline :: Eq a => [a] -> [a] -> [a]
pipeline xs ys = unmatchPalette (myAlgorithm (matchPalette xs ys)) xs

wholeShebang :: ColourStream -> ColourStream -> ColourStream
wholeShebang (Greys gs) (Greys gs') = Greys (pipeline gs gs')
wholeShebang (Colours rgbs) (Colours rgbs') = Colours (pipeline rgbs rgbs')
wholeShebang _ _ = error "Yikes! The colour stream and palette didn't match up."

Here goes a simpler version of your program, sans compilations problems:

import Data.Word

type ColourGrey = Word8

data ColourRGB = ColourRGB Word8 Word8 Word8
  deriving (Show)

data ColourStream a = ColourStream [a]

extractStreamData (ColourStream stream) = stream

someColours = ColourStream [ColourRGB 255 0 0, ColourRGB 0 255 0, ColourRGB 0 0 255]
someGreys   = ColourStream ([0, 127, 255] :: [ColourGrey])

main :: IO ()
main = do
  print $ extractStreamData someColours
  print $ extractStreamData someGreys

Of course, I don't know how you will be using these definitions outside this simple example, so I'm not sure if it's good enough for what you're trying to do.

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top