3

I have the following Scotty app:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Web.Scotty
import Data.Monoid (mconcat)
import Control.Concurrent.STM
import Control.Monad.IO.Class
import Control.Concurrent

main :: IO ()
main = do
  counter <- newTVarIO 0
  scotty 3000 $
    get "/:word" $ do
      liftIO $ threadDelay 1000000
      liftIO $ atomically $ do
        counter' <- readTVar counter
        writeTVar counter (counter' + 1)
      liftIO $ do
        counter' <- atomically (readTVar counter)
        print counter'
      beam <- param "word"
      html $ mconcat ["<h1>Scotty, ", beam, " me up!</h1>"]

And am invoking the exposed endpoint like this (200 concurrent requests):

wrk -c 200 -t 20 -d 10 http://127.0.0.1:3000/z

I was expecting the value of the counter' to be printed sequentially. However, some numbers are missing, and some are duplicated (for example 147 is there twice, but 146 is not there at all).

Two questions:

  1. The only way this can happen I think is that the second liftIO is not necessarily followed by the third liftIO. Is this correct? Or is there another explanation for it?

  2. How can I print the value of counter' in the second liftIO? I'm not sure how to place it between (or after) readTVar and writeTVar.

snak
  • 6,483
  • 3
  • 23
  • 33
zoran119
  • 10,657
  • 12
  • 46
  • 88
  • I've not used STM before, but it seems your proposed explanation is plausible, there is nothing preventing other threads executing between the 2nd and 3rd liftIO. If you want to print directly the new value, i would use `liftIO $ print =<< atomically (stateTVar counter (\c -> (c+1,c+1)))` (might need to massage that a bit) – moonGoose Apr 11 '19 at 12:09

1 Answers1

2

There are a couple problems with your code. First, as you point out, anything can happen in between the 2nd and 3rd liftIOs (that is, between incrementing the counter and reading it again). You can restructure the code like this to fix that:

main :: IO ()
main = do
  counter <- newTVarIO 0
  scotty 3000 $
    get "/:word" $ do
      -- wrap IO in do-block to avoid repeating liftIO
      liftIO $ do
        threadDelay 1000000
        -- Remember the value instead of reading it again.
        value <- atomically $ do
          x <- readTVar counter
          let x' = x + 1
          writeTVar counter x'
          return x'
        print value
      beam <- param "word"
      html $ mconcat ["<h1>Scotty, ", beam, " me up!</h1>"]

This will fix the missing numbers and duplicated numbers. However, the output still looks messy because of interleaved print results. You could fix that by following the suggestion in Can I ensure that Haskell performs atomic IO?:

main :: IO ()
main = do
  counter <- newTVarIO 0
  -- Create a lock for printing.
  lock <- newMVar ()
  scotty 3000 $
    get "/:word" $ do
      liftIO $ do
        threadDelay 1000000
        value <- atomically $ do
          x <- readTVar counter
          let x' = x + 1
          writeTVar counter x'
          return x'
        -- Hold a lock while printing.
        withMVar lock $ \_ -> print value
      beam <- param "word"
      html $ mconcat ["<h1>Scotty, ", beam, " me up!</h1>"]

This cleans up the output, but it still doesn't guarantee the numbers will be printed in sequence, since anything can happen in between the atomically and withMVar sections. When I ran it, as expected the output was mostly in sequence (numbers 1 through 2180) but with a few exceptions.

There might be a way of performing both the increment and print atomically, but the STM monad isn't designed to make that easy. In particular, see all the warnings about using unsafe IO with atomically.

mk12
  • 25,873
  • 32
  • 98
  • 137