[Help] Print every N seconds while in recursive loop

Hi, let’s say I have a recursive loop - it’s a crosswords solver, could be a sudoku/scrabble/any BFS recursive solver.

  • I know how to print at each recursion. My function recurse has a -> IO() return type
  • What I don’t know is to print “at most each second”. And haven’t tried using an MVar yet.
  • Kudos it this also helps me terminate the recursion after N solutions

Scenario, let’s say the function does roughly

recurse matrix = let
    -- computing child outcomes
    children = allNextStates matrix
    in do
        print matrix
        mapM_ recurse children

I’d like this function to “print only if one second is elapsed till the last print”. What is your advice ? today I can imagine a solution based on an additional MVar parameter which would contain lastTimeStamp and compute now. Upon printing again, the MVar would get updated. This would also allow me to store a solutionsCount to exit early from the recursion when some threshold goal has been reached.

FWIW the code is here and a working JS equivalent can be found here. Any trivial or standard way of doing this other than an MVar parameter ?

An attempt:

from your main, fork 2 threads: one for the solver, one for a timer that sleeps and then reads the “state” MVar. If some condition is reached, throw an exception to the first thread to stop it.

1 Like

Thanks @ocramz … but I have sufficient experience in other languages to know that it would be an anti-pattern.

  • I don’t need realtime (in which case threads would be one solution)
  • I don’t really care about the (perfection of the) delay, I just want to print “once in a while”
  • Involving concurrent thread for a typically sequential process would be adding burden

I’ll let you (all) know once I’ve used an MVar. My question is more “you advanced haskellers” how would you (advise me to) do that ?

Not saying it isn’t overkill but haskell uses “green threads” which are very light weight. So the burden (at least in terms of computation cost) is quite low compared to what one might expect.

If your code is single threaded I would probably use what you said except I would use an IORef instead of an MVar. If you want to be fancy you can use a State(T) monad (transformer) to abstract the IORef passing away but that seems overkill for this.

Or even better just pass the time itself along using State!

The 1:1 correspondence to your JS code would be using a top level mutable variable:

{-# NOINLINE newIORef #-}
lastTimeStamp = unsafePerformIO $ do
    time <- <getTime>
    newIORef time

recurse matrix = let
    -- computing child outcomes
    children = allNextStates matrix
    in do
        current_time <- <getTime>
        old_time <- readIORef lastTimeStamp
        when (<timespan large enough>) $ print matrix
        mapM_ recurse children

But global mutable state is generally considered an anti pattern in Haskell :slight_smile: So not sure why this was the one approach were i wrote out pseudo code.

1 Like

I was indeed referring to “green thread” concurrency, as in Control.Concurrent .

Wow thx, that’s exactly the kind of advice I’m looking for.

I know it’s not stackoverflow (and that’s what I like here) But basically

  • Use an MVar
  • Better, use an IORef
  • Better, go into the State monad.

Sometimes explicitly passing an argument can be a clearer alternative than using a state monad. (Especially if it’s a single self-recursive function or a small number of mutually recursive functions). But to some degree that’s a matter of taste.

2 Likes

While I’m still not accustomed to the whole process, I prefer argument passing.

Looking here, stackoverflow suggests I should refrain from using an IORef and go straight to ST.

Thanks all - I have sufficient… insight to try something. I will go for ST and may fallback to IORef. Will let you know the outcome (for an IO newbie like me)

one problem is that you cannot run an IO action like synchronous logging and timeouts within the ST monad. So your synchronous “orchestration”/threading mechanism has to be in IO, and you might as well use an IORef for state sharing.

1 Like

I’d suggest decoupling the solution generation from the printing and the termination. So something like this:

allSolutions :: Matrix -> [Matrix]
allSolutions matrix = matrix : (allNextStates matrix >>= allSolutions)

mkThrottledPrinter :: TimeDifference -> IO (Matrix -> IO ())
mkThrottledPrinter minPeriod = do
  lastTimeRef <- newIORef Nothing
  return $ \matrix -> do
    currentTime <- getCurrentTime
    shouldPrint <- atomicModifyIORef' lastTimeRef $ \case
      Just lastTime | currentTime - lastTime < minPeriod -> (Just lastTime, False)
      _ -> (Just currentTime, True)
    when shouldPrint $ print matrix

printNSolutions :: TimeDifference -> Int -> Matrix -> IO ()
printNSolutions minPeriod maxSolutions matrix = do
  throttledPrinter <- mkThrottledPrinter minPeriod
  forM (take maxSolutions $ allSolutions matrix) $ \matrix -> 
    throttledPrinter matrix
1 Like

I’m a bit late to the party, but I think you just need threadDelay.

Especially considering that your goal is not a perfect delay (unlike, e.g., a game engine loop, where you want to render a frame exactly, say, every 16ms), you don’t even need to count how much time your previous iteration took to get the time-left to sleep.

import Control.Concurrent
mapM_ (\x -> threadDelay 1_000_000 >> print x) [1,2,3,4,5,6::Int]

Using your example

import Control.Concurrent -- from base
recurse matrix = let
    -- computing child outcomes
    children = allNextStates matrix
    in do
        print matrix
        threadDelay 1_000_000
        mapM_ recurse children

To stop recursion after N solutions I’d likely thread through a time-to-live (TTL) and kill the recursion when that TTL reaches 0:

import Data.Traversable (mapAccumM)
-- mapAccumM :: (s -> a -> m (s,b)) -> s -> [a] -> m (s, [b])

n = 100

main = recurse n 0 where
  recurse ttl x = do
    let
      children = [x+1..x+3]
      go ttl' child
        | ttl' == 0 = return (0, ())
        | otherwise = recurse (ttl'-1) child
    print x
    (finalTtl, _) <- mapAccumM go ttl children
    return (finalTtl, ())

Thanks @ocramz and @AndreasPK : I’ve used an IORref, full disclosure

So the basic idea which works + seems idiomatic to me is the one from AndreasPK :

  • newIORef after getCurrentTime
  • readIORef, compare to getCurrentTime
  • when delay is expired, both print and atomicWriteIORef

You can get best of both worlds with Bluefin:

but with the ability to remove effects from scope, like ST.

1 Like

Thanks to all of you who helped me here !

Not to brag - but to offer a little bit of context - here’s what I’ve prototypes in NodeJS - a Crosswords generation algo.

I’m rewriting it in Haskell now, and that will allow for more fine tuned optimisations. The algo is in the CSP class - NP-hard but only a few solutions matter, not all. Thank you !

  1. please don’t use IORefs when you have any amount of concurrency, they really have no mechanisms of synchronization and it is trivial to generate race conditions with them
  2. error "success" please don’t use exceptions as control flow
  3. we have System.Timeout which seems to do what you semantically want to do
    but besides this it looks good
1 Like
  1. Not my case, warning taken
  2. Of course ! It’s a work in progress
  3. Will read the documentation thank you

1 sure but we are talking about one writing thread and one that reads