Search code examples
haskellmonad-transformershaskell-lensioref

Zoom instance for ReaderT IORef


I'm new to lens and having trouble implementing the Zoom instance for this type:

newtype MyStateT s m a = MyStateT
    { unMyStateT :: ReaderT (IORef s) m a
    } deriving (Functor, Applicative, Monad, MonadIO)

instance (MonadIO m) => MonadState s (MyStateT s m) where
    get = MyStateT $ ReaderT $ liftIO . readIORef
    put x = MyStateT $ ReaderT $ \ref -> liftIO $ writeIORef ref x

I've been trying to make a new IORef with the lens substate, run the ReaderT on that substate, and then grab the changed substate and replace it in the main IORef:

type instance Zoomed (MyStateT s m) = Focusing m
instance (Monad m) => Zoom (MyStateT s m) (MyStateT t m) s t where
    zoom l (MyStateT r) =
        MyStateT $ ReaderT $ \ref -> do
            s <- liftIO $ readIORef ref
            ref' <- liftIO $ newIORef $ s ^. l
            let v = runReader r ref'
            subS' <- liftIO $ readIORef ref'
            let s' = s & l .~ subS'
            liftIO $ writeIORef ref s'
            return v

l seems to be different from a normal lens so ^. and .~ doesn't compile with it and I get errors like this:

    • Couldn't match type ‘Focusing m c t’ with ‘Const s t’
  Expected type: Getting s t s
    Actual type: LensLike' (Zoomed (MyStateT s m) c) t s
   • Couldn't match type ‘Focusing m c t’ with ‘Identity t’
  Expected type: ASetter t t s s
    Actual type: LensLike' (Zoomed (MyStateT s m) c) t s

Can anyone help me get this Zoom instance to work properly? Thanks!


Solution

  • My suggestion would be:

    type instance Zoomed (MyStateT s m) = Focusing m
    
    instance (MonadIO m) => Zoom (MyStateT s m) (MyStateT t m) s t where
        zoom l (MyStateT r) =
            MyStateT $ ReaderT $ \ref -> do
                s <- liftIO $ readIORef ref
                (v', s') <- unfocusing . flip l s $ \t -> Focusing $ do
                    ref' <- liftIO (newIORef t)
                    v <- runReaderT r ref'
                    t' <- liftIO (readIORef ref')
                    return (v, t')
                liftIO $ writeIORef ref s'
                return v'
        {-# INLINE zoom #-}
    

    The problem you were having with (^.) and (.~) is that they work for Lens, which is polymorphic in the functor. But here the functor is fixed to be Zoomed (MyState s m) c, which is Focusing m c. So you need to apply l directly using function application.

    Note: You need to be a bit careful with this implementation. IORef ins't atomic, unless you use atomicModifyIORef on a pure function (which doesn't seem possible in zoom). So it might make sense to use MVar with takeMVar and putMVar instead, to make sure your computations work correctly when running in a multi-threaded environment.