使用带外数据编写 monad(也称为并行组合 monad)

发布于 2025-01-04 09:36:26 字数 559 浏览 3 评论 0原文

我目前正在编写一个名为 GL 的 monad 封装 OpenGL,并且我希望能够查询计算以获取它可能需要的每个纹理的列表。

这是一个已解决的问题吗?我在为 GL 编写 Monad 实例时遇到很多麻烦。

这是我到目前为止所尝试过的:

-- GL should be able to be inspected for its HashSet without running the computation.
newtype GL a = GL (S.HashSet String) (IO a)

instance Monad (GL a) where
    return = GL S.empty . return -- Calls IO.return
    (>>=) (GL textures action) f = -- What goes here?

但我是不是找错了树?它实际上并不能作为一个 monad 工作,因为我必须在运行它之前查询它。我应该用什么来代替?我真的很喜欢使用 do 表示法。

我认为这可以分解为:如何并行组合两个 monad,然后独立运行它们?

I'm currently writing a monad wrapping OpenGL called GL and I want to be able to query a computation to get a list of every texture it would possibly need.

Is this a solved problem? I'm having a lot of trouble writing the Monad instance for GL.

This is what I've tried so far:

-- GL should be able to be inspected for its HashSet without running the computation.
newtype GL a = GL (S.HashSet String) (IO a)

instance Monad (GL a) where
    return = GL S.empty . return -- Calls IO.return
    (>>=) (GL textures action) f = -- What goes here?

but am I barking up the wrong tree? It doesn't really work as a monad, since I have to query it before running it. What should I be using instead? I realllly like using do-notation.

I think this breaks down to: How do I compose two monads in parallel, then run them independently?

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

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

发布评论

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

评论(2

过去的过去 2025-01-11 09:36:26

您的 GL 类型的问题是“计算结果”a 依赖于 IO 操作,因此您无法实现一个 monad 实例,在该实例中您可以在不运行的情况下计算最终纹理 HashSet IO 动作。

正确的解决方案取决于您想要如何使用 GL monad 的详细信息,但假设您可以决定使用哪些纹理而不运行 IO 操作,那么您可以使用这样的类型,

type GL a = WriterT (Set String) (Writer (IO ())) a

即您使用两个嵌套的 writer monad,一个用于纹理,另一个用于累积 IO 操作。生成的 monad 堆栈分两个阶段运行,您无需执行 IO 操作即可获得最终的纹理集。

不幸的是,Writer 仅适用于 monoid,因此我们需要首先为 IO () 定义一个 Monoid 实例。

{-# LANGUAGE FlexibleInstances #-}

import Data.Monoid

instance Monoid (IO ()) where
    mempty = return ()
    mappend = (>>)

现在,您可以编写一个注册新纹理的函数,如下所示:

addTexture :: String -> GL ()
addTexture = tell . S.singleton

另一个函数缓存要稍后执行的 IO 操作

addIO :: IO () -> GL ()
addIO = lift . tell

这是一个用于运行 GL monad 的实用函数

runGL :: GL a -> (a, Set String, IO ())
runGL gl = let iow = runWriterT gl
               ((a, textures), io) = runWriter iow
            in (a, textures, io)

这会重新调整一个包含三个元素的元组: 计算的结果值,累积纹理集和累积 io 动作。请注意,此时,元组中的 IO () 值仅描述了操作,并且尚未执行任何操作(例如绘图操作)。

我不确定这是否涵盖您的用例,但希望它能给您一些关于如何构建合适的 monad 堆栈的想法。如果您需要更多帮助,请提供一些有关您希望如何实际使用 GL monad 的示例。

这是我测试过的完整代码。请注意,我使用了 Set 类型而不是 HashSet,因为根据 hashmap 库,HashSet 名称已弃用。

{-# LANGUAGE FlexibleInstances #-}

import Control.Monad.Writer
import Data.Monoid
import Data.HashSet (Set)
import qualified Data.HashSet as S

instance Monoid (IO ()) where
    mempty = return ()
    mappend = (>>)

type GL a = WriterT (Set String) (Writer (IO ())) a

addTexture :: String -> GL ()
addTexture = tell . S.singleton

addIO :: IO () -> GL ()
addIO = lift . tell

runGL :: GL a -> (a, Set String, IO ())
runGL gl = let iow = runWriterT gl
               ((a, textures), io) = runWriter iow
            in (a, textures, io)

编辑:如果将 IO 效果包装在新类型中,您还可以避免语言扩展,如 dave4420 所建议的。

import Control.Monad.Writer
import Data.Monoid
import Data.HashSet (Set)
import qualified Data.HashSet as S

newtype WrapIO = WrapIO { unwrapIO :: IO () }

instance Monoid WrapIO where
    mempty = WrapIO 
nbsp;return ()
    WrapIO a `mappend` WrapIO b = WrapIO $ a >> b

type GL a = WriterT (Set String) (Writer WrapIO) a

addTexture :: String -> GL ()
addTexture = tell . S.singleton

addIO :: IO () -> GL ()
addIO = lift . tell . WrapIO

runGL :: GL a -> (a, Set String, IO ())
runGL gl = let iow = runWriterT gl
               ((a, textures), WrapIO io) = runWriter iow
            in (a, textures, io)

The problem with your GL type is that the "result of the computation" a is dependent on IO-actions, and therefore you can't implement a monad instance where you could compute the final texture HashSet without running the IO-actions.

The correct solution depends on the details on how you want to use the GL monad, but assuming that you can decide which textures to use without running IO-actions then you could a type like this

type GL a = WriterT (Set String) (Writer (IO ())) a

I.e. you use two nested writer monads, one for textures and one for accumulating the IO actions. The resulting monad stack is run in two phases, and you can get the final texture set without executing the IO actions.

Unfortunately, Writer only works for monoids so we need to define a Monoid instance for IO () first.

{-# LANGUAGE FlexibleInstances #-}

import Data.Monoid

instance Monoid (IO ()) where
    mempty = return ()
    mappend = (>>)

Now, you can write a function that registers a new texture like this:

addTexture :: String -> GL ()
addTexture = tell . S.singleton

And another function that caches an IO action to be executed later

addIO :: IO () -> GL ()
addIO = lift . tell

Here's an utility function for running the GL monad

runGL :: GL a -> (a, Set String, IO ())
runGL gl = let iow = runWriterT gl
               ((a, textures), io) = runWriter iow
            in (a, textures, io)

This retuns a tuple with three elements: the result value from the computation, the set of accumulated textures and the accumulated io actions. Note that at this point, the IO () value in the tuple just describes the action and nothing (e.g. drawing operations) haven't been executed yet.

I'm not sure if this covers your use-case, but hopefully it will give you some ideas on how to build a suitable monad stack. If you need more help, please provide some examples on how you want to actually use the GL monad.

Here's the complete code that I tested. Note that I used the type Set instead of HashSet, because according to the documentation of the hashmap library, the HashSet name is deprecated.

{-# LANGUAGE FlexibleInstances #-}

import Control.Monad.Writer
import Data.Monoid
import Data.HashSet (Set)
import qualified Data.HashSet as S

instance Monoid (IO ()) where
    mempty = return ()
    mappend = (>>)

type GL a = WriterT (Set String) (Writer (IO ())) a

addTexture :: String -> GL ()
addTexture = tell . S.singleton

addIO :: IO () -> GL ()
addIO = lift . tell

runGL :: GL a -> (a, Set String, IO ())
runGL gl = let iow = runWriterT gl
               ((a, textures), io) = runWriter iow
            in (a, textures, io)

EDIT: You can also avoid the language extension if you wrap the IO effects in a newtype, as suggested by dave4420.

import Control.Monad.Writer
import Data.Monoid
import Data.HashSet (Set)
import qualified Data.HashSet as S

newtype WrapIO = WrapIO { unwrapIO :: IO () }

instance Monoid WrapIO where
    mempty = WrapIO $ return ()
    WrapIO a `mappend` WrapIO b = WrapIO $ a >> b

type GL a = WriterT (Set String) (Writer WrapIO) a

addTexture :: String -> GL ()
addTexture = tell . S.singleton

addIO :: IO () -> GL ()
addIO = lift . tell . WrapIO

runGL :: GL a -> (a, Set String, IO ())
runGL gl = let iow = runWriterT gl
               ((a, textures), WrapIO io) = runWriter iow
            in (a, textures, io)
森林迷了鹿 2025-01-11 09:36:26

当您需要在不实际运行计算的情况下推断出有关计算的内容时,应用函子往往比 monad 更好,因为它们的效果具有静态结构。

这是因为对于应用函子,排序操作的方法仅限于 (<*>) :: f (a -> b) ->发-> f b,因此第一个参数中的函数无法改变将发生的副作用,这与 (=<<) :: (a -> mb) ->;妈-> m b 其中函数参数可以自由选择任何副作用,因此为了提取有关这些副作用的信息,您必须评估该函数,这又需要上一个操作的结果,依此类推,直到你几乎被迫运行整个事情。

一个快速的应用实现看起来像这样:

data GL a = GL (S.HashSet String) (IO a)

instance Functor GL where
  fmap f (GL s x) = GL s (fmap f x)

instance Applicative GL where
  pure x = GL S.empty (pure x)
  (GL t0 f) <*> (GL t1 x) = GL (t0 `S.union` t1) (f <*> x)

当然,避免单子意味着你失去了一堆控制结构,所以你必须在函子中提供替换原语,例如如果你想允许条件,并确保您正确地组合了来自不同分支的信息。

whenGL :: GL Bool -> GL () -> GL ()
whenGL (GL t0 cond) (GL t1 body) = GL (t0 `S.union` t1) (cond >>= \b -> if b then body else return ())

总而言之,我认为应该可以使用应用程序来完成您想要做的事情,但编程可能有点麻烦。特别是因为您失去了诸如 do-notation 和 Control.Monad 中的各种控制结构之类的东西。

When you need to deduce things about your computations without actually running them, applicative functors tend to work better than monads, since their effects have static structure.

This is because with applicative functors, your method of sequencing actions is limited to (<*>) :: f (a -> b) -> f a -> f b, so the function in the first argument cannot change what side effects will happen, unlike (=<<) :: (a -> m b) -> m a -> m b where the function argument is free to choose any side effect, so in order to extract information about those side effects, you have to evaluate the function, which in turn requires the result of the previous action and so on, until you're pretty much forced to run the whole thing.

A quick applicative implementation would look something like this:

data GL a = GL (S.HashSet String) (IO a)

instance Functor GL where
  fmap f (GL s x) = GL s (fmap f x)

instance Applicative GL where
  pure x = GL S.empty (pure x)
  (GL t0 f) <*> (GL t1 x) = GL (t0 `S.union` t1) (f <*> x)

Of course, avoiding monads means that you lose a bunch of control structures, so you'll have to provide replacement primitives in your functor if for example you want to allow conditionals, and make sure that you combine the information from the different branches correctly.

whenGL :: GL Bool -> GL () -> GL ()
whenGL (GL t0 cond) (GL t1 body) = GL (t0 `S.union` t1) (cond >>= \b -> if b then body else return ())

All in all, I think it should be possible to use applicatives to do what you're trying to do, but it might be somewhat cumbersome to program with. Especially because you lose out on things like do-notation and the various control structures in Control.Monad.

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