[Haskell-cafe] tips on using monads

Michael P Mossey mpm at alumni.caltech.edu
Mon May 18 00:44:42 EDT 2009


I've got one of those algorithms which "threatens to march off the right edge" 
(in the words of Goerzen et al). I need something like a State or Maybe monad, 
but this is inside the IO monad. So I presume I need StateT or MaybeT. However, 
I'm still (slowly) learning about monads from first principles. I thought I 
might present my code and get some pointers... maybe someone could actually show 
me how to rewrite it, which would be a neat way to see MaybeT and StateT in 
action. I'm hoping to get anything from a one-line response to a rewrite of my 
code. Anything will help.

Here's the program:

{-

  This is a program which starts with a document containing "notes"
  about software requirements (in a particular format) and puts them
  into a database. Notes include details such as the "source" of the
  requirement (who gave it), the topic(s) to which it pertains, the
  date, etc.

  I have written a parser to take a text document typed up by me during a
  meeting and parse it into a NoteRecord structure. Here is the
  structure:

-}

data NoteRecord = NoteRecord {
       recordSource :: String,       -- Name of person who gave req.
       recordDate :: [Int],          -- Date in [<year>,<month>,<date>]
       recordSourceType :: String,   -- "meeting", "phone", "email", etc.
       recordBugNum :: Maybe Int,    -- Bugzilla # (if relevant)
       recordTopics :: [String],     -- list of official topics pertaining
       recordText :: String }        -- the text of the note itself
                 deriving (Show)

{-

  One other wrinkle. The source (person name) and topic must be one
  of a set of pre-determined strings. A person has an official full name
  which is stored in the database. Topics also have official descriptive
  strings. If I wasn't clever, then the note, as I type it up,
  must have the exact name and topic. But I hate trying to remember things
  like that. So I have implemented a "fuzzy string match" system so
  that I can type part of someone's name (or even misspell it) or part of
  a topic string, and the system will find the best match to an official
  string.

  In pseudocode, the function to insert a note in the database must do this:

  This function starts with a NoteRecord.
   - If text already exists in the database, give an error and skip to end.
   - Fuzzy-match strings to topics and source.
   - If no potential match can be found to some of topics or source,
     give error and skip to end.
   - Ask user to confirm if the matched topics and source look okay.
        - if user says no, skip to end.
   - Actually insert the record.
-}
insertNote :: NoteRecord -> Connection -> IO ()
insertNote nr conn =
     do -- Check if it exists in the database already.
        status <- checkPreExistingText nr conn
        if status
          then putStrLn "Skipping... text exists already."
          else
            do -- Find best fit for all topics and source.
               -- See type signatures below.
               bestFitTopics <- fitTopics nr conn
               bestFitSource <- fitSource nr conn
               case any isNothing bestFitTopics of
                 True ->
                     putStrLn "Error... some topic couldn't be matched."
                 False ->
                     case bestFitSource of
                       Nothing ->
                           putStrLn "Error.. source couldn't be matched."
                       _ ->
                           do b <- isUserOkay nr bestFitTopics bestFitSource
                              if b
                                 then do
                                   -- Create a new NoteRecord with matched
                                   -- and validated topics/source.
                                   nrValidated =
                                       nr { recordTopics = bestFitTopics
                                          , recordSource = bestFitSource }
                                   insertRow nrValidated conn
                                 else putStrLn "Abort due to user request."


checkPreExistingText :: NoteRecord -> Connection -> Bool

-- There are multiple topics in the NoteRecord. For each one,
-- find the best fuzzy match, or indicate if there is no plausible
-- match at all.
fitTopics :: NoteRecord -> Connection -> [Maybe String]

-- There is one source. Try to find fuzzy match.
fitSource :: NoteRecord -> Connection -> Maybe String

-- Present user with all fuzzy matches and get a yes/no response if it's
-- okay to proceed.
isUserOkay :: NoteRecord -> [Maybe String] -> Maybe String -> Bool

-- Do actual insert into database.
insertRow :: NoteRecord -> Connection -> IO ()


More information about the Haskell-Cafe mailing list