Restore the State while Using Effectful

{-# OPTIONS_GHC -fplugin=Effectful.Plugin #-}
import Effectful
import Effectful.State.Static.Shared
import Effectful.Concurrent (runConcurrent)
import Effectful.Concurrent.MVar
import Control.Monad (replicateM)

action :: (State Int :> es, IOE :> es) => Eff es Int
action = do
    modify (+1)
    n <- get
    liftIO $ print n
    return n

magic :: (forall a. Eff es a -> IO a) -> Eff es b -> IO (IO b)
magic _ = undefined

actionMagic :: IO (IO Int)
actionMagic = magic runEff $ evalState 0 action

actionMVar :: IO (IO Int)
actionMVar = runEff $ runConcurrent $ do
    mvar <- newMVar 0
    return $ runEff $ evalStateMVar mvar action

main :: IO ()
main = do
    action' <- actionMVar
    replicateM 5 action' >>= print

-- output:
-- 1
-- 2
-- 3
-- 4
-- 5
-- [1,2,3,4,5]

I have an action with side effects that is wrapped in the Eff monad. How to restore the side effect so that when this action is called multiple times, the state is continued? Can such a “magic” function be implemented for all the possible effect rows (that include IOE, maybe)? Will unliftio help?

I’m not sure I follow exactly what you’re trying to do, but it certainly sounds strange. Could you give some more explanation about what you need this for?

firstly magic just sounds like an unlift, they will maintain state so they may be exactly what you need.

However if a unlift isn’t what you want how much of the state would be saved/stored in your example you use a MVar.
Would your magic function need to save the values of all MVars in the program ? If not what should be saved exactly?
Depending on how much needs to be watched this goes from trivial. if you only need certain MVars created with a specific function you supply. To hellish if you need to hook into the RTS or garbage collector to monitor all MVars in the Program.

Doesn’t seem like you can implement magic to get exactly the output you posted in a simple way.

If the action increments state and prints, and you call evalState 0 on it, then we’ve locked the state to be 0 and for the thing to print 1 every time we run the action.

If we don’t care about the printing, then we can get the actionMVar solution by doing something dumb along the same lines

magic runEff action = do
  mvar <- IO.newMVar 0
  pure $ do 
    result <- action
    modifyMVar mvar (\i -> pure (i + result, i + result))
    // applies to entire do block
    & runConcurrent
    & runEff

However if you could stay in the eff monad and not need to run the effect stack each action then you could share the state like in the evalStateMVar case. Alternatively, if you could pass the state of the previous action to the evalState of the next action then we could do the same.