
On Thu, 2020-08-27 at 01:20 +0300, Georgi Lyubenov wrote:
Hi!
I believe the canonical way to handle this in Yesod is the "reader pattern" (https://www.fpcomplete.com/blog/2017/06/readert-design-pattern): * it's by the same author
I think the essence of the above blog post concerning state is the following. The overlapping instance hints at why this is not in Yesod in this generality. It is probably fine to declare such a MonadState instance for any concrete reader monad, though. Olaf {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} import Control.Monad.Reader import Control.Monad.State.Class import Data.IORef class Monad m => Ref m var where readRef :: var a -> m a writeRef :: var a -> a -> m () modifyRef :: var a -> (a -> a) -> m () modifyRef v f = readRef v >>= (writeRef v . f) instance Ref IO IORef where readRef = readIORef writeRef = writeIORef modifyRef = modifyIORef getRef :: Ref m var => ReaderT (var a) m a getRef = ReaderT readRef putRef :: Ref m var => a -> ReaderT (var a) m () putRef = ReaderT . flip writeRef instance {-# OVERLAPPING #-} Ref m var => MonadState a (ReaderT (var a) m) where get = getRef put = putRef