I wrote up some code for you although, judging from the style of your code,
it won't be much help since it uses some language features (higher-order
functions and one abstract type) that your text probably hasn't covered yet.
Frankly, it is a pain to write this stuff in explicit recursive style,
although it probably makes for a good exercise. Sorry.

> My problems are :
> 1. type Person = String
>    type Book = String
>    type Database = [(Person,Book)]
>    exampleBase
>    = [("Alice", "Postmn Pat"),("Anna","All Alone"),("Alice","Spot")]
>
>    books      :: Database -> Person -> [Book]
>    borrowers  :: Database -> Book -> [Person]
>    borrowed   :: Database -> Book -> [Bool]
>    numBorrowed        :: Database -> Person -> Int
>
>   books :: Database -> Person -> [Book]
>   books [] borrowers = []
>   books ((pers,bk):rest) borrowers
>     |  pers == borrowers = bk : books rest borrower
>     |  otherwise       =      books rest borrower
>
>   {-output :
>     books exampleBase "Alice" = ["Postman Pat","Spot"]
>   -}
>
>   borrowers :: Database -> Book -> [Person]
>   borrowers [] books  = []
>   borrowers ((pers,bk):rest) books
>     | bk == books     = pers : borrowers rest books
>     | otherwise               =        borrowers rest books
>
>   {- output:
>    books exampleBase "Spot" = ["Alice"]
>   -}
>
>   How should I do to  make borrowed and numBorrowed, because it's use
>   String and integer, and i confuse.

  borrowed db bk = map ((== bk) . snd) db

  numBorrowed db pers = length (filter ((== pers) . fst) db)

The map function takes a function f and a list xs and returns the result of
applying f to each member of the list. (.) is function composition. snd
(x,y) = y. (== bk) is a function that returns True if the argument equals
bk, False otherwise. What borrowed does is look at the second component of
each pair in a list, and return a boolean indicating whether it equals bk.
Aw hell, I'll just write it out:

  --- this is untested
  borrowed [] = []
  borrowed ((_,b):rest) = b == bk

As for numBurrowed, filter f xs applies f to each member x of the list xs,
and discards x iff f x is false. You can figure out the rest.

> 2. type Name    = String
>    type Price   = Int
>    type BarCode = Int
>
>    type Database = [(BarCode,Name,Price)]
>
>    codeIndex :: Database
>    codeIndex = [(4719, "Fish Fingers",121),
>               (5643,"NAppies",1010),
>               (3814,"Orange Jelly",56)]
>
>    type TillType = [BarCode]
>    type BillType = [(Name,Price)]
>
>   How should I do to make function ?
>       - makeBill :: TillType -> BillType
>       - formatBill :: BillType -> String
>       - printBill :: TillType -> String
>   How should I defined BarCode to print (Name, Price)?

   till :: TillType
   till = [4719,5643,3814,4719]

An example till, used below.

   makeBill :: TillType -> BillType
   formatBill :: BillType -> String
   printBill :: TillType -> String

   lookupBy :: (a -> Maybe b) -> [a] -> Maybe b
   lookupBy f []     = Nothing
   lookupBy f (x:xs) = case f x of
                         Nothing -> lookupBy f xs
                         r       -> r

Um, think of this as a slightly fancy way of selecting a list member, and
postponing error recovery.

   makeBill = map mkBill
     where mkBill code =
             case lookupBy (matchingCode code) codeIndex of
               Just item -> item
               Nothing   -> error "unknown code"
           matchingCode code (c,n,p) | c == code = Just (n,p)
                                     | otherwise = Nothing

I defined makeBill, which operates over an entire list, in terms of the
local function mkBill, which  operates on just one element. mkBill looks for
a matching code, returns the relevant bill type, or  causes a run-time error
if there is no such code entry in codeIndex.

   formatBill = concat . map fBill
     where fBill (name, price) = name ++ " " ++ show price ++ ", "

(++) is list (here [Char] = String) concatenation. concat is like (++), but
it concatenates a list of strings. show is a kind of generic function that
converts values of most types into a string representation. Your text
probably described a more specialized function for converting integers into
strings in an earlier section.

   printBill t = formatBill bill ++ "Total " ++ total bill
     where total = show . sum . map snd
           bill = makeBill t

This calculates the total price, and tacks it onto a bill generated from the
till t using makeBill. total is a function that sums up the second
components of a list of pairs, and converts the result into a string.

{-
Main> printBill till
"Fish Fingers 121, NAppies 1010, Orange Jelly 56, Fish Fingers 121, Total
1308"
-}

This was the result on my example till, using Hugs.

Maybe I misunderstood you, but I got the feeling that you were searching for
a way to actually print the result as a side-effect, like in C. Notice that
there are no side-effects in the above code. The signature of printBill
calls for a String result type, which simply means to return a string, not
to do something like printf. If you really want to print a string out, you
can write this at the prompt:

  putStr (printBill till)

but it is not so easy to explain how and why that works until you cover more
advanced material.

--FC



Reply via email to