Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Minimize parenthesis when printing expression

I have a simple arithmetic expression data structure that I want to be able to print. For sake of simplicity here I have made an example with 3 binary operations, addition, multiplication and division. The definition looks like this:

module ExprPrint where

import Text.Printf

data Expr = Lit Int
          | Add Expr Expr
          | Mul Expr Expr
          | Div Expr Expr

instance Show Expr where
  show (Lit x) = show x
  show (Add e1 e2) = printf "(%s) + (%s)" (show e1) (show e2)
  show (Mul e1 e2) = printf "(%s) * (%s)" (show e1) (show e2)
  show (Div e1 e2) = printf "(%s) / (%s)" (show e1) (show e2)

The goal I have is to print the data structure while removing all superfluous parenthesis. of course the naive show function I have implemented above includes way too many of them. So what I want to do is make the Show instance take the precedence (Div and Mul over Add) and associativity(Add and Mul are associative while Div is left-associative) of the operations into account.

Here are some examples:

one = Lit 1

-- Shows "((1) + (1)) + (1)" but should be 1 + 1 + 1
addAssoc = show $ Add (Add one one) one
-- Shows "((1) * (1)) * (1)" but should be 1 * 1 * 1
mulAssoc = show $ Mul (Mul one one) one
-- Shows "((1) / (1)) / (1)" but should be 1 / 1 / 1
divAssoc = show $ Div (Div one one) one
-- Shows "(1) / ((1) / (1)) but should be 1 / (1 / 1)
divAssoc2 = show $ Div one (Div one one)

-- Show "((1) * (1)) + (1)" but should 1 * 1 + 1
addPrec = show $ Add (Mul one one) one
-- Show "(1) + ((1) * (1))" but should show 1 + (1 * 1)
addPrec2 = show $ Add one (Mul one one)

Is there an "easy" to take that into account in the show instance? I think I could do it by taking all the cases into account but that would be an explosion of functions. Is there some algorithm or known way to handle this?

I hope somebody has some pointers!

Thanks.

like image 552
CryptoNoob Avatar asked Apr 11 '20 15:04

CryptoNoob


1 Answers

An instance in terms of show isn't powerful enough to avoid redundant parentheses, since it doesn't have any information about precedence available. You'll need to write your instance in terms of showsPrec instead, which does, like this:

module ExprPrint where

import Text.Show

data Expr = Lit Int
          | Add Expr Expr
          | Mul Expr Expr
          | Div Expr Expr

instance Show Expr where
  showsPrec prec (Lit x) = showsPrec prec x
  showsPrec prec (Add e1 e2) = showParen (prec >= 7) $ showsPrec 7 e1 . showString " + " . showsPrec 7 e2
  showsPrec prec (Mul e1 e2) = showParen (prec >= 8) $ showsPrec 8 e1 . showString " * " . showsPrec 8 e2
  showsPrec prec (Div e1 e2) = showParen (prec >= 8) $ showsPrec 8 e1 . showString " / " . showsPrec 8 e2

I chose 6 and 7 for your precedence levels since that's what Haskell uses for its own +, *, and div operators, but it should be obvious how you'd choose different ones.

As for associativity, there's no perfect way to do that in general, but you can fake it with some precedence tweaks in your case, since math doesn't have any operators at the same precedence levels with different associativies. Here's an example of how to do that (I added Exp, with precendence level 8, to give an example of the right-associative way to do it too):

module ExprPrint where

import Text.Show

data Expr = Lit Int
          | Add Expr Expr
          | Mul Expr Expr
          | Div Expr Expr
          | Exp Expr Expr

instance Show Expr where
  showsPrec prec (Lit x) = showsPrec prec x
  showsPrec prec (Add e1 e2) = showParen (prec >= 7) $ showsPrec 6 e1 . showString " + " . showsPrec 7 e2
  showsPrec prec (Mul e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " * " . showsPrec 8 e2
  showsPrec prec (Div e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " / " . showsPrec 8 e2
  showsPrec prec (Exp e1 e2) = showParen (prec >= 9) $ showsPrec 9 e1 . showString " ^ " . showsPrec 8 e2

That's still not perfect, since it still doesn't know the associative property of Add or Mul, so Mul one (Mul one one) will show as 1 * (1 * 1) instead of 1 * 1 * 1, but I don't think there's any possible way to fix that, since division doesn't share that property, but since it has the same precedence as multiplication, you can't distinguish them in showsPrec.


Actually, you can cheat a bit more than that, by peeking at the next level down and re-associating:

module ExprPrint where

import Text.Show

data Expr = Lit Int
          | Add Expr Expr
          | Mul Expr Expr
          | Div Expr Expr
          | Exp Expr Expr

instance Show Expr where
  showsPrec prec (Lit x) = showsPrec prec x
  showsPrec prec (Add e1 (Add e2 e3)) = showsPrec prec (Add (Add e1 e2) e3)
  showsPrec prec (Add e1 e2) = showParen (prec >= 7) $ showsPrec 6 e1 . showString " + " . showsPrec 7 e2
  showsPrec prec (Mul e1 (Mul e2 e3)) = showsPrec prec (Mul (Mul e1 e2) e3)
  showsPrec prec (Mul e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " * " . showsPrec 8 e2
  showsPrec prec (Div e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " / " . showsPrec 8 e2
  showsPrec prec (Exp e1 e2) = showParen (prec >= 9) $ showsPrec 9 e1 . showString " ^ " . showsPrec 8 e2

I think this is perfect. All of your test cases pass now.

like image 122
Joseph Sible-Reinstate Monica Avatar answered Nov 01 '22 04:11

Joseph Sible-Reinstate Monica