2

我有一个最好描述为向量上的迭代突变的计算;最终结果是向量的最终状态。

我认为,使这个功能化的“惯用”方法是在“修改”时简单地传递一个新的向量对象。所以你的迭代方法是operate_on_vector :: Vector -> Vector,它接受一个向量并输出修改后的向量,然后再次通过该方法馈送。

这种方法非常简单,即使是 Haskell 的新手,我也可以毫无问题地实现它。

或者,可以将所有这些封装在一个Statemonad 中,并传递一个不断重新创建和修改的向量作为状态值。

然而,我遭受了巨大的性能成本,因为这些计算非常密集,迭代次数很多(大约数百万)并且数据向量可能会变得非常大(至少有数千个基元的数量级)。在迭代的每一步都在内存中重新创建一个新向量似乎非常昂贵,无论是否收集数据。

然后我考虑了它是如何IO工作的——它基本上可以看作是State,除了状态值是“世界”,它是不断变化的。

也许我可以使用类似于IO在“世界”上“操作”的东西?而“世界”将是内存中的向量?有点像数据库查询,但一切都在内存中。

例如用 io 你可以做

do
  putStrLn "enter something"
  something <- getLine
  putStrLine $ "you entered " ++ something

这可以看作是“执行”putStrLn和“修改” World 对象,返回一个新的 World 对象并将其输入到 next 函数中,该函数在 world 对象中查询作为修改结果的字符串,然后返回另一个世界再次修改后的对象。

有没有类似的东西可以为可变向量做到这一点?

do
  putInVec 0 9          -- index 0, value 9
  val <- getFromVec 0
  putInVec 0 (val + 1)

,使用“不纯”“可变”向量,而不是在每一步传递一个新的修改向量。

4

1 回答 1

8

我相信您可以使用可变向量和 Reader + ST(或 IO)monad 上的薄包装器来做到这一点。

它看起来像这样:

type MyVector = IOVector $x  -- Use your own elements type here instead of $x
newtype VectorIO a = VectorIO (ReaderT MyVector IO a) deriving (Monad, MonadReader, MonadIO)
-- You will need GeneralizedNewtypeDeriving extension here

-- Run your computation over an existing vector
runComputation :: MyVector -> VectorIO a -> IO MyVector
runComputation vector (VectorIO action) = runReaderT action vector >> return vector

-- Run your computation over a new vector of the specified length
runNewComputation :: Int -> VectorIO a -> IO MyVector
runNewComputation n action = do
  vector <- new n
  runComputation vector action

putInVec :: Int -> $x -> VectorIO ()
putInVec idx val = do
  v <- ask
  liftIO $ write v idx val

getFromVec :: Int -> VectorIO $x
getFromVec idx = do
  v <- ask
  liftIO $ read v idx

仅此而已。您可以使用VectorIOmonad 来执行计算,就像您在示例中想要的那样。如果你不想要 IO 但想要纯计算,你可以使用STmonad;对上面代码的修改将是微不足道的。

更新

这是一个基于 ST 的版本:

{-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances, MultiParamTypeClasses, Rank2Types #-}
module Main where

import Control.Monad
import Control.Monad.Trans.Class
import Control.Monad.Reader
import Control.Monad.Reader.Class
import Control.Monad.ST
import Data.Vector as V
import Data.Vector.Mutable as MV

-- Your type of the elements
type E = Int

-- Mutable vector which will be used as a context
type MyVector s = MV.STVector s E

-- Immutable vector compatible with MyVector in its type
type MyPureVector = V.Vector E

-- Simple monad stack consisting of a reader with the mutable vector as a context 
-- and of an ST action
newtype VectorST s a = VectorST (ReaderT (MyVector s) (ST s) a) deriving Monad

-- Make the VectorST a reader monad
instance MonadReader (MyVector s) (VectorST s) where
    ask = VectorST $ ask
    local f (VectorST a) = VectorST $ local f a
    reader = VectorST . reader

-- Lift an ST action to a VectorST action
liftST :: ST s a -> VectorST s a
liftST = VectorST . lift

-- Run your computation over an existing vector
runComputation :: MyVector s -> VectorST s a -> ST s (MyVector s)
runComputation vector (VectorST action) = runReaderT action vector >> return vector

-- Run your computation over a new vector of the specified length
runNewComputation :: Int -> VectorST s a -> ST s (MyVector s)
runNewComputation n action = do
  vector <- MV.new n
  runComputation vector action

-- Run a computation on a new mutable vector and then freeze it to an immutable one
runComputationPure :: Int -> (forall s. VectorST s a) -> MyPureVector
runComputationPure n action = runST $ do
  vector <- runNewComputation n action
  V.unsafeFreeze vector

-- Put an element into the current vector
putInVec :: Int -> E -> VectorST s ()
putInVec idx val = do
  v <- ask
  liftST $ MV.write v idx val

-- Retrieve an element from the current vector
getFromVec :: Int -> VectorST s E
getFromVec idx = do
  v <- ask
  liftST $ MV.read v idx
于 2013-06-22T08:03:33.627 回答