How to dynamic plan in Haskell?

Hi, I solved the question. But I could not figure out a FP style solution. Question: 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].

Hello, On Sat, May 18, 2019 at 12:33:00PM +0800, Magicloud Magiclouds wrote:
I solved the question. But I could not figure out a FP style solution.
Question:
1 - 9, nine numbers. Show all the possible combinations that sum up to 10. Different orders are counted as the same.
A possible solution takes advantage of powersets with the [] Monad. λ> :m +Control.Monad λ> f cs = filterM (\x -> [True, False]) cs λ> filter ((==10) . sum) (f [1..10])

I see. Did not got the filterM part in mind. Thanks.
On Sat, May 18, 2019 at 1:48 PM Francesco Ariis
Hello,
On Sat, May 18, 2019 at 12:33:00PM +0800, Magicloud Magiclouds wrote:
I solved the question. But I could not figure out a FP style solution.
Question:
1 - 9, nine numbers. Show all the possible combinations that sum up to 10. Different orders are counted as the same.
A possible solution takes advantage of powersets with the [] Monad.
λ> :m +Control.Monad λ> f cs = filterM (\x -> [True, False]) cs λ> filter ((==10) . sum) (f [1..10])
_______________________________________________ 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.

This is also an interesting solution: sums :: [[Integer]] sums = do x <- [1..9] go x [x] (10 - x) where go x xs r | r > 0 = do x <- [1..min x r] go x (x:xs) (r - x) | otherwise = return xs On 05/18/2019 02:00 AM, Magicloud Magiclouds wrote:
I see. Did not got the filterM part in mind. Thanks.
On Sat, May 18, 2019 at 1:48 PM Francesco Ariis
wrote: Hello,
On Sat, May 18, 2019 at 12:33:00PM +0800, Magicloud Magiclouds wrote:
I solved the question. But I could not figure out a FP style solution.
Question:
1 - 9, nine numbers. Show all the possible combinations that sum up to 10. Different orders are counted as the same. A possible solution takes advantage of powersets with the [] Monad.
λ> :m +Control.Monad λ> f cs = filterM (\x -> [True, False]) cs λ> filter ((==10) . sum) (f [1..10])
_______________________________________________ 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.
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.

Ah, I did not make it clear. Once for each number.
On Sat, May 18, 2019 at 2:11 PM David Kraeutmann
This is also an interesting solution:
sums :: [[Integer]] sums = do x <- [1..9] go x [x] (10 - x)
where go x xs r | r > 0 = do x <- [1..min x r] go x (x:xs) (r - x)
| otherwise = return xs
On 05/18/2019 02:00 AM, Magicloud Magiclouds wrote:
I see. Did not got the filterM part in mind. Thanks.
On Sat, May 18, 2019 at 1:48 PM Francesco Ariis
wrote: Hello,
On Sat, May 18, 2019 at 12:33:00PM +0800, Magicloud Magiclouds wrote:
I solved the question. But I could not figure out a FP style solution.
Question:
1 - 9, nine numbers. Show all the possible combinations that sum up to 10. Different orders are counted as the same. A possible solution takes advantage of powersets with the [] Monad.
λ> :m +Control.Monad λ> f cs = filterM (\x -> [True, False]) cs λ> filter ((==10) . sum) (f [1..10])
_______________________________________________ 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.
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.
_______________________________________________ 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.

As an aside: I feel certain I saw a beautiful solution presented as
lecture notes and referencing a game show (around 2007). Maybe it was
in Hudak's book?
Perhaps I missed something, but the answer's I've seen posted thus far
are not dynamic programming. Certainly in the powerset case you'll
experience exponential costs. Benchmarks are good - try to solve with
numbers [1..64] in low numbers of seconds.
An explicit 98-ish solution is to have a generator that will refer to
the prior indexes in the list when computing the current index.
First the boiler plate:
```
{-# LANGUAGE OverloadedLists #-}
module Main where
import qualified Data.Set as Set
import Control.Monad (guard)
type Solution = Set.Set Int
-- A list of all sets of numbers, no duplicates and ignoring order,
-- that sum to the value @index + 1@.
answer :: [[Solution]]
answer = fmap op [1..10]
where
```
Now for the interesting part. The recursive definition of a solution
for value `target` is `[target]` and the solutions for `x` added with
the solution for `target - x` where `x <- [0..target/2]. Some care
must be taken because solutions will overlap.
With that in mind:
```
-- Generate the entry for value @target@ (list index @target - 1@)
op :: Int -> [Solution]
op target =
([target] :: Solution) -- The target itself is an answer
: snub -- Ignore duplicate results
-- Better idea: don't
generate dups if you can...
(do let half = target `div` 2
halfRDown = (target-1) `div` 2
(ls,hs) <- zip (slice 0 half answer) -- Pair 0 .. t/2
-- with t-1, t-2 .. t/2+1
(reverse $ slice half halfRDown answer)
l <- ls -- For each solution to the lower number
h <- hs -- and the matching solution to the larger number
guard (Set.intersection l h == []) -- No repeat values! (?)
pure (l <> h) -- target = l + h
)
-- | List slice from a base and of given length
slice :: Int -> Int -> [a] -> [a]
slice base len = take len . drop base
-- | Efficient combined sort and nub
snub :: (Eq a, Ord a) => [a] -> [a]
snub = Set.toList . Set.fromList
main :: IO ()
main = print answers
```
-Thomas
On Fri, May 17, 2019 at 9:35 PM Magicloud Magiclouds
Hi,
I solved the question. But I could not figure out a FP style solution.
Question:
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]. _______________________________________________ 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.

Thanks. Just to make it clear, the code is for generating candidates,
not the answer, right? From first glance, the code shows a lot
solutions that do not sum to 10. Have not check if it contains all
answers.
On Sat, May 18, 2019 at 3:03 PM Thomas DuBuisson
As an aside: I feel certain I saw a beautiful solution presented as lecture notes and referencing a game show (around 2007). Maybe it was in Hudak's book?
Perhaps I missed something, but the answer's I've seen posted thus far are not dynamic programming. Certainly in the powerset case you'll experience exponential costs. Benchmarks are good - try to solve with numbers [1..64] in low numbers of seconds.
An explicit 98-ish solution is to have a generator that will refer to the prior indexes in the list when computing the current index.
First the boiler plate:
``` {-# LANGUAGE OverloadedLists #-} module Main where
import qualified Data.Set as Set import Control.Monad (guard)
type Solution = Set.Set Int
-- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@. answer :: [[Solution]] answer = fmap op [1..10] where ```
Now for the interesting part. The recursive definition of a solution for value `target` is `[target]` and the solutions for `x` added with the solution for `target - x` where `x <- [0..target/2]. Some care must be taken because solutions will overlap.
With that in mind:
``` -- Generate the entry for value @target@ (list index @target - 1@) op :: Int -> [Solution] op target = ([target] :: Solution) -- The target itself is an answer : snub -- Ignore duplicate results -- Better idea: don't generate dups if you can... (do let half = target `div` 2 halfRDown = (target-1) `div` 2 (ls,hs) <- zip (slice 0 half answer) -- Pair 0 .. t/2 -- with t-1, t-2 .. t/2+1 (reverse $ slice half halfRDown answer) l <- ls -- For each solution to the lower number h <- hs -- and the matching solution to the larger number guard (Set.intersection l h == []) -- No repeat values! (?) pure (l <> h) -- target = l + h )
-- | List slice from a base and of given length slice :: Int -> Int -> [a] -> [a] slice base len = take len . drop base
-- | Efficient combined sort and nub snub :: (Eq a, Ord a) => [a] -> [a] snub = Set.toList . Set.fromList
main :: IO () main = print answers ```
-Thomas
On Fri, May 17, 2019 at 9:35 PM Magicloud Magiclouds
wrote: Hi,
I solved the question. But I could not figure out a FP style solution.
Question:
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]. _______________________________________________ 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.

On Sat, May 18, 2019 at 2:56 AM Magicloud Magiclouds
Thanks. Just to make it clear, the code is for generating candidates, not the answer, right? From first glance, the code shows a lot solutions that do not sum to 10. Have not check if it contains all answers.
They were the right answers for each index. N.B. the comment -- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@. I'm glad to hear you only want the answer for 10 and the DP aspect isn't supposed to re-use sum sets for values 1..9 to construct sums for 10 (which is what I did, it was ugly and slow). In that case you can use Ariis's awesome solution with very minor modification: ``` import Data.List main = print answer type Solution = [Integer] answer = sums 10 sums :: Integer -> [Solution] sums n = do x <- [1..n] -- Pick a largest number in the same go x [x] (n - x) -- recursively pass the smallest value, the current solution, and remainder where go x xs r | r > 0 && x == 1 = fail "" -- If there is a remainder and we've already used 1 this isn't a soluton | r > 0 = do x <- [1..min (x-1) r] -- The next value must be between 1 and the min of remainder and one-less than the last pick go x (x:xs) (r - x) | otherwise = return xs ``` -Thomas
On Sat, May 18, 2019 at 3:03 PM Thomas DuBuisson
wrote: As an aside: I feel certain I saw a beautiful solution presented as lecture notes and referencing a game show (around 2007). Maybe it was in Hudak's book?
Perhaps I missed something, but the answer's I've seen posted thus far are not dynamic programming. Certainly in the powerset case you'll experience exponential costs. Benchmarks are good - try to solve with numbers [1..64] in low numbers of seconds.
An explicit 98-ish solution is to have a generator that will refer to the prior indexes in the list when computing the current index.
First the boiler plate:
``` {-# LANGUAGE OverloadedLists #-} module Main where
import qualified Data.Set as Set import Control.Monad (guard)
type Solution = Set.Set Int
-- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@. answer :: [[Solution]] answer = fmap op [1..10] where ```
Now for the interesting part. The recursive definition of a solution for value `target` is `[target]` and the solutions for `x` added with the solution for `target - x` where `x <- [0..target/2]. Some care must be taken because solutions will overlap.
With that in mind:
``` -- Generate the entry for value @target@ (list index @target - 1@) op :: Int -> [Solution] op target = ([target] :: Solution) -- The target itself is an answer : snub -- Ignore duplicate results -- Better idea: don't generate dups if you can... (do let half = target `div` 2 halfRDown = (target-1) `div` 2 (ls,hs) <- zip (slice 0 half answer) -- Pair 0 .. t/2 -- with t-1, t-2 .. t/2+1 (reverse $ slice half halfRDown answer) l <- ls -- For each solution to the lower number h <- hs -- and the matching solution to the larger number guard (Set.intersection l h == []) -- No repeat values! (?) pure (l <> h) -- target = l + h )
-- | List slice from a base and of given length slice :: Int -> Int -> [a] -> [a] slice base len = take len . drop base
-- | Efficient combined sort and nub snub :: (Eq a, Ord a) => [a] -> [a] snub = Set.toList . Set.fromList
main :: IO () main = print answers ```
-Thomas
On Fri, May 17, 2019 at 9:35 PM Magicloud Magiclouds
wrote: Hi,
I solved the question. But I could not figure out a FP style solution.
Question:
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]. _______________________________________________ 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.

That prior mail built on code from Kraeutmann, sorry for the mis-attribution.
On Sat, May 18, 2019 at 8:34 AM Thomas DuBuisson
On Sat, May 18, 2019 at 2:56 AM Magicloud Magiclouds
wrote: Thanks. Just to make it clear, the code is for generating candidates, not the answer, right? From first glance, the code shows a lot solutions that do not sum to 10. Have not check if it contains all answers.
They were the right answers for each index. N.B. the comment -- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@.
I'm glad to hear you only want the answer for 10 and the DP aspect isn't supposed to re-use sum sets for values 1..9 to construct sums for 10 (which is what I did, it was ugly and slow). In that case you can use Ariis's awesome solution with very minor modification:
``` import Data.List
main = print answer
type Solution = [Integer]
answer = sums 10
sums :: Integer -> [Solution] sums n = do x <- [1..n] -- Pick a largest number in the same go x [x] (n - x) -- recursively pass the smallest value, the current solution, and remainder where go x xs r | r > 0 && x == 1 = fail "" -- If there is a remainder and we've already used 1 this isn't a soluton | r > 0 = do x <- [1..min (x-1) r] -- The next value must be between 1 and the min of remainder and one-less than the last pick go x (x:xs) (r - x) | otherwise = return xs ```
-Thomas
On Sat, May 18, 2019 at 3:03 PM Thomas DuBuisson
wrote: As an aside: I feel certain I saw a beautiful solution presented as lecture notes and referencing a game show (around 2007). Maybe it was in Hudak's book?
Perhaps I missed something, but the answer's I've seen posted thus far are not dynamic programming. Certainly in the powerset case you'll experience exponential costs. Benchmarks are good - try to solve with numbers [1..64] in low numbers of seconds.
An explicit 98-ish solution is to have a generator that will refer to the prior indexes in the list when computing the current index.
First the boiler plate:
``` {-# LANGUAGE OverloadedLists #-} module Main where
import qualified Data.Set as Set import Control.Monad (guard)
type Solution = Set.Set Int
-- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@. answer :: [[Solution]] answer = fmap op [1..10] where ```
Now for the interesting part. The recursive definition of a solution for value `target` is `[target]` and the solutions for `x` added with the solution for `target - x` where `x <- [0..target/2]. Some care must be taken because solutions will overlap.
With that in mind:
``` -- Generate the entry for value @target@ (list index @target - 1@) op :: Int -> [Solution] op target = ([target] :: Solution) -- The target itself is an answer : snub -- Ignore duplicate results -- Better idea: don't generate dups if you can... (do let half = target `div` 2 halfRDown = (target-1) `div` 2 (ls,hs) <- zip (slice 0 half answer) -- Pair 0 .. t/2 -- with t-1, t-2 .. t/2+1 (reverse $ slice half halfRDown answer) l <- ls -- For each solution to the lower number h <- hs -- and the matching solution to the larger number guard (Set.intersection l h == []) -- No repeat values! (?) pure (l <> h) -- target = l + h )
-- | List slice from a base and of given length slice :: Int -> Int -> [a] -> [a] slice base len = take len . drop base
-- | Efficient combined sort and nub snub :: (Eq a, Ord a) => [a] -> [a] snub = Set.toList . Set.fromList
main :: IO () main = print answers ```
-Thomas
On Fri, May 17, 2019 at 9:35 PM Magicloud Magiclouds
wrote: Hi,
I solved the question. But I could not figure out a FP style solution.
Question:
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]. _______________________________________________ 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.

Ah, I see. Sorry did not make myself clear.
On Sat, May 18, 2019 at 11:34 PM Thomas DuBuisson
On Sat, May 18, 2019 at 2:56 AM Magicloud Magiclouds
wrote: Thanks. Just to make it clear, the code is for generating candidates, not the answer, right? From first glance, the code shows a lot solutions that do not sum to 10. Have not check if it contains all answers.
They were the right answers for each index. N.B. the comment -- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@.
I'm glad to hear you only want the answer for 10 and the DP aspect isn't supposed to re-use sum sets for values 1..9 to construct sums for 10 (which is what I did, it was ugly and slow). In that case you can use Ariis's awesome solution with very minor modification:
``` import Data.List
main = print answer
type Solution = [Integer]
answer = sums 10
sums :: Integer -> [Solution] sums n = do x <- [1..n] -- Pick a largest number in the same go x [x] (n - x) -- recursively pass the smallest value, the current solution, and remainder where go x xs r | r > 0 && x == 1 = fail "" -- If there is a remainder and we've already used 1 this isn't a soluton | r > 0 = do x <- [1..min (x-1) r] -- The next value must be between 1 and the min of remainder and one-less than the last pick go x (x:xs) (r - x) | otherwise = return xs ```
-Thomas
On Sat, May 18, 2019 at 3:03 PM Thomas DuBuisson
wrote: As an aside: I feel certain I saw a beautiful solution presented as lecture notes and referencing a game show (around 2007). Maybe it was in Hudak's book?
Perhaps I missed something, but the answer's I've seen posted thus far are not dynamic programming. Certainly in the powerset case you'll experience exponential costs. Benchmarks are good - try to solve with numbers [1..64] in low numbers of seconds.
An explicit 98-ish solution is to have a generator that will refer to the prior indexes in the list when computing the current index.
First the boiler plate:
``` {-# LANGUAGE OverloadedLists #-} module Main where
import qualified Data.Set as Set import Control.Monad (guard)
type Solution = Set.Set Int
-- A list of all sets of numbers, no duplicates and ignoring order, -- that sum to the value @index + 1@. answer :: [[Solution]] answer = fmap op [1..10] where ```
Now for the interesting part. The recursive definition of a solution for value `target` is `[target]` and the solutions for `x` added with the solution for `target - x` where `x <- [0..target/2]. Some care must be taken because solutions will overlap.
With that in mind:
``` -- Generate the entry for value @target@ (list index @target - 1@) op :: Int -> [Solution] op target = ([target] :: Solution) -- The target itself is an answer : snub -- Ignore duplicate results -- Better idea: don't generate dups if you can... (do let half = target `div` 2 halfRDown = (target-1) `div` 2 (ls,hs) <- zip (slice 0 half answer) -- Pair 0 .. t/2 -- with t-1, t-2 .. t/2+1 (reverse $ slice half halfRDown answer) l <- ls -- For each solution to the lower number h <- hs -- and the matching solution to the larger number guard (Set.intersection l h == []) -- No repeat values! (?) pure (l <> h) -- target = l + h )
-- | List slice from a base and of given length slice :: Int -> Int -> [a] -> [a] slice base len = take len . drop base
-- | Efficient combined sort and nub snub :: (Eq a, Ord a) => [a] -> [a] snub = Set.toList . Set.fromList
main :: IO () main = print answers ```
-Thomas
On Fri, May 17, 2019 at 9:35 PM Magicloud Magiclouds
wrote: Hi,
I solved the question. But I could not figure out a FP style solution.
Question:
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]. _______________________________________________ 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.

On 2019-05-18 3:03 a.m., Thomas DuBuisson wrote:
As an aside: I feel certain I saw a beautiful solution presented as lecture notes and referencing a game show (around 2007). Maybe it was in Hudak's book?
Perhaps Hutton's book, chapter 9 "the countdown problem". (The game show is Countdown.) "Given a sequence of numbers and a target number, attempt to construct an expression whose value is the target, by combining one or more numbers from the sequence using addition, subtraction, multiplication, division and parentheses."

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

Thanks. This is kind like my original (did not get through) thought.
On Sat, May 18, 2019 at 8:25 PM Thorkil Naur
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

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 < magicloud.magiclouds@gmail.com> 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.

Cool. Thanks.
On Sat, May 18, 2019 at 10:18 PM William Yager
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.

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 < magicloud.magiclouds@gmail.com> 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 <
magicloud.magiclouds@gmail.com> 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.

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.
participants (7)
-
Albert Y. C. Lai
-
David Kraeutmann
-
Francesco Ariis
-
Magicloud Magiclouds
-
Thomas DuBuisson
-
Thorkil Naur
-
William Yager