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

Reply via email to