[Haskell-cafe] Getting an attribute of an object

Dmitri Pissarenko mailing-lists at dapissarenko.com
Fri Feb 11 08:48:01 EST 2005


Hello!

I have now another problem.

I have a function

readClassifiedImages :: [ClassifiedImage] -> [IO (ClassifiedImage, Image)]
readClassifiedImages classifiedImages = map readClassifiedImagesSelector
classifiedImages

data ClassifiedImage = ClassifiedImage {imageFileName :: String, subjectID ::
String}
         deriving Show

I have another function, which should transform [IO (ClassifiedImage, Image)]
to
[IO Image]. For a certain operation, I need just the images without the
information contained in the data type ClassifiedImage.

So I defined following function:

getImages :: [IO (ClassifiedImage, Image)] -> [IO Image]
getImages classifiedImages = map snd classifiedImages

First argument of it has the same type as the "return value" of function
readClassifiedImages.

Then I created following program.

<program>
module ExperimentalYaleDb
	where

import Lik

main = do
	let trainingSet = [(ClassifiedImage "../data-test/yalefaces-
pgm/subject01.centerlight.pgm" "subject01"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject02.centerlight.pgm" "subject02"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject03.centerlight.pgm" "subject03"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject04.centerlight.pgm" "subject04"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject05.centerlight.pgm" "subject05"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject06.centerlight.pgm" "subject06"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject07.centerlight.pgm" "subject07"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject08.centerlight.pgm" "subject08"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject09.centerlight.pgm" "subject09"),
		(ClassifiedImage "../data-test/yalefaces-
pgm/subject10.centerlight.pgm" "subject10")]

         -- read images from files
         classifiedImagesWithData <- (readClassifiedImages trainingSet)

         -- fetch images only from classifiedImagesWithData
         allImages <- (getImages classifiedImagesWithData)

         return 0
</program>

When I try to run this program in GHCi, I'm getting this error message

<error>
C:\dapWork\lik\sw\src>startghci
Lik.hs:14:
     Couldn't match
         `(a, IO Image)' against `IO (ClassifiedImage, Image)'
         Expected type: [(a, IO Image)]
         Inferred type: [IO (ClassifiedImage, Image)]
     In the second argument of `map', namely `classifiedImages'
     In the definition of `getImages':
         getImages classifiedImages = map snd classifiedImages
Failed, modules loaded: HUnit, HUnitText, HUnitBase, HUnitLang.
*HUnit>
</error>

where "Lik.hs:14" denotes the line

getImages classifiedImages = map snd classifiedImages

How can I solve this problem?

TIA

Dmitri Pissarenko
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com



More information about the Haskell-Cafe mailing list