
On Sun, 7 Apr 2002, Eric wrote: |> Hi there, I am a beginner a haskell,and I have some |> difficulty in dealing with an assignment that is to |> translate a string representation of a list of |> appointments into a list of appointments. For example: [requirements snipped] |> How can I finish the requirement make use of library |> functions such as words, unwords, lines and break. Hey Leo, Well, I'm just learning haskell too, but I decided to give this a shot. I think I solved the main problem, but I did hit a few snags of my own so I can't be sure. Here goes: Basically, I defined "appointment" as a single type... But I couldn't figure out how to print that type. So I can't really test what I've done, other than I know it compiles. :) Can someone show me how to fill in "show" down here? )
module Main where
data Appt = Appt (Bool, Int, Int, String) instance Show Appt where show x = "???????????"
I then used liness and words to break the multi-line string into a list of lists of words:
strToApps :: String -> [Appt] strToApps x = map lineToApp (lines x) lineToApp x = wordsToApp (words x)
Since the starting "!" was optional, the structure of the list could go in two directions here:
wordsToApp :: [String] -> Appt wordsToApp ws | head ws == "!" = mkAppt True (tail ws) | otherwise = mkAppt False (ws)
Now it's just a matter of parsing the rest of the line. For simplicity's sake, I took the liberty of assuming you always used the same number of digits for the hours, so I didn't have to search for the "-":
mkAppt :: Bool -> [String] -> Appt mkAppt isImp (w:ws) = Appt (isImp, start, done, note) where (hs, hd) = splitAt 3 w -- assumes zero-padded (eg 01-03) start = atoi hs done = atoi hd note = foldr1 concat ws concat a b = a ++ " " ++ b
That "atoi" function came from working through the exercises in Rex Pages online book ( http://www.cs.ou.edu/cs1323h/textbook/haskell.shtml )
horner str = foldr1 op (reverse str) where op d s = d + (10 * s) atoi str = horner [digitToInt d | d <- str]
Then I defined a main function:
-- I wonder what a refec is. :) main = do print $ strToApps "! 10-11 lecture\n12-13 lunch at the refec :("
... And that's it! I think it would work if I could figure out how to print Appt objects (or whatever you call them in haskell). Meanwhile, I get this because of the way I defined show: Main> main [???????????,???????????] Cheers, - Michal http://www.sabren.net/ sabren@manifestation.com ------------------------------------------------------------ Give your ideas the perfect home: http://www.cornerhost.com/ cvs - weblogs - php - linux shell - perl/python/cgi - java ------------------------------------------------------------