Hello!

Thanks for your answer!

Perhaps try:

do ...
   ciwd <- sequence classifiedImagesWithData
   let allImages = (getImages ciwd)
   ...

as it seems like you're trying to gave getImages act on a value of
type [IO (ClassifiedImage, Image)]. Applying sequence to
classifiedImagesWithData will turn it into an IO [(ClassifiedImage,
Image)] by doing the natural thing, from which you can pull out the
list to apply getImages to.

I've tried that and wrote

<code-snippet>
do...
let classifiedImagesWithData = ((return trainingSet) >>= readClassifiedImages)
ciwd <- (sequence classifiedImagesWithData)
let allImages = (getImages ciwd)
</code-snippet>

Now, I get the error

<error>
Compiling ExperimentalYaleDb ( ExperimentalYaleFaceDb.hs, interpreted )

ExperimentalYaleFaceDb.hs:41:
    Couldn't match `[]' against `IO'
        Expected type: [[a]]
        Inferred type: [IO (ClassifiedImage, Image)]
    In the first argument of `sequence', namely
        `classifiedImagesWithData'
    In a 'do' expression: ciwd <- (sequence classifiedImagesWithData)
Failed, modules loaded: TestLik, Lik, HUnit, HUnitText, HUnitBase, HUnitLang.
</error>

at line

ciwd <- (sequence classifiedImagesWithData)

Are there any other options?

Thanks in advance

Dmitri Pissarenko

PS: Maybe the error is rooted in code parts other than those given here. In
the attachment there is the code of the main program
(ExperimentalYaleFaceDb.hs) and the function definitions (Lik.hs).
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com

module ExperimentalYaleDb
	where

import Lik

createTrainingSet = [(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")]
        

main = do
	-- create a list of image to subject mapping
	-- the training set is all centerlight images of subjects 1 to 10
	-- 
	-- Following images are not contained in the training set
	-- 
	-- a) images of subjects 11 to 15 
	-- b) images of subjects 1 to 10, which are not centerlight
	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")]
        trainingSet :: [ClassifiedImage]
	
        
        -- read images from files
        let classifiedImagesWithData = ((return trainingSet) >>= readClassifiedImages)
        ciwd <- (sequence classifiedImagesWithData)

        -- calculate average image
        --let allImages = (getImages classifiedImagesWithData)

        let allImages = (getImages ciwd)
	-- calculate eigenfaces of the training set
	
        
	-- calculate weights of the training set
	
        
	-- now create a list of unknown images
	-- these are 
	-- a) images of subjects 11 to 15 
	-- b) images of subjects 1 to 10, which are not centerlight
        return 0
module Lik
        where

import IO
import Array

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

--type ClassifiedImageWithData = IO (ClassifiedImage, IO Image)
type ClassifiedImageWithData = (ClassifiedImage, Image)
type Image = [Double]


--getImagesSelector :: Monad IO => IO (ClassifiedImage, Image) -> Image
getImagesSelector :: (ClassifiedImage, Image) -> Image
getImagesSelector classifiedImageWithData = snd classifiedImageWithData


getImages :: [(ClassifiedImage, Image)] -> [Image]
-- getImages classifiedImgs = (map getImagesSelector classifiedImgs)
getImages classifiedImgs = snd (unzip classifiedImgs)

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

--readClassifiedImagesSelector :: ClassifiedImage -> IO (ClassifiedImage, Image)
readClassifiedImagesSelector classifiedImg = do
        image <- (readImageAsDouble classifiedImg)
        return (classifiedImg, image)


readImageAsDouble :: ClassifiedImage -> IO Image
readImageAsDouble classifiedImg = do
        imageAsString <- readImage (imageFileName classifiedImg)
        return (normalizeImg (convertToList imageAsString))



readImage :: String -> IO String
readImage filename = do 
	fileContent <- readFile filename
	return fileContent


writeImage filename stuffToWrite = do
	writeFile filename stuffToWrite

commentLine :: String -> Bool
commentLine text | ((head text) == '#') = True
                 | otherwise = False

noCommentLine :: String -> Bool
noCommentLine text = not (commentLine text)

removeComments :: String -> String
removeComments text = foldr (appendWithSeparator) "" linesWithoutComments
	where linesWithoutComments = filter noCommentLine (lines text)

appendWithSeparator :: String -> String -> String
appendWithSeparator part1 part2 = whole
	where whole = part1 ++ " " ++ part2
	
convertToArr :: forall a. (Read a) => String -> Array Int a
convertToArr fileContent = listArray (1, imgDatLength) imgDat
	where  	imgDat = convertToList fileContent
		imgDatLength = length imgDat
		
convertToList fileContent = drop 3 fileContentNumbers
	where 	fileContentNoComments = removeComments fileContent
		fileContentTokens = words fileContentNoComments
	      -- fileContentTokens contains token "P2", the magic number, which
	      -- we don't need
	      -- we "remove" it by taking the tail of fileContentTokens
	      	fileContentNumbers = map read (tail fileContentTokens)
		fileContentNumArr = listArray (1, length fileContentNumbers) fileContentNumbers

convertToFileContent :: Int -> Int -> Int -> [Int] -> String
convertToFileContent width height maxGray pixels = foldr (appendWithSeparator) [] (["P2", (show width), (show height), (show maxGray)] ++ pixelsAsStrings)
	where pixelsAsStrings = map show pixels

normalizeImg :: [Int] -> Image
normalizeImg img = map normalizePixel imgAsDouble
	where imgAsDouble = map fromIntegral img


normalizePixel :: Double -> Double
normalizePixel pixel = pixel/255

averageImage :: [Image] -> Image
averageImage images = map (/ numberOfImages) sum
	where 
		sum = sumOfImages images
		numberOfImages = fromIntegral(length images)

sumOfImages :: [Image] -> Image
sumOfImages images = foldr (add2Img) emptyImg images
	where emptyImg = replicate (length (head images)) 0.0

add2Img :: Image -> Image -> Image
add2Img summand1 summand2 = sum
	where sum = zipWith (+) summand1 summand2

denormalizeImg :: Image -> Image
denormalizeImg normalizedImage = map (*255) normalizedImage

doubleToInt :: Image -> [Int]
doubleToInt image = map (ceiling) image
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to