maxharrison
maxharrison

Reputation: 99

Haskell: Keeping track and modifying state with Scotty HTTP API

Can I modify my state using IO via the Scotty API? Currently, I have a state transformer inside IO monad to modify state with user input. But I want to achieve this via the Scotty API.

This is my state transformer types I currently have that I use to keep modifying the state type and allow for IO actions.

-- State Transformer type inside IO monad
type STIO st a = STM st IO a

-- State transformer inside a monad
newtype STM st m a = S (st -> m (a, st))

... and with this lift functions to lift an action into the IO monad:

lift :: Monad m => m a -> STM st m a
lift mx = S (\s -> do
    x <- mx
    return (x, s))

This is my current bare bones Scotty server:

port = 8080

main = server

server :: IO ()
server = do
    print ("Starting Server at port " ++ show port)
    scotty port $ do
        get "/start" $ do
            json ("{starting: "++"True"++"}")

In my head I am wanting something along these lines, but unsure how to implement it:

type State = Int

server :: STIO State ()
server = do
    print ("Starting Server at port " ++ show port)
    lift $ scotty port $ do
        get "/start" $ do
            updateCounterByOneInState
            counter <- getCounterFromState
            json $ "{count: " ++ counter ++ "}"

Is something like this even possible, or am I just getting confused?

Upvotes: 1

Views: 145

Answers (1)

K. A. Buhr
K. A. Buhr

Reputation: 50829

Scotty, like all WAI applications, needs to be prepared to handle multiple concurrent requests in separate threads. This poses a bit of a problem for your STIO monad, since it doesn't directly support concurrent access to the state. You'd need to arrange to load the state, run the handlers, and save the state in a way that's concurrency-safe.

Technically, you can do this with help from the functions in Web.Scotty.Trans, but it's not a very good idea. For example, the following self-contained example stores the state in a concurrency-safe MVar:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}

import Web.Scotty.Trans as W
import Control.Monad.State as S
import Control.Concurrent.MVar
import Network.Wai.Handler.Warp (Port)
import Data.Text.Lazy (Text)

type STIO s = StateT s IO

scottySTIO :: MVar s -> Port -> ScottyT Text (STIO s) () -> (STIO s) ()
scottySTIO sref p = scottyT p $ \act -> do
  s <- takeMVar sref
  (r, !s') <- runStateT act s
  putMVar sref s'
  return r

server :: STIO Int ()
server = do
  let port = 8080
  liftIO $ print ("Starting Server at port " ++ show port)
  s <- S.get
  sref <- liftIO $ newMVar s
  scottySTIO sref port $ do
    W.get "/start" $ do
      modify (+1)
      counter <- S.get
      json $ "{count: " ++ show counter ++ "}"

main :: IO ()
main = evalStateT server 0

This will "work", but it will exhibit horrible concurrency performance because it ends up serializing all requests in their entirety, instead of just protecting critical code sections. It really only makes sense if you already have a huge amount of code running in the STIO monad, you don't want to modify any of it, and you're willing to take the performance hit.

Most of the time, it will be much easier to refactor your design to store the state in a concurrency-safe manner and access it directly from IO. For example, the counter can be stored in a single MVar and safely accessed in a short critical section:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}

import Web.Scotty
import Control.Concurrent.MVar
import Control.Monad.IO.Class

main :: IO ()
main = do
  let port = 8080
  print ("Starting Server at port " ++ show port)
  sref <- newMVar (0 :: Int)
  scotty port $ do
    get "/start" $ do
      -- start of critical section
      counter <- liftIO $ takeMVar sref
      let !counter' = counter + 1
      liftIO $ putMVar sref counter'
      -- end of critical section
      json $ "{count: " ++ show counter' ++ "}"

Upvotes: 1

Related Questions