Haskell:递归记忆



如果我有以下函数:

go xxs t i
| t == 0         = 1
| t < 0          = 0
| i < 0          = 0
| t < (xxs !! i) = go xxs t (i-1)
| otherwise      = go xxs (t - (xxs !! i)) (i-1) + go xxs t (i-1)

记忆结果的最佳方法是什么?我似乎无法理解如何存储一组动态元组并同时更新和返回值。

相当于我试图在 python 中做的事情是:

def go(xxs, t , i, m):
k = (t,i)
if  k in m:      # check if value for this pair is already in dictionary 
return m[k]
if t == 0:
return 1
elif t < 0:
return 0
elif i < 0:
return 0
elif t < xxs[i]:
val = go(xxs, t, i-1,m)  
else:
val = (go(xxs, total - xxs[i]), i-1,m) + go(xxs, t, i-1,m)
m[k] = val  # store the new value in dictionary before returning it
return val

编辑:我认为这与这个答案有些不同。那里有问题的函数具有线性进展,您可以使用列表[1..]索引结果。在这种情况下,我的密钥(t,i)不一定是按顺序或增量排列的。例如,我最终可能会得到一组键,它们是

[(9,1),(8,2),(7,4),(6,4),(5,5),(4,6),(3,6),(2,7),(1,8),(0,10)]

道没有更简单的方法来滚动自己的[记忆?

比什么容易?状态 monad 真的很容易,如果你习惯于命令式思考,那么它也应该是直观的。

使用向量而不是列表的完整内联版本是:

{-# LANGUAGE MultiWayIf #-}
import Control.Monad.Trans.State as S
import Data.Vector as V
import Data.Map.Strict as M
goGood :: [Int] -> Int -> Int -> Int
goGood xs t0 i0 =
let v = V.fromList xs
in evalState (explicitMemo v t0 i0) mempty
where
explicitMemo :: Vector Int -> Int -> Int -> State (Map (Int,Int) Int) Int
explicitMemo v t i = do
m <- M.lookup (t,i) <$> get
case m of
Nothing ->
do res <- if | t == 0          -> pure 1
| t < 0           -> pure 0
| i < 0           -> pure 0
| t < (v V.! i)   -> explicitMemo v t (i-1)
| otherwise       -> (+) <$> explicitMemo v (t - (v V.! i)) (i-1) <*> explicitMemo v t
(i-1)
S.modify (M.insert (t,i) res)
pure res
Just r  -> pure r

也就是说,如果我们已经计算了结果,我们会在地图上查找。如果是这样,则返回结果。如果没有,请在返回结果之前计算并存储结果。

我们可以通过几个辅助函数来清理很多问题:

prettyMemo :: Vector Int -> Int -> Int -> State (Map (Int,Int) Int) Int
prettyMemo v t i = cachedReturn =<< cachedEval (
if | t == 0          -> pure 1
| t < 0           -> pure 0
| i < 0           -> pure 0
| t < (v V.! i)   -> prettyMemo v t (i-1)
| otherwise       ->
(+) <$> prettyMemo v (t - (v V.! i)) (i-1)
<*> prettyMemo v t (i-1)
)
where
key = (t,i)
-- Lookup value in cache and return it
cachedReturn res = S.modify (M.insert key res) >> pure res
-- Use cached value or run the operation
cachedEval oper = maybe oper pure =<< (M.lookup key <$> get)

现在,我们的地图查找和地图更新是一些简单的(对于经验丰富的Haskell开发人员来说)帮助函数,这些函数包装了整个计算。 这里的一个小区别是,无论计算是否以一些较小的计算成本缓存,我们都会更新地图。

我们可以通过删除monad来使其更加干净(请参阅链接的相关问题)。 有一个流行的软件包(MemoTrie)可以为您处理胆量:

memoTrieVersion :: [Int] -> Int -> Int -> Int
memoTrieVersion xs = go
where
v = V.fromList xs
go t i | t == 0 = 1
| t < 0  = 0
| i < 0  = 0
| t < v V.! i = memo2 go t (i-1)
| otherwise   = memo2 go (t - (v V.! i)) (i-1) + memo2 go t (i-1)

如果您喜欢一元风格,您可以随时使用monad-memo包。

编辑:将Python代码直接转换为Haskell显示了一个重要的区别,即变量的不变性。 在otherwise(或else)的情况下,您使用go两次,并且隐式地一次调用将更新第二次调用使用的缓存(m),从而以记忆方式保存计算。 在Haskell中,如果你避免使用monads和惰性求值来递归定义一个向量(这可能非常强大),那么剩下的最简单的解决方案就是显式传递你的map(字典):

import Data.Vector as V
import Data.Map as M
goWrapped :: Vector Int -> Int -> Int -> Int
goWrapped xxs t i = fst $ goPythonVersion xxs t i mempty
goPythonVersion :: Vector Int -> Int -> Int -> Map (Int,Int) Int -> (Int,Map (Int,Int) Int)
goPythonVersion xxs t i m =
let k = (t,i)
in case M.lookup k m of -- if  k in m:
Just r -> (r,m)       --     return m[k]
Nothing ->
let (res,m') | t == 0 = (1,m)
| t  < 0 = (0,m)
| i  < 0 = (0,m)
| t  < xxs V.! i = goPythonVersion xxs t (i-1) m
| otherwise  =
let (r1,m1) = goPythonVersion xxs (t - (xxs V.! i)) (i-1) m
(r2,m2) = goPythonVersion xxs t (i-1) m1
in (r1 + r2, m2)
in (res, M.insert k res m')

虽然这个版本是Python的一个不错的翻译,但我宁愿看到一个更惯用的解决方案,如下所示。 请注意,我们将一个变量绑定到生成的计算(为 Int 和更新的映射命名为"computed"),但由于惰性计算,除非缓存不产生结果,否则不会完成太多工作。

{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TupleSections #-}
goMoreIdiomatic:: Vector Int -> Int -> Int -> Map (Int,Int) Int -> (Int,Map (Int,Int) Int)
goMoreIdiomatic xxs t i m =
let cached = M.lookup (t,i) m
~(comp, M.insert (t,i) comp -> m')
| t == 0 = (1,m)
| t  < 0 = (0,m)
| i  < 0 = (0,m)
| t  < xxs V.! i = goPythonVersion xxs t (i-1) m
| otherwise  =
let (r1,m1) = goPythonVersion xxs (t - (xxs V.! i)) (i-1) m
(r2,m2) = goPythonVersion xxs t (i-1) m1
in (r1 + r2, m2)
in maybe (comp,m') (,m) cached

最新更新