[Haskell-cafe] Re: Adding new entry to list

Johnny Morrice spoon at killersmurf.com
Thu Jul 8 06:29:10 EDT 2010


Hi there Jack,

I have modified your program.  However, where you were attempting to use
direct recursion to compute totalSales, I have used functions from the
prelude.

I have also provided a recursive definition totalSalesRec.

Here is a lesson on recursion from the Haskell wikibook
http://en.wikibooks.org/wiki/Haskell/Recursion

Also, what you have is an associative array which pairs (Artist, Title)
with Sold.  A linked list [(Artist, Title, Sold)] is an inappropriate
data type for this purpose.  Consider using Map from Data.Map in the
form Map (Artist, Title) Sold.

I have included comments which I hope you will find useful in
understanding the code.

Also note my use of comments like:

-- | This is a function that does blah

These are annotations for the Haskell documention generator, Haddock
http://www.haskell.org/haddock/

What I'd do to run haddock on this file (I use linux and I have saved as
artist.hs) is

mkdir doc && haddock artist.hs -o doc -h

Now you can look at documentation for your program in a web browser
while fickering with it in GHCi.

Be aware that my copy pasting this file onto here may well have mangled
its syntax!

Have fun,
   Johnny

module Main
   (main
   ,testDatabase
   ,totalSales
   ,totalSalesRec
   ,printNames
   ,mainLoop)
   where

-- | Title of a record
type Title = String
-- | An artist, who makes records
type Artist = String
-- | Number of copies of a record sold
type Sold = Int

type Sales = [(Title, Artist, Sold)]

-- | A small sales database
testDatabase :: Sales
testDatabase = [("Kids", "MGMT", 3), ("This Charming Man", "The Smiths",
5), ("Gimme Shelter", "The Rolling Stones", 7)]

-- Notice there are no explicit function arguments here.  Look up
'partial application'.
-- | Total sales of all records in the database.
totalSales :: Sales -> Sold 
totalSales =
   -- The sum of all the sales
   sum . map sale
   where
   sale (_,_,s) = s

-- | Recursive version of totalSales
totalSalesRec :: Sales -> Sold
totalSalesRec ((_,_,s):ss) = s + totalSalesRec ss
totalSalesRec _            = 0

-- | Print out the contents of a sales database
printNames :: Sales -> IO ()
printNames testDatabase = mapM_ print testDatabase

-- Main application loop
mainLoop :: Sales -> IO ()
mainLoop testDatabase = do
                putStrLn "1 - Show all tracks in database"
                putStrLn "2 - Show the total sales"
                putStrLn "3 - Add a new entry"
                putStrLn "4 - Exit"
                putStrLn ""
                putStrLn "Please select an option:"
                input <- getLine
                case read input of
                        1 -> do
                                banner "Show All Tracks"
                                printNames testDatabase
                                putStrLn ""
                                mainLoop testDatabase
                        2 -> do 
                                banner "Total Sales"
                                print $ totalSales testDatabase
                                putStrLn ""
                                mainLoop testDatabase
                        3 -> do
                                banner "New entry"
                                putStrLn "Enter artist name"
                                a <- getLine
                                putStrLn ""
                                putStrLn "Enter title"
                                t <- getLine
                                putStrLn ""
                                putStrLn "Enter number of sales"
                                -- Look up functors to understand fmap
                                s <- fmap read getLine
                                putStrLn ""
                                -- 'cons' the new element to the start
of the linked list testDatabase
                                -- Look up data constructors.
                                mainLoop $ (a,t,s) : testDatabase
                        -- No 'do' is required for only one statement.
Look up monads and how 'do' is syntactic sugar. 
                        4 -> return ()
   where
   -- Print banner
   banner s = do
                 putStrLn "------------------"
                 putStrLn s
                 putStrLn "------------------"

-- | Run
main :: IO ()
main = mainLoop testDatabase



More information about the Haskell-Cafe mailing list