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

You can use an effect library for managing what a monadic function can do. I recommend effectful (disclaimer: I’m the author). See the main module for documentation and rationale, hopefully it explains the concept of managing effects sufficiently.

4 Likes

The only IO you are using is getCurrentTime. You can simply add the current time as an argument to the loanBookToPatron function:

loanBookToPatron :: Book -> Integer -> Date -> Patron -> Patron
loanBookToPatron bk days now p =
    let duedate = Time.addUTCTime (fromInteger days * Time.nominalDay) now
        lo = Loan bk now duedate
        addedLoan = lo : borrowed p
    in p {borrowed = addedLoan}
6 Likes

My advise is: almost never you want to use system’s date. This applies to any programming language on my experience having to debug time dependant applications in which time was taken from system… It is a bad Idea to do so. In Haskell you’d pass the date as a parameter hence

-- instead of 
loanBookToPatron :: Book -> Integer -> Patron -> IO Patron
loanBookToPatron bk days p = do
  now <- Time.getCurrentTime
  ...

-- You do                                ----------------| No IO Patron
loanBookToPatron :: Time -> Book -> Integer -> Patron -> Patron
loanBookToPatron now bk days p = ...

-- Then in main
main :: IO ()
main = do 
  now <- Time.getCurrentTime
  ...
  let patron =  loanBookToPatron now x y z
  ...

Same principle applies to OOP via some factory pattern

# instead of 
class Patron:

  def __init__(self):
    self.taken = datetime.date.today()

# Much better design 
class Patron:
  # TimeProviderFactory is a factory which can be configure to return 
  # sys.today() in production and some_debuging_date in develop.
  def __init__(self, time_provider: TimeProviderFactory):
    self.taken = time_provider.get_time()

I know, passing the date as argument can be a little bit verbose, but It pays off in the long term. By the way, you could pass the date in python as well as you do in haskell, but for some reason OOP tends to scale better with that kind of patterns.

3 Likes

Thanks, I’ll have a deeper read through this afternoon! I’ve heard of effectful before but I couldn’t understand any of the concepts before I started learning the fundamentals of mtl.

Please don’t use effect for that. Just pass the current time as a parameter (as other people suggested) or if you must use implicit parameter.

8 Likes

That is exactly why I am against “effects” : it tends to be the solution to everything even when there is no problem initially.

2 Likes

Well, I think effect systems could be useful if you end up having to add many extra arguments to many functions. But it really is a matter of finding the right level of abstraction.

2 Likes

This is a common stumbling block for people learning how to write IO-using programs in Haskell. I second the suggestion of just passing a time argument to a pure function, as I find that it makes the program much easier to test (in GHCi or in a test suite).

Then, to use that function with the time returned by an action like getCurrentTime, you can use the tools provided by the Functor/Applicative/Monad type classes.

If you are still learning the fundamentals, I would leave learning an advanced library like effectful until later.

5 Likes

Oh yeah, for context I added it as a parameter and rewrote my types, classes and instances and it’s going very well! Very grateful for that :slight_smile:

Now the part of figuring out how to combine changing libraries with potentially changing patrons haha.

2 Likes

That’s a bold assertion to make - what exactly is it that would hold a language like Haskell back on this front?

1 Like

That is just my impression. In OOP, plain argument passing is (just) fine but in the long term things like Factory, Strategy, Builder, etc… become neccessary to have an easy-to-maintain app. Whereas in Haskell is kind of the opposite, plain argument passing scales very well, and jumping into other patterns like monads/mtl, effect systems, typeclasses, etc… makes the program more difficult.

Was that the question? Maybe I didn’t understand it well

Anyway Nothing of this is part of the original question :sweat_smile:

3 Likes

Effect systems seem rather irreplaceable for properly testable production-grade code that doesn’t need to be fast. The other two, yes: mtl seems mostly useless (either use an effect system or just work in IO directly) and typeclasses tend to be overused in places that don’t really need them.

I assume trying to make everything an object means you need constant workarounds for things that aren’t objects (which is most things), hence the proliferation of patterns. I’m talking out of my butt however, I have not been exposed to OOP enough to properly understand it.

Oh, I see, I think I misunderstood your assertion then. I thought you meant that OOP scales better in general, which does not match my experience.

Unfortunately this seems to be a common misconception. Slowness is not an inherent property of effect libraries, effectful is fast.

By “fast” I mean in performance-critical applications, such as videogames, where an effect system would only truly shine if it’s zero-cost. Bad phrasing on my part.

Also am I reading the benchmarks incorrectly or are all the tests written around 2-3 effects? The production stack I wrote used roughly 15, so I’d expect a bit more of a convoluted setup.

Surely, effect can’t be faster than no effect. So when you mean fast, you mean the effect overhead is fast, do you ?

I’d argue that if you care about the overhead of the effect dispatch (which in effectful takes nanoseconds on modern hardware, i.e. countdown.1000.effectful (local/dynamic) does 2000 dispatches and runs 30 microseconds), Haskell might be the wrong tool for the job :slight_smile:

That’s what the shallow vs deep variation is for - it puts 10 additional effects in the stack to showcase that the effect dispatch is constant time, no matter how big the stack is. Compare this to what happens with other libraries (especially mtl).

Well, of course. But see above, the overhead is so small it’s largely irrelevant.

1 Like