[Haskell-cafe] List all multiply/add combinations
Artyom Kazak
artyom.kazak at gmail.com
Sat Nov 17 21:47:30 CET 2012
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
More information about the Haskell-Cafe
mailing list