I have some function app :: StateT AppState IO ()
which maintains some application state whilst doing a bunch of computation and IO (I have defined main = void $ runStateT app initialState
). I want to register a signal handler handler :: StateT AppState IO ()
which can look at and modify the current state by writing something like
installHandler sigINT (Catch handler) Nothing
This does not work because Catch :: IO () -> Handler
and handler :: StateT AppState IO ()
.
I have tried the following:
installHandler . Catch . pure <$> handler <*> pure Nothing
This runs handler
the instant this line of code is evaluated (since we are using the StateT
applicative). Moreover, Catch . pure <$> handler
is the same as Catch . pure $ ()
since we run the side effects to retrieve ()
, then applying pure
just wraps this up in IO
without capturing those side effects.
Is there a way I can register the signal handler so that it actually does stuff without breaking the abstraction of StateT
? I would appreciate any advice!
Also, sorry if I have ruffled any feathers by using the phrase "side effects".
As per @chi's comment, there's no way to get this exact design to work.
Signals are handled via a separate IO thread, so the most straightforward way of implementing this is via a shared mutable reference that is "known" to the application monad and provided via a closure to the handler function.
If the handler only needs to access a tiny part of the state, and that tiny part isn't used much throughout the rest of the application, then the easiest approach will be to add a field to the application state to store either an IORef
or an MVar
to that tiny piece of state.
In particular, if you're just trying to set a flag in the handler that will be "noticed" in an application loop, an IORef
will be fine. The following program illustrates the general approach:
{-# LANGUAGE OverloadedRecordDot #-}
import System.Posix.Signals
import Control.Concurrent
import Control.Monad.State
import Data.IORef
data AppState = AppState
{ count :: Int
, flagINT :: IORef Bool
}
app :: StateT AppState IO ()
app = do
x <- gets count
modify $ \s -> s{count=s.count+1}
liftIO $ putStrLn $ "Running " ++ show x
liftIO $ threadDelay 1000000
quit <- gets flagINT >>= liftIO . readIORef
if quit then do
liftIO $ putStrLn "Quitting"
else app
main = do
flagINT_ <- newIORef False
installHandler sigINT (Catch (writeIORef flagINT_ True)) Nothing
runStateT app (AppState 0 flagINT_)
Here, I've installed the handler in main
where I directly access the flagInt_
mutable reference that's created there. Alternatively, you can set the handler in the application monad by reading the flag reference from the state:
setINTHandler :: StateT AppState IO ()
setINTHandler = do
flagINT_ <- gets flagINT
liftIO $ installHandler sigINT (Catch (writeIORef flagINT_ True)) Nothing
pure ()
A few things to note:
flagInt
is a field of a mutable State
, this is only for convenience. flagInt
is just accessed as a read-only only field that gives the mutable reference for the actual mutable flag. It could just as well be part of a separate Reader
.IORef
here and non-atomic writeIORef
is sufficiently thread-safe for this particular example. If you're performing a more complicated manipulation of the state within the handler), then you may need to be a little more careful and maybe switch to using an MVar
.If, as you seem to be suggesting in your question, you want to perform a fairly complex manipulation of the state from the handler, then you need to rewrite your program with a concurrency-safe explicit state. A monadic State
won't work well for this. For performance reasons, you can't be locking and unlocking the state for every monadic operation. Instead, you'll need to operate in the IO
monad and manipulate the state more explicitly.
Note that a reasonable design for this might be to use an application monad of the form:
app :: ReaderT (MVar AppState) IO ()
where you takeMVar
and putMVar
the state over chunks of main application code. When the handler is invoked, it will wait on the next main application putMVar
before performing its manipulation.