如何使用 monad-control 通过 ReaderT 进行简单的新型包装
我定义了一个简单的 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 技术交流群。
绑定邮箱获取回复消息
由于您还没有绑定你的真实邮箱,如果其他用户或者作者回复了您的评论,将不能在第一时间通知您!
发布评论
评论(1)
问题是,因为基本 monad 是 IO,所以 run 的类型是 MaybeT (EntityBuilderT IO) a -> IO (StM (MaybeT (EntityBuilderT IO) a)),但您将其返回值用作
EntityBuilderT IO
操作。此外,传递给control
的函数的返回值必须位于IO
中,而不是EntityBuilderT IO
中。这是因为您的
MonadBaseControl
实例表示您将事物提升到转换后的 monadm
的基础 monad 中;由于MaybeT (EntityBuilderT IO)
的基础是IO
,因此control
从RunInBase (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 typeMaybeT (EntityBuilderT IO) a -> IO (StM (MaybeT (EntityBuilderT IO) a))
, but you're using its return value as anEntityBuilderT IO
action. Additionally, the return value of the function you pass tocontrol
must be inIO
, notEntityBuilderT IO
.This is because your
MonadBaseControl
instance says that you lift things into the base monad of the transformed monadm
; since the base ofMaybeT (EntityBuilderT IO)
isIO
,control
takes a function fromRunInBase (MaybeT (EntityBuilderT IO)) IO
toIO (StM (MaybeT (EntityBuilderT IO)) a)
.Unfortunately, I'm not experienced enough with monad-control to suggest a solution; perhaps you could use
MaybeT
'sMonadTransControl
instance to achieve the "one level down" functionality?