Description
Describe the bug
Sometimes an enclosing call to 'local' for a particular Reader capability causes the accumulated value for a (conceptually unrelated) Writer capability to be reset. This only seems to happen when the concrete monad implementing the capabilities stores the values in the same record, though it's possible the record thing is a red herring.
To Reproduce
Below is the smallest example I have been able to come up with.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE TypeApplications #-}
import qualified Capability.Reader as CR
import qualified Capability.Sink as CSk
import qualified Capability.Source as CSc
import qualified Capability.State as CS
import qualified Capability.Writer as CW
import qualified Control.Monad.Reader as MR
import qualified Control.Monad.State as MS
import Data.Bifunctor (second)
import Data.Monoid (Sum (..))
import GHC.Generics (Generic)
------------------------------------------------------------
-- This is the generic action we will run. The fact that the call to 'tell' is enclosed within
-- a call to 'local' should not affect the accumulated Writer value, but as we will see,
-- sometimes it does.
act :: (CW.HasWriter "w" (Sum Int) m, CR.HasReader "r" Char m) => m ()
act = CR.local @"r" (const 'b') $ do
CW.tell @"w" (Sum 1)
return ()
------------------------------------------------------------
-- One concrete monad with the required capabilities, simply using mtl transformers.
newtype M1 a = M1 { unM1 :: MS.StateT (Sum Int) (MR.Reader Char) a }
deriving (Functor, Applicative, Monad)
deriving (CW.HasWriter "w" (Sum Int), CSk.HasSink "w" (Sum Int)) via
(CW.WriterLog
(CS.MonadState
(MS.StateT (Sum Int) (MR.Reader Char))))
deriving (CR.HasReader "r" Char, CSc.HasSource "r" Char) via
(CR.MonadReader
(MS.StateT (Sum Int) (MR.Reader Char)))
runM1 :: M1 a -> (a, Sum Int)
runM1 = flip MR.runReader 'a' . flip MS.runStateT mempty . unM1
------------------------------------------------------------
-- Another concrete monad with the required capabilities, this time using a state monad
-- with a single record, using the Field strategy to pick out fields for the various capabilities.
data S = S { w :: Sum Int, r :: Char }
deriving (Eq, Ord, Show, Generic)
newtype M2 a = M2 { unM2 :: MS.State S a }
deriving (Functor, Applicative, Monad)
deriving (CW.HasWriter "w" (Sum Int), CSk.HasSink "w" (Sum Int)) via
(CW.WriterLog
(CS.Field "w" ()
(CS.MonadState
(MS.State S))))
deriving (CR.HasReader "r" Char, CSc.HasSource "r" Char) via
(CS.Field "r" ()
(CR.ReadStatePure
(CS.MonadState
(MS.State S))))
runM2 :: M2 a -> (a, Sum Int)
runM2 = second w . flip MS.runState (S 0 'a') . unM2
------------------------------------------------------------
main = do
let ((), s') = runM1 act
print (getSum s')
let ((), s) = runM2 act
print (getSum s)
Expected behavior
I expect the above code to print 1 twice; which concrete monad + deriving strategies we use should not change the semantics of 'act', especially when only Reader + Writer are involved (which should commute etc.) and there are no IO or exceptions anywhere to be seen.
Instead, the above code prints 1, then 0.
Environment
- OS name + version: Ubuntu 20.10
- Version of the code: I am using capability 0.4.0.0 and compiling with GHC 8.10.4 and cabal-install 3.4.0.0.