date sorting II

Michael Ruth meruth@hotmail.com
Sun, 10 Mar 2002 00:40:52 -0600


I wrote to the group earlier this week regarding a haskell script to sort 
dates from input. Someone said:

Why don't you write this up and send it to the list so that we
can look at code rather than English text?

So Here's the code... It is my first Haskell program so please forgive me if 
I broke any rules. I have been trying to debug it but keep running into 
walls, any and all help will be appreciated.


import IO

-- not really sure how to use globals variables.

--myfile :: IO Handle

myList :: [String]
myList = []

--myDates :: [[String]]

-- start is the main flow of the program.  Each output will be used by
-- the input of the next line or so I tried anyway.  This was done so
-- at the end I could compose the functions f1 . f2 . f3 ...

start:: IO()
start = do {
	putStr   "Enter a filename: ";
	theFile <- getLine;
	myfile <- openFile theFile ReadMode;
	myList <- getInput myfile;
	myDates <- stripSpaces myList;
	myDates <- qSort myDates;
	myList <- formatOutput myDates;
	writeFile "output.txt" (getOutput (myList));
}

-- get input was designed to suck in the input strings line by line
-- into a list until there are no more lines
-- Not at all sure how to do this I wallowed through
-- example after example.

getInput :: Handle -> [String]
getInput myfile
  = while (do res <- hIsEOF myfile
              return (not res))
          (do line <- hGetLine myfile
              return (line:myList))

-- Strip spaces turns the input strings into a list of strings
-- so its [day, month, year] each of these being Int's
-- this is done for easier sorting later on (or to make it possible)

stripSpaces :: [String] -> [[String]]
stripSpaces x = map words x

-- The standard basic quicksort to be done using multidimensional
-- lists.  Never really got to this point yet, although I may
-- rearrange this function to compare strings of the form...
-- yyyy mm dd which should sort correctly then rearrange them
-- once done for printing.

qSort :: [[String]] -> [[String]]
qSort [[]]    = [[]]
qSort ([x]:[xs]) = qSort elts_lt_x ++ [[x]] ++ qSort elts_greq_x
		 where
		   elts_lt_x   = [[y] | [y] <- [xs], [y] < [x]]
		   elts_greq_x = [[y] | [y] <- [xs], [y] >= [x]]


-- this function puts each of the lists back into string form
-- to format for output

formatOutput:: [[String]] -> [String]
formatOutput [n] = map unwords [n]

-- This getoutput f(x) is designed to create the string to output to
-- the file

getOutput:: [String] -> String
getOutput [] = []
getOutput (x:xs) = show x ++ "\n"

--
-- this "while" function allowed me to write the above, it was in an
-- example.

while :: IO Bool -> IO () -> IO ()

while test action
  = do res <- test
       if res then do action
                      while test action
              else return ()

The end.

I am extremely lost and any and all help would be greatly appreciated.
Michael

_________________________________________________________________
Chat with friends online, try MSN Messenger: http://messenger.msn.com