List all multiply/add combinations

Given a list of numbers of fixed length I need to list all possible values (and the associated computation) you get by inserting +,-,*,/ between the numbers, and also set parentheses where you please. It shouldn't list computations with unnecessary parentheses. Example list of length 3 [a,b,c] and only with + and *: a*b+c, a*(b+c),a*b*c,a+b*c,(a+b)*c,a+b+c What would be a good way to do this, and a good representation in Haskell? Best, Rune

This smells like homework to me,
which isn't a bad thing,
it will however change the way I answer you.
Please look at http://hackage.haskell.org/packages/archive/base/latest/doc/
html/Data-List.html#v:permutations
and show us your attempts to use this function.
Timothy
---------- Původní zpráva ----------
Od: Rune Harder Bak

It might be rare that a "real world" problem can be formulated as such
a simple mathematical challenge,
so I can't blame you for thinking about home work. I did too.
Actually it's part of a logic puzzle I'm implementing.
Attacking the problem textually, I can treat the list of infix
operators as char, and
insert parentheses in all possible configurations. Then remove the
illegal and unnecessary one.
To get the result, I then need to parse the string.
That seems slow, and awkward.
I need to do hundreds of thousands of these calculations.
I could then work directly with parsing trees, and generate all binary
trees of fixed lengths.
But most of them would be unnecessary, so it seems like I'm attacking
it from the wrong angle.
I get that using permutations you can get rid of the need for
parentheses, but you also get a lot of
impossible calculations (like a*c+b in the example before). It's also
not straight forward to go back to the
original representation with parentheses. But maybe I'm missing
something obvious here?
On Sat, Nov 17, 2012 at 4:18 PM,
This smells like homework to me, which isn't a bad thing, it will however change the way I answer you.
Please look at http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-List.h... and show us your attempts to use this function.
Timothy
---------- Původní zpráva ---------- Od: Rune Harder Bak
Datum: 17. 11. 2012 Předmět: [Haskell-cafe] List all multiply/add combinations Given a list of numbers of fixed length I need to list all possible values (and the associated computation) you get by inserting +,-,*,/ between the numbers, and also set parentheses where you please. It shouldn't list computations with unnecessary parentheses. Example list of length 3 [a,b,c] and only with + and *: a*b+c, a*(b+c),a*b*c,a+b*c,(a+b)*c,a+b+c
What would be a good way to do this, and a good representation in Haskell?
Best, Rune
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Instead of attacking the problem textually, try to create a datatype which would describe your expressions, then generate all values of this datatype, filter those you don’t need, and convert the rest into Strings. Currently your expressions are represented by “String” — conversion is very cheap, but filtering is “hard” (since it boils down to parsing). Binary trees would suit you better.

Sorry! I replied without reading your message properly.
I could then work directly with parsing trees, and generate all binary trees of fixed lengths. But most of them would be unnecessary, so it seems like I'm attacking it from the wrong angle.
They won’t be unnecessary if you generate them in a right way. I will think about it and reply with a detailed answer as soon as possible.

The following algorithm generates all possible expressions and throws away most of unnecessary duplicates.
import qualified Data.Map as M
data Expr = Num Int | Add Expr Expr | Sub Expr Expr | Mul Expr Expr | Div Expr Expr
Rendering function is highly imperfect. Either write one yourself, or change the definition of Expr to something like “Num Int | App Op [Expr]” — this way rendering would become much easier.
render :: Expr -> String render (Num n) = show n render (Add a b) = "(" ++ render a ++ "+" ++ render b ++ ")" render (Sub a b) = "(" ++ render a ++ "-" ++ render b ++ ")" render (Mul a b) = "(" ++ render a ++ "*" ++ render b ++ ")" render (Div a b) = "(" ++ render a ++ "/" ++ render b ++ ")"
Let’s assume that we have lN numbers.
nums = [1, 2, 3] lN = length nums
Our goal is to build table of all possible expressions, which can be build using numbers from i-th to j-th, where i, j are in range from 0 to lN-1. We have to fill the table in the following order: numbers themselves, expressions consisting of two numbers, three, four, … N.
table :: M.Map (Int, Int) [Expr] table = M.fromList $ [((i, i), [Num n] ) | (i, n) <- zip [0..lN-1] nums] ++ [((i, j), calc i j) | i <- [0..lN-1], j <- [i+1,i+2..lN-1]]
answer = table M.! (0, lN-1)
Our next goal is a function which fills this table:
calc :: Int -> Int -> [Expr] calc i j = do --elements from i to k will form one branch, k+1 to j — another k <- [i,i+1..j-1] le <- table M.! (i, k) re <- table M.! (k+1, j)
We don’t want to generate both (a+b)+c and a+(b+c), or (a+b)-c and a+(b-c), or (a-b)-c and a-(b+c), or (a-b)+c and a-(b-c), so we’re eliminating the second variant in each pair. Multiplication and division follow the same pattern.
case re of Add _ _ -> [Mul le re, Div le re] Sub _ _ -> [Mul le re, Div le re] Mul _ _ -> [Add le re, Sub le re] Div _ _ -> [Add le re, Sub le re] otherwise -> [Add le re, Sub le re, Mul le re, Div le re]
Here are generated expressions: 1*(2+3) 1/(2+3) 1*(2-3) 1/(2-3) 1+(2*3) 1-(2*3) 1+(2/3) 1-(2/3) (1+2)+3 (1+2)-3 (1+2)*3 (1+2)/3 (1-2)+3 (1-2)-3 (1-2)*3 (1-2)/3 (1*2)+3 (1*2)-3 (1*2)*3 (1*2)/3 (1/2)+3 (1/2)-3 (1/2)*3 (1/2)/3
participants (3)
-
Artyom Kazak
-
Rune Harder Bak
-
timothyhobbs@seznam.cz