
Awesome, thanks for the explanation.
On Sun, May 19, 2019 at 2:32 PM William Yager
I realized that there is a simplification which makes the transformation more obvious. I should have put the base case inside the recursive step, rather than special-casing it:
module Main where import Data.Map.Strict as Map import Data.Vector as Vec
-- The recursive step
rec :: (Int -> [[Int]]) -> Int -> [[Int]] rec rec 0 = [[]] rec rec n = do this <- [1..n] other <- rec (n - this) return $ (this : other)
-- Non-dynamic
sumsTo1 :: Int -> [[Int]] sumsTo1 = rec sumsTo1
-- Dynamic (corecursive)
sumsTo2 :: Int -> [[Int]] sumsTo2 n = lookup Map.! n where lookup = go 0 Map.empty go m acc | m > n = acc | otherwise = go (m + 1) (Map.insert m (rec (acc Map.!) m) acc)
-- Dynamic (lazy)
sumsTo3 :: Int -> [[Int]] sumsTo3 n = lookup Vec.! n where lookup = generate (n + 1) $ rec (lookup Vec.!)
main = do let a = sumsTo1 10 b = sumsTo2 10 c = sumsTo3 10 print (a == b && b == c) print a
Also, to expand on this:
* Corecursive DP is good in cases where you can figure out which order to generate things in, especially if you can drop no-longer-relevant data as you go * Lazy DP (using Vector) is good and fast in the case where the data is dense in the (n-dimensional) integers. Also very elegant! * If your DP dependency graph doesn't have any nice properties (not trivially dense in the integers, not easily predictable dependencies), you can implement your algorithm using e.g. a State monad over a map of cached values. However, I think this requires the recursive step to be written in terms of a monad rather than a non-monadic function (so that you can interrupt the control flow of the recursive step).
On Sat, May 18, 2019 at 11:49 PM Magicloud Magiclouds
wrote: Cool. Thanks.
On Sat, May 18, 2019 at 10:18 PM William Yager
wrote: Here are two mechanical strategies for implementing DP in haskell:
module Main where import Data.Map.Strict as Map import Data.Vector as Vec
-- The recursive step
rec :: (Int -> [[Int]]) -> Int -> [[Int]] rec rec n = do this <- [1..n] other <- rec (n - this) return $ (this : other)
-- Non-dynamic
sumsTo1 :: Int -> [[Int]] sumsTo1 0 = [[]] sumsTo1 n = rec sumsTo1 n
-- Dynamic (corecursive)
sumsTo2 :: Int -> [[Int]] sumsTo2 n = lookup Map.! n where lookup = go 1 (Map.singleton 0 [[]]) go m acc | m > n = acc | otherwise = go (m + 1) (Map.insert m (rec (acc Map.!) m) acc)
-- Dynamic (lazy)
sumsTo3 :: Int -> [[Int]] sumsTo3 n = lookup Vec.! n where lookup = generate (n + 1) $ \m -> if m == 0 then [[]] else rec (lookup Vec.!) m
main = do let a = sumsTo1 10 b = sumsTo2 10 c = sumsTo3 10 print (a == b && b == c) print a
In case the formatting is messed up, see https://gist.github.com/wyager/7daebb351d802bbb2a624b71c0f343d3
On Sat, May 18, 2019 at 10:15 PM Magicloud Magiclouds
wrote: Thanks. This is kind like my original (did not get through) thought.
On Sat, May 18, 2019 at 8:25 PM Thorkil Naur
wrote: Hello,
On Sat, May 18, 2019 at 12:33:00PM +0800, Magicloud Magiclouds wrote:
... 1 - 9, nine numbers. Show all the possible combinations that sum up to 10. Different orders are counted as the same.
For example, [1, 4, 5].
With
sumIs n [] = if n == 0 then [[]] else [] sumIs n (x:xs) = (if n < x then [] else map (x:) $ sumIs (n-x) xs ) ++ sumIs n xs
we can do:
Prelude Main> sumIs 10 [1..9] [[1,2,3,4],[1,2,7],[1,3,6],[1,4,5],[1,9],[2,3,5],[2,8],[3,7],[4,6]]
...
Best Thorkil
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.