[Haskell-cafe] List all multiply/add combinations

Jonas Almström Duregård jonas.duregard at chalmers.se
Sun Nov 18 23:31:01 CET 2012


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 <rune at bak.dk> wrote:
>
> On Sun, Nov 18, 2012 at 2:04 PM, Stefan Klinger
> <all-lista at stefan-klinger.de> 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 <artyom.kazak at gmail.com>
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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121118/16166b23/attachment.htm>


More information about the Haskell-Cafe mailing list