Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Neil Brown

Michael P Mossey wrote:
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 a version using ErrorT from mtl.  I added some missing IO bits on 
your types; the type error that remains is for you to fix :-)  With 
ErrorT you can use throwError when you want to break out of the block 
and give back an error, which seems to fit what you were doing.  The 
downside is you have to add all these liftIO bits wherever you do a 
plain IO computation.


insertNote :: NoteRecord - Connection - IO ()
insertNote nr conn = either putStrLn return = runErrorT
  (do -- Check if it exists in the database already.
  status - liftIO $ checkPreExistingText nr conn
  when status $ throwError Skipping... text exists already.
  -- Find best fit for all topics and source.
  -- See type signatures below.
  bestFitTopics - liftIO $ fitTopics nr conn
  bestFitSource - liftIO $ fitSource nr conn
  case any isNothing bestFitTopics of
True - throwError Error... some topic couldn't be matched.
False -
  case bestFitSource of
Nothing - throwError Error.. source couldn't be matched.
_ - do b - liftIO $ isUserOkay nr bestFitTopics bestFitSource
when (not b) $ throwError Abort due to user request.
-- Create a new NoteRecord with matched
-- and validated topics/source.
let nrValidated =
  nr { recordTopics = bestFitTopics
 , recordSource = bestFitSource }
liftIO $ insertRow nrValidated conn
  )

checkPreExistingText :: NoteRecord - Connection - IO Bool
fitTopics :: NoteRecord - Connection - IO [Maybe String]
fitSource :: NoteRecord - Connection - IO (Maybe String)
isUserOkay :: NoteRecord - [Maybe String] - Maybe String - IO Bool
insertRow :: NoteRecord - Connection - IO ()


Thanks,

Neil.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Claus Reinke
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.


Perhaps this is useful:
http://www.haskell.org/haskellwiki/Equational_reasoning_examples#Coding_style:_indentation_creep_with_nested_Maybe

Claus 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Ryan Ingram
On Mon, May 18, 2009 at 3:08 AM, Neil Brown nc...@kent.ac.uk wrote:
 With ErrorT you can use throwError when you want to break out of the
 block and give back an error, which seems to fit what you were doing.

Of course, now that you are using throwError, you can remove a lot of
the extra indentation:

 insertNote :: NoteRecord - Connection - IO ()
 insertNote nr conn = either putStrLn return = runErrorT
  (do -- Check if it exists in the database already.
      status - liftIO $ checkPreExistingText nr conn
      when status $ throwError Skipping... text exists already.
      -- Find best fit for all topics and source.
      -- See type signatures below.
      bestFitTopics - liftIO $ fitTopics nr conn
      bestFitSource - liftIO $ fitSource nr conn
      when (any isNothing bestFitTopics) $ throwError Error... some topic 
 couldn't be matched.
      when (isNothing bestFitSource) $ throwError Error.. source couldn't be 
 matched.
      b - liftIO $ isUserOkay nr bestFitTopics bestFitSource
      when (not b) $ throwError Abort due to user request.
      -- Create a new NoteRecord with matched
      -- and validated topics/source.
      let nrValidated = nr { recordTopics = bestFitTopics, recordSource = 
 bestFitSource }
      liftIO $ insertRow nrValidated conn
  )

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Claus Reinke
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 (sdlowly) 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.


Perhaps this is useful:
http://www.haskell.org/haskellwiki/Equational_reasoning_examples#Coding_style:_indentation_creep_with_nested_Maybe
I can't quite tell--is that example in the IO monad? Part of my difficulty is that I'm inside IO. 
I know how to do this with Maybe, except that I have to combine Maybe and IO (use MaybeT?)


It was in the GHC.Conc.STM monad, so yes, it used a MaybeT
and Control.Monad.Trans.MonadTrans's lift (btw, the MonadTrans
docs only point to [1], but [2] might also be of interest, if rather
more compact/terse).

Claus

[1] http://web.cecs.pdx.edu/~mpj/pubs/springschool.html
[2] http://web.cecs.pdx.edu/~mpj/pubs/modinterp.html




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] tips on using monads

2009-05-17 Thread Michael P Mossey
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 ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe