如何使用 monad-control 通过 ReaderT 进行简单的新型包装

发布于 2025-01-03 05:06:37 字数 2785 浏览 1 评论 0原文

我定义了一个简单的 monad 转换器,EntityBuilderT,它只是 ReaderT 上的一个新类型。

data EntityBuilderState = ...

newtype EntityBuilderT m a = EntityBuilderT (ReaderT EntityBuilderState m a)

为了将函数包装在新的“环境”中,我编写了以下组合器:

withNewSource :: (Monad m) => String -> EntityBuilderT m a -> EntityBuilderT m a
withNewSource itemId builder = ...

在某些情况下,我还想构建更大的变压器堆栈。例如:

f :: MaybeT (EntityBuilderT m) a

显然,我无法将 withNewSource 应用于此函数 f,因为 monad 类型不再匹配。因此,我尝试使用 monad-control 编写此类组合器的新版本。

到目前为止我编写的代码如下所示。尽管实例定义似乎没问题,但编译器 (GHC 7.4.1) 拒绝了该代码并显示以下消息:

   Couldn't match type `IO' with `EntityBuilderT m0'
    When using functional dependencies to combine
      MonadBaseControl IO IO,
        arising from the dependency `m -> b'
        in the instance declaration in `Control.Monad.Trans.Control'
      MonadBaseControl (EntityBuilderT m0) IO,
        arising from a use of `control'
    In the expression: control
    In the expression: control $ \ run -> withNewSource itemId (run m)

我有点迷失了。有人知道问题到底是什么吗?


{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving,
             MultiParamTypeClasses, TypeFamilies, UndecidableInstances #-}

import Control.Applicative (Applicative)
import Control.Monad (liftM)
import Control.Monad.Base
import Control.Monad.Trans (MonadTrans)
import Control.Monad.Trans.Control
import Control.Monad.Trans.Maybe (MaybeT)
import Control.Monad.Trans.Reader (ReaderT, withReaderT)


data EntityBuilderState

newtype EntityBuilderT m a = EntityBuilderT { unEB :: ReaderT EntityBuilderState m a }
  deriving (Applicative, Functor, Monad, MonadTrans)

instance MonadBase b m => MonadBase b (EntityBuilderT m) where
    liftBase = liftBaseDefault

instance MonadTransControl EntityBuilderT where
    newtype StT EntityBuilderT a = StEB { unStEB :: StT (ReaderT EntityBuilderState) a }
    liftWith f = EntityBuilderT $ liftWith $ \run ->
                   f $ liftM StEB . run . unEB
    restoreT = EntityBuilderT . restoreT . liftM unStEB

instance MonadBaseControl b m => MonadBaseControl b (EntityBuilderT m) where
    newtype StM (EntityBuilderT m) a = StMT { unStMT :: ComposeSt EntityBuilderT m a }
    liftBaseWith = defaultLiftBaseWith StMT
    restoreM     = defaultRestoreM   unStMT


withNewSource :: (Monad m) => String -> EntityBuilderT m a -> EntityBuilderT m a
withNewSource itemId (EntityBuilderT m) = EntityBuilderT (withReaderT undefined m)

withNewSource' :: String -> MaybeT (EntityBuilderT IO) a -> MaybeT (EntityBuilderT IO) a
withNewSource' itemId m = control $ \run -> withNewSource itemId (run m)

I have defined a simple monad transformer, EntityBuilderT, that is just a newtype over ReaderT.

data EntityBuilderState = ...

newtype EntityBuilderT m a = EntityBuilderT (ReaderT EntityBuilderState m a)

To wrap a function in a new "environment", I have written the following combinator:

withNewSource :: (Monad m) => String -> EntityBuilderT m a -> EntityBuilderT m a
withNewSource itemId builder = ...

In certain cases, I also want to build a larger transformer stack. For example:

f :: MaybeT (EntityBuilderT m) a

Obviously, I cannot apply withNewSource to this function f as the monad types no longer match. I have therefore tried to use monad-control to write a new version of such combinator.

The code I've written thus far is shown below. Though the instance definitions seems to be OK, the compiler (GHC 7.4.1) rejects the code with the following message:

   Couldn't match type `IO' with `EntityBuilderT m0'
    When using functional dependencies to combine
      MonadBaseControl IO IO,
        arising from the dependency `m -> b'
        in the instance declaration in `Control.Monad.Trans.Control'
      MonadBaseControl (EntityBuilderT m0) IO,
        arising from a use of `control'
    In the expression: control
    In the expression: control $ \ run -> withNewSource itemId (run m)

I'm somewhat lost. Anyone understands what the problem really is?


{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving,
             MultiParamTypeClasses, TypeFamilies, UndecidableInstances #-}

import Control.Applicative (Applicative)
import Control.Monad (liftM)
import Control.Monad.Base
import Control.Monad.Trans (MonadTrans)
import Control.Monad.Trans.Control
import Control.Monad.Trans.Maybe (MaybeT)
import Control.Monad.Trans.Reader (ReaderT, withReaderT)


data EntityBuilderState

newtype EntityBuilderT m a = EntityBuilderT { unEB :: ReaderT EntityBuilderState m a }
  deriving (Applicative, Functor, Monad, MonadTrans)

instance MonadBase b m => MonadBase b (EntityBuilderT m) where
    liftBase = liftBaseDefault

instance MonadTransControl EntityBuilderT where
    newtype StT EntityBuilderT a = StEB { unStEB :: StT (ReaderT EntityBuilderState) a }
    liftWith f = EntityBuilderT $ liftWith $ \run ->
                   f $ liftM StEB . run . unEB
    restoreT = EntityBuilderT . restoreT . liftM unStEB

instance MonadBaseControl b m => MonadBaseControl b (EntityBuilderT m) where
    newtype StM (EntityBuilderT m) a = StMT { unStMT :: ComposeSt EntityBuilderT m a }
    liftBaseWith = defaultLiftBaseWith StMT
    restoreM     = defaultRestoreM   unStMT


withNewSource :: (Monad m) => String -> EntityBuilderT m a -> EntityBuilderT m a
withNewSource itemId (EntityBuilderT m) = EntityBuilderT (withReaderT undefined m)

withNewSource' :: String -> MaybeT (EntityBuilderT IO) a -> MaybeT (EntityBuilderT IO) a
withNewSource' itemId m = control $ \run -> withNewSource itemId (run m)

如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。

扫码二维码加入Web技术交流群

发布评论

需要 登录 才能够评论, 你可以免费 注册 一个本站的账号。

评论(1

黑寡妇 2025-01-10 05:06:37

问题是,因为基本 monad 是 IO,所以 run 的类型是 MaybeT (EntityBuilderT IO) a -> IO (StM (MaybeT (EntityBuilderT IO) a)),但您将其返回值用作 EntityBuilderT IO 操作。此外,传递给 control 的函数的返回值必须位于 IO 中,而不是 EntityBuilderT IO 中。

这是因为您的 MonadBaseControl 实例表示您将事物提升到转换后的 monad m 的基础 monad 中;由于 MaybeT (EntityBuilderT IO) 的基础是 IO,因此 controlRunInBase (MaybeT (EntityBuilderT IO)) IO 获取函数IO (StM (MaybeT (EntityBuilderT IO)) a)

不幸的是,我在 monad-control 方面没有足够的经验来提出解决方案;也许您可以使用 MaybeT 的 MonadTransControl 实例来实现“下一级”功能?

The problem is that, because the base monad is IO, run has type MaybeT (EntityBuilderT IO) a -> IO (StM (MaybeT (EntityBuilderT IO) a)), but you're using its return value as an EntityBuilderT IO action. Additionally, the return value of the function you pass to control must be in IO, not EntityBuilderT IO.

This is because your MonadBaseControl instance says that you lift things into the base monad of the transformed monad m; since the base of MaybeT (EntityBuilderT IO) is IO, control takes a function from RunInBase (MaybeT (EntityBuilderT IO)) IO to IO (StM (MaybeT (EntityBuilderT IO)) a).

Unfortunately, I'm not experienced enough with monad-control to suggest a solution; perhaps you could use MaybeT's MonadTransControl instance to achieve the "one level down" functionality?

~没有更多了~
我们使用 Cookies 和其他技术来定制您的体验包括您的登录状态等。通过阅读我们的 隐私政策 了解更多相关信息。 单击 接受 或继续使用网站,即表示您同意使用 Cookies 和您的相关数据。
原文