Does effectful have a policy on thread safety? #293
-
I was wondering if effectful has a policy on the thread safety of code written using it. Currently the provided functionality seems to support
(which seems perfectly reasonable). I wonder if this is actually the intended policy. In particular, it's quite easy to write code that doesn't look obviously thread-unsafe, but actually is. For example, something like the below. The reason this isn't obviously thread unsafe is that the use of In particular, it is possible to interpret any dynamic effect, even one that might be used concurrently, in a non-thread safe way. As far as I can tell, effectful's policy is essentially "Use either #!/usr/bin/env cabal
{- cabal:
build-depends: base, effectful==2.5.1.0, async
-}
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
import Control.Concurrent
import Control.Concurrent.Async
import Data.IORef
import Effectful
import Effectful.Dispatch.Dynamic
import Effectful.State.Dynamic
evalState ::
(IOE :> es) =>
s ->
Eff (State s : es) a ->
Eff es a
evalState s0 m = do
v <- liftIO (newIORef s0)
reinterpret id (ioState v) m
ioState ::
(IOE :> es) =>
IORef s ->
LocalEnv localEs es ->
State s (Eff localEs) a ->
Eff es a
ioState v env = \case
Get -> liftIO (readIORef v)
Put s -> liftIO (writeIORef v s)
State f -> liftIO $ do
s <- readIORef v
let (r, s') = f s
writeIORef v s
pure r
StateM _ -> error "Dunno"
useStateConcurrently ::
(State Int :> es, IOE :> es) => Eff es ()
useStateConcurrently = do
withEffToIO (ConcUnlift Persistent Unlimited) $
\effToIO -> do
concurrently
( effToIO $ do
liftIO (threadDelay 500)
s <- get @Int
put (s + 1)
)
( effToIO $ do
s <- get @Int
liftIO (threadDelay 1000)
put (s * 2)
)
(liftIO . print) =<< get @Int
-- We "want" the result to be either
--
-- - 12 (== (5 + 1) * 2), or
--
-- - 11 (== (5 * 2) + 1)
--
-- but we get
--
-- % cabal run test-effectful-thread-unsafe.hs
-- 10
main :: IO ()
main = runEff $ do
evalState @_ @Int 5 $ do
useStateConcurrently |
Beta Was this translation helpful? Give feedback.
Replies: 1 comment 1 reply
-
Yes, that's pretty much it. Correctly working primitives are there, if someone wants to reimplement them for some reason, they should know what they're doing. |
Beta Was this translation helpful? Give feedback.
Yes, that's pretty much it. Correctly working primitives are there, if someone wants to reimplement them for some reason, they should know what they're doing.