Structuring IO actions with conditional logic

Hi there,

I’m learning Haskell by implementing a small toy project. I’m stuck implementing an IO action to insert medical reports into a Postgres database.

These reports have many lesions associated with them. I need to insert the report and all its lesions within a transaction.

The reason I’m stuck is because I don’t know how to structure conditional logic for the different conditions that might occur within this IO action.

Lesions should be inserted only if I successfully inserted the report and got the report’s ID. I also need to propagate any potential error from inserting a lesion to the calling function. The action returns IO (Either String Int64), see code sketch below.

This is the sketch of code I’m working on at the moment. It clearly doesn’t even compile but I just want to convey where I’m trying to go. Let me know if it isn’t clear and I’ll provide any clarifications.

data Report = Report
  { procedureDate :: LocalTime,
    lesions :: [Lesion]
  } deriving (Show, Eq)

insertLesions :: Connection -> Int64 -> [Lesion] -> IO (Either String Int64)
insertLesions db reportID lesions = undefined

insertReport :: Connection -> Int64 -> Report -> IO (Either String Int64)
insertReport db pid report = do
  -- Transaction begin omitted
  (rs :: [Only Int64]) <-
    query
      db
      "insert into catheterization_reports (user_id, procedure_date)\
      \values (?, ?) returning id"
      (pid, procedureDate report)
  
  -- I need to make sure `rs` has one element, the ID of the created report, before moving to insert its lesions
  -- It would be even better if we can guarantee `rs` contains strictly one element before continuing.
  case rs of
    [] -> return ()
    (Only rid : _) -> do
      -- IO action inside a different monad (is this code screaming for monad transformers?)
      insertLesions db rid (lesions report)
  -- Transaction commit/rollback omitted
  -- When the IO action ends I'd like to provide the caller with either the ID of the created report or a string with an error
-- This pattern of error handling might not be the best. I'm trying to understand if exceptions are better in this scenario.

Thanks

is this code screaming for monad transformers?

It’s definitely something you might like to try. How about trying to change the type signature to

insertReport :: Connection -> Int64 -> Report -> ExceptT IO Int64

Alternatively you might like to try the effectful effect system, which I recommend above monad transformers, these days.

1 Like

Using ExceptT could be a nice first step, for example you could implement the initial insert that way:

insertRS :: _ -> ExceptT String IO Int64
insertRS _ = do
  (rs :: [Only Int64]) <- liftIO (query _)
  case rs of
    [Only rid] -> pure rid
    [] -> throwE "Insert failed"
    _ -> throwE "Multiple id returned"

Then you wouldn’t have to deal with rs not having one element in the insertReport:

insertReport :: _ -> ExceptT String IO ()
insertReport _ = do
  rid <- insertRS _
  traverse_ (insertLesions rid) (lesions report)
 where
    insertLession :: _ -> ExceptT String IO ()

Finally you handle the exceptions when doing the transaction:

insertReportDo :: _ -> IO ()
insertReportDo _ = do
  createTransaction
  result <- runExceptT (insertReport _)
  case result of
    Left e -> rollbackTransaction
    Right () -> commitTransaction

You might be interested in the talk Monad transformers are good, actually by @Gabriella439 for the ZuriHac 2023. It’s a nice intro to transformers. Here are the slide: link.