<div dir="ltr"><div dir="ltr">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:<div><br></div><div><div><font face="courier new, monospace">module Main where</font></div><div><font face="courier new, monospace">import Data.Map.Strict as Map</font></div><div><font face="courier new, monospace">import Data.Vector as Vec</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">-- The recursive step</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">rec :: (Int -> [[Int]]) -> Int -> [[Int]]</font></div><div><font face="courier new, monospace">rec rec 0 = [[]]</font></div><div><font face="courier new, monospace">rec rec n = do</font></div><div><font face="courier new, monospace">    this <- [1..n]</font></div><div><font face="courier new, monospace">    other <- rec (n - this)</font></div><div><font face="courier new, monospace">    return $ (this : other)</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">-- Non-dynamic</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">sumsTo1 :: Int -> [[Int]]</font></div><div><font face="courier new, monospace">sumsTo1 = rec sumsTo1</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">-- Dynamic (corecursive)</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">sumsTo2 :: Int -> [[Int]]</font></div><div><font face="courier new, monospace">sumsTo2 n = lookup Map.! n</font></div><div><font face="courier new, monospace">    where</font></div><div><font face="courier new, monospace">    lookup = go 0 Map.empty</font></div><div><font face="courier new, monospace">    go m acc | m > n = acc</font></div><div><font face="courier new, monospace">             | otherwise = go (m + 1) (Map.insert m (rec (acc Map.!) m) acc)</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">-- Dynamic (lazy)</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">sumsTo3 :: Int -> [[Int]]</font></div><div><font face="courier new, monospace">sumsTo3 n = lookup Vec.! n</font></div><div><font face="courier new, monospace">    where</font></div><div><font face="courier new, monospace">    lookup = generate (n + 1) $ rec (lookup Vec.!)</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">main = do</font></div><div><font face="courier new, monospace">    let a = sumsTo1 10</font></div><div><font face="courier new, monospace">        b = sumsTo2 10</font></div><div><font face="courier new, monospace">        c = sumsTo3 10</font></div><div><font face="courier new, monospace">    print (a == b && b == c)</font></div><div><font face="courier new, monospace">    print a</font></div></div><div><br></div><div>Also, to expand on this:</div><div><br></div><div>* 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</div><div>* Lazy DP (using Vector) is good and fast in the case where the data is dense in the (n-dimensional) integers. Also very elegant!</div><div>* 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).</div><div><br></div></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Sat, May 18, 2019 at 11:49 PM Magicloud Magiclouds <<a href="mailto:magicloud.magiclouds@gmail.com">magicloud.magiclouds@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;border-left-color:rgb(204,204,204);padding-left:1ex">Cool. Thanks.<br>
<br>
On Sat, May 18, 2019 at 10:18 PM William Yager <<a href="mailto:will.yager@gmail.com" target="_blank">will.yager@gmail.com</a>> wrote:<br>
><br>
> Here are two mechanical strategies for implementing DP in haskell:<br>
><br>
> module Main where<br>
> import Data.Map.Strict as Map<br>
> import Data.Vector as Vec<br>
><br>
><br>
> -- The recursive step<br>
><br>
> rec :: (Int -> [[Int]]) -> Int -> [[Int]]<br>
> rec rec n = do<br>
>     this <- [1..n]<br>
>     other <- rec (n - this)<br>
>     return $ (this : other)<br>
><br>
> -- Non-dynamic<br>
><br>
> sumsTo1 :: Int -> [[Int]]<br>
> sumsTo1 0 = [[]]<br>
> sumsTo1 n = rec sumsTo1 n<br>
><br>
> -- Dynamic (corecursive)<br>
><br>
> sumsTo2 :: Int -> [[Int]]<br>
> sumsTo2 n = lookup Map.! n<br>
>     where<br>
>     lookup = go 1 (Map.singleton 0 [[]])<br>
>     go m acc | m > n = acc<br>
>              | otherwise = go (m + 1) (Map.insert m (rec (acc Map.!) m) acc)<br>
><br>
> -- Dynamic (lazy)<br>
><br>
> sumsTo3 :: Int -> [[Int]]<br>
> sumsTo3 n = lookup Vec.! n<br>
>     where<br>
>     lookup = generate (n + 1) $ \m -><br>
>         if m == 0<br>
>         then [[]]<br>
>         else rec (lookup Vec.!) m<br>
><br>
> main = do<br>
>     let a = sumsTo1 10<br>
>         b = sumsTo2 10<br>
>         c = sumsTo3 10<br>
>     print (a == b && b == c)<br>
>     print a<br>
><br>
> In case the formatting is messed up, see<br>
> <a href="https://gist.github.com/wyager/7daebb351d802bbb2a624b71c0f343d3" rel="noreferrer" target="_blank">https://gist.github.com/wyager/7daebb351d802bbb2a624b71c0f343d3</a><br>
><br>
> On Sat, May 18, 2019 at 10:15 PM Magicloud Magiclouds <<a href="mailto:magicloud.magiclouds@gmail.com" target="_blank">magicloud.magiclouds@gmail.com</a>> wrote:<br>
>><br>
>> Thanks. This is kind like my original (did not get through) thought.<br>
>><br>
>> On Sat, May 18, 2019 at 8:25 PM Thorkil Naur <<a href="mailto:naur@post11.tele.dk" target="_blank">naur@post11.tele.dk</a>> wrote:<br>
>> ><br>
>> > Hello,<br>
>> ><br>
>> > On Sat, May 18, 2019 at 12:33:00PM +0800, Magicloud Magiclouds wrote:<br>
>> > > ...<br>
>> > > 1 - 9, nine numbers. Show all the possible combinations that sum up to<br>
>> > > 10. Different orders are counted as the same.<br>
>> > ><br>
>> > > For example, [1, 4, 5].<br>
>> ><br>
>> > With<br>
>> ><br>
>> >   sumIs n [] = if n == 0 then [[]] else []<br>
>> >   sumIs n (x:xs)<br>
>> >     = (if n < x then<br>
>> >         []<br>
>> >       else<br>
>> >         map (x:) $ sumIs (n-x) xs<br>
>> >       )<br>
>> >       ++ sumIs n xs<br>
>> ><br>
>> > we can do:<br>
>> ><br>
>> > Prelude Main> sumIs 10 [1..9]<br>
>> > [[1,2,3,4],[1,2,7],[1,3,6],[1,4,5],[1,9],[2,3,5],[2,8],[3,7],[4,6]]<br>
>> ><br>
>> > > ...<br>
>> ><br>
>> > Best<br>
>> > Thorkil<br>
>> _______________________________________________<br>
>> Haskell-Cafe mailing list<br>
>> To (un)subscribe, modify options or view archives go to:<br>
>> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
>> Only members subscribed via the mailman list are allowed to post.<br>
</blockquote></div>