Re: [Haskell-cafe] List all multiply/add combinations

On Sun, Nov 18, 2012 at 2:04 PM, Stefan Klinger
Sounds like you would want to enumerate all possible *abstract* syntax trees, these implicitly have exactly the necessary parentheses. I'd do this recursively, splitting the sequence of numbers in two at all possible places, and then combine the corresponding results with all possible operators.
That was my second idea, but just doing it naively resulted in many
equivalent calculations,
so I thought there might be a better way to view the problem.
But as Artyom showed
On Sat, Nov 17, 2012 at 11:37 PM, Artyom Kazak
Indentation messed up… I have pasted the code here: http://hpaste.org/77864
enumerating the abstract syntax tree is actually (or at least could be) the way to go! Thanks a lot! What I need is a little bit different, but now I feel I'm on the right track! This is my first question to the café and it makes me a lot more certain using Haskell for production, when you can get this kind of quick and thorough help when in doubt. Great community! -Rune

Hi,
You can make a datatype that captures exactly the expressions you want (see
code below). Essentially you want to make sure that a subtraction or
addition never has another subtraction or addition as its left operand.
I would also like to advertise a bit and show how this type can be
enumerated automatically by Feat (
http://hackage.haskell.org/package/testing-feat).
Main> nvars 3
(24,[X/X-X,X*X-X,X/X+X,X*X+X,X-X-X,X-X+X,X-X/X,X-X*X,X+X-X,X+X+X,X+X/X,X+X*X,(X-X)/X,(X+X)/X,(X-X)*X,(X+X)*X,X/(X-X),X/(X+X),X/X/X,X/X*X,X*(X-X),X*(X+X),X*X/X,X*X*X])
(Obviously the Xs need to be replaced by proper variables, I can explain
how that's done if anyone wants to know)
24 is the number of values in the list, you can do fst $ nvars 100 to find
out that there are
317334467851069836531554283592442220021116
711774843850938552230690568780568787114173
2912210230558851072
values with 100 variables. You can even select any one of those values by
index or randomly select values with uniform distribution and use it with
QuickCheck (for instance to test that my experiments with showsPrec hasn't
messed everything up).
Pasted code: http://hpaste.org/77898
{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-}
import Test.Feat
import Data.Typeable
-- | Any expression
data AnyExpr = AnyAddSub AddSub
| AnyMulDiv MulDiv
| AnyVar
deriving Typeable
-- | Expressions with a top level addition or subtraction
data MulDiv = MDOp Bool AddSub AnyExpr -- Left operand is add. or sub.
| MDOpVar Bool AnyExpr -- Left operand is a variable
deriving Typeable
-- | Expressions with a top level multiplication or division
data AddSub = ASOp Bool MulDiv AnyExpr -- Left operand is mult. or div.
| ASOpVar Bool AnyExpr -- Left operand is a variable
deriving Typeable
deriveEnumerable ''AnyExpr
deriveEnumerable ''AddSub
deriveEnumerable ''MulDiv
allExpressions = values :: [(Integer,[AnyExpr])]
nvars n = allExpressions !! ((n-1)*3+1)
instance Show AnyExpr where
showsPrec d (AnyAddSub e) = showsPrec d e
showsPrec d (AnyMulDiv e) = showsPrec d e
showsPrec _ (AnyVar) = ("X"++)
instance Show AddSub where
showsPrec d (ASOpVar b e) = showParen (d > 6) $ ("X"++) . ((if b then
"+" else "-")++) . showsPrec 6 e
showsPrec d (ASOp b e1 e2) = showParen (d > 6) $ showsPrec 6 e1 . ((if b
then "+" else "-")++) . showsPrec 6 e2
instance Show MulDiv where
showsPrec d (MDOpVar b e) = showParen (d > 7) $ ("X"++) . ((if b then
"*" else "/")++) . showsPrec 7 e
showsPrec d (MDOp b e1 e2) = showParen (d > 7) $ showsPrec 7 e1 . ((if b
then "*" else "/")++) . showsPrec 7 e2
On 18 November 2012 20:31, Rune Harder Bak
On Sun, Nov 18, 2012 at 2:04 PM, Stefan Klinger
wrote: Sounds like you would want to enumerate all possible *abstract* syntax trees, these implicitly have exactly the necessary parentheses. I'd do this recursively, splitting the sequence of numbers in two at all possible places, and then combine the corresponding results with all possible operators.
That was my second idea, but just doing it naively resulted in many equivalent calculations, so I thought there might be a better way to view the problem. But as Artyom showed
On Sat, Nov 17, 2012 at 11:37 PM, Artyom Kazak
wrote:
Indentation messed up… I have pasted the code here: http://hpaste.org/77864
enumerating the abstract syntax tree is actually (or at least could be) the way to go! Thanks a lot! What I need is a little bit different, but now I feel I'm on the right track!
This is my first question to the café and it makes me a lot more certain using Haskell for production, when you can get this kind of quick and thorough help when in doubt.
Great community!
-Rune
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Jonas Almström Duregård
Hi,
You can make a datatype that captures exactly the expressions you want (see code below). Essentially you want to make sure that a subtraction or addition never has another subtraction or addition as its left operand.
I would also like to advertise a bit and show how this type can be enumerated automatically by Feat ( http://hackage.haskell.org/package/testing-feat).
After a quick look, Feat seems to be awesome. Thanks! I don’t yet know how I am going to use it, but I hope an opportunity will present itself soon :)

Well, at least this is a nice exercise! I'm assuming that all operators associate to the left, and use the usual precedence rules. My approach would consider (1+2)+3 different from 1+(2+3), and enumerate it again. Of course they are different computations, though mathematically equivalent. Jonas' approach is better here, but it seems to miss X/(X/X) — not tested, it's just not in his email. But then the equivalent X/X*X is present. So... what kind of equivalences *exactly* do you want to omit? Here's some code for my somewhat more permissive solution:
data Expr = Val Float | Op Char Expr Expr deriving (Eq)
instance Show Expr where showsPrec _ (Val v) = shows v showsPrec p (Op o e1 e2) = showParen (p>q) $ showsPrec q e1 . showString [' ',o,' '] . showsPrec (q+1) e2 where q = case o of '+' -> 1 '-' -> 1 '*' -> 3 '/' -> 3
Split a sequence in two non-empty sequences at all possible places.
allSplits :: [a] -> [([a],[a])] -- ok, this is ugly allSplits xs = [splitAt n xs | n <- [1 .. length xs - 1]]
Calculate all ASTs.
exps [x] = [Val x] exps xs = [ Op o l r | (as,bs) <- allSplits xs , l <- exps as , r <- exps bs , o <- "+-*/" ]
putStr . unlines . map show $ exps [1..3] -- Stefan Klinger o/klettern /\/ bis zum send plaintext only - max size 32kB - no spam \ Abfallen http://stefan-klinger.de
participants (4)
-
Artyom Kazak
-
Jonas Almström Duregård
-
Rune Harder Bak
-
Stefan Klinger