Using IO Safely With Heavily Stateful Problem

One of the things I’m trying to learn is that once you enter IO, it’s “impossible” to leave and that I shouldn’t enter IO if I don’t need to. I have code that needs to get the current time and do some stuff with that time and use that information to calculate the due dates for the patron’s loan.

LibraryM is similar to PatronM except it uses State instead of StateT.

type Date = Time.UTCTime

data Patron = Patron  { libCardNo  :: !Int
                      , pname      :: !String
                      , borrowed      :: ![Loan]
                      } deriving (Show, Eq)

data Loan  = Loan { book   :: !Book
                  , taken  :: !Date
                  , due    :: !Date
                  } deriving (Show, Eq)

newtype PatronM m a = PatronM {runPatronM :: StateT Patron m a}

loanBookToPatron :: Book -> Integer -> Patron -> IO Patron
loanBookToPatron bk days p = do
    now <- liftIO Time.getCurrentTime
    let duedate = Time.addUTCTime (fromInteger days * Time.nominalDay) now
        lo = Loan bk now duedate
        addedLoan = lo : borrowed p
    return $ p {borrowed = addedLoan}

loanBookToPatronM :: MonadIO m => Book -> Integer -> PatronM m Patron
  loanBookToPatronM b d = PatronM $ do
    p <- get 
    newp <- liftIO $ loanBookToPatron b d p
    put newp
    return newp

The plan is for the patron to be able to take out a book from the library, only if there is a book to give them in the first place, and then calculate the terms of the loan at that point and add it to the Patron's loan list.

My question is, am I stuck in IO? My thinking is that I can use the IO action to generate the loan but return a brand new patron, but evalStateT will always return the IO Patron, so I’m not sure if I should change strategy here.

decreaseBkInLibrary :: Int -> Book -> Maybe Book
decreaseBkInLibrary num bk
    | available bk <= 0 = Nothing
    | otherwise = increaseBkInLibrary (negate num) bk

decBkByOne :: Book -> Maybe Book
decBkByOne = decreaseBkInLibrary 1

borrowBook :: MonadIO f => Patron -> Integer -> Book -> LibraryM (f Patron)
  borrowBook p days b = LibraryM $ do
              lib <- gets $ findByAttribute b
              case lib of
                [] -> return $ return p
                (x:_) -> do modify $ Map.alter (decBkByOne =<<) (getTitle . title $ x)
                            return $ 
                              evalStateT (runPatronM $ loanBookToPatronM b days) p
2 Likes