anujuhi01
anujuhi01

Reputation: 71

Operations with user defined Datatype

I have a datatype

data Expr = ExprNum Double -- constants
          | ExprVar String -- variables
          | ExprAdd Expr Expr
          | ExprSub Expr Expr
          | ExprNeg Expr -- The unary '-' operator
          | ExprMul Expr Expr
          | ExprDiv Expr Expr
          deriving Show

If I have (3* 4 + 5) of datatype Expr it should return 17 and if the expression includes a variable: (3 * x) it should return ExprMul (ExprNum 3) (ExprVar "x")

I tried doing it this way:

calculate (ExprMul a b) = a * b
calculate (ExprAdd a b) = a + b
calculate (ExprDiv a b) = a `div` b
calculate (ExprSub a b) = a - b
calculate (ExprVar a )= a
calculate (ExprNum a ) = Read a : Double

But I am unable to execute it. What am I doing wrong here?

Another thing that I wish to know about is that if a user enters a value in Expr type ,and I need to convert it into string format,i.e,if User enters as

ExprAdd (ExprNum 1) (ExprVar "x")

I wish to get the output as follows

1+x

I tried using Read but I am unable to execute it.

Please if anyone can help.Thankyou.

Upvotes: 1

Views: 572

Answers (1)

Random Dev
Random Dev

Reputation: 52290

Looking at your question and your examples, I think we can make this happen in a nice way using some type-classes to get some syntactic sugar.

You can find the complete code at the end but as Luke made a good point on me not explaining stuff let's start doing this.

First we have to take care on some minor problems in your implementation of calculate and then we can start looking for some syntactic sugar to enable input like (3* 4 + 5) :: Expr.

implementing calculate

It was not 100% clear to me but I think you want your calculate to have this signature:

calculate :: Expr -> Expr

I most cases you see things like evaluate :: Expr -> Maybe Double but I think in this case (because you want 3 * x to be ExprMul (ExprNum 3) (ExprVar "x")) we want indeed just to simplify terms using calculate.

So let's try to simplify things.

For expressions of the form ExprNum and ExprVar we can do nothing more to simplify things as it is, so let's be honest and say so:

calculate a@(ExprNum _) = a
calculate a@(ExprVar _) = a

If you did not see the a@(ExprNum _) syntax before it's just fancy way of matching (ExprNum _) but remembering the compllete matched expression in a.

With this in mind we have to take care of the more interesting cases - for example multiplication:

calculate (ExprMul a b) = a * b

The problem is your right side a * b Right now this cannot work as (*) needs to have it's operands to be in Num and Expr is not (yet).

Of course what we really want is to calculate the product if we can - meaning if both a and b are indeed numbers - or in this case ExprNum.

The easiest way to check this (I can come up with) is to recursivley simplify both operants a and b and then to use a case expression:

calculate (ExprMul a b) = let a' = calculate a
                              b' = calculate b
                          in case (a',b') of
                             (ExprNum a'', ExprNum b'') -> ExprNum (a''*b'')
                             _                          -> ExprMul a' b'

Let's look at this step by step:

  • first it simplifies a and b into a' and b' using calculate recursivley
  • then if both of these are numbers (ExprNum) it yield the product of their values as another ExprNum
  • if they are not both ExprNums it just yield an ExprMul using the simplified term

The last point is where a bit of the magic happens - because we yield the simplified terms the algorithm will try to simplify subterms even if a variable is around and we cannot get a complete evaluation.

refactoring a bit

Now we can do the same to the other expressions like ExprDiv, ExprAdd, ... but I did not really like to repeat the stuff again and again so let's refactor this out:

operateOnNums :: (Expr -> Expr -> Expr) 
              -> (Double -> Double -> Double) 
              -> Expr -> Expr -> Expr
operateOnNums def f a b = let a' = calculate a
                              b' = calculate b
                          in case (a',b') of
                            (ExprNum a'', ExprNum b'') -> ExprNum (f a'' b'')
                            _                          -> def a' b'

operateOnNum :: (Expr -> Expr) 
             ->  (Double -> Double) 
             -> Expr -> Expr
operateOnNum def f a = let a' = calculate a
                       in case a' of
                         ExprNum a'' -> ExprNum (f a'')
                         _           -> def a'

This is really just the same we did above even if these might seem to be a bit more complicated. Again we only check if we can simplify subterms (two for operateOnNums and only one for operateOnNum) into ExprNum expressions and if so apply the value of those to a function f (that will be the operations on the real numbers - like (*) for ExprMul or negate for ExprNeg) and if not usedef(meaning *defaults*) to wrap the simplified subterms intoExpr`s again.

Calculate itself now look rather nice (or so I think):

calculate :: Expr -> Expr
calculate (ExprMul a b) = operateOnNums ExprMul (*) a b
calculate (ExprAdd a b) = operateOnNums ExprAdd (+) a b
calculate (ExprDiv a b) = operateOnNums ExprDiv (/) a b
calculate (ExprSub a b) = operateOnNums ExprSub (-) a b
calculate (ExprNeg a)   = operateOnNum ExprNeg negate a
calculate a             = a

and I think we can move on.

enabling syntactic sugar: implementing some type-classes

Num

This leaves us with the problem that we want to be able to input something like 3*4+5 :: Expr.

Now there is a basic type-class named Num that provides us exactly with the means to do so. You basically have to tell Haskell how to do a big enough subset of the basic math-operators like *, +, .. together with a function fromIntegral that will translate numbers like 0, 1, 2, ... into Expr.

What's really nice here is, that we have those operators and even the fromIntegral already handy in form of our type-constructors ExprMul, ExprAdd, .. and ExprNum.

So let's make Expr an instance of Num:

instance Num Expr where
  a + b         = ExprAdd a b
  a * b         = ExprMul a b
  negate a      = ExprNeg a
  fromInteger n = ExprNum (fromInteger n)
  abs _         = undefined
  signum _      = undefined

Easy isn't it?

Note that I cheated with the abs and signum functions. If you like you can implement these too if you add other Expr cases for them and complement the calculate function accordingly - but for the examples the OP gave they are not really needed here.

With this done this will already work:

> calculate $ 3*4+5
ExprNum 17.0

> calculate $ 3*4 + ExprVar "a"
ExprAdd (ExprNum 12.0) (ExprVar "a")

IsString

@behklir suggested to implement this type-class as well - using this and the OverloadedString extension we will be able to evaluate something like this:

> calculate $ 3*4+"a"
ExprAdd (ExprNum 12.0) (ExprVar "a")

OverloadedStrings is there to translate "a" using the fromString from IsString instead of just compiling it into a [char], so let's implement IsString - which again is really easy as we already have fromString in the form of ExprVar:

instance IsString Expr where
  fromString = ExprVar

Don't forget to enable OverloadedStrings with {-# LANGUAGE OverloadedStrings #-} in source. In GHCi you might want to - start it with ghci -XOverloadedStrings - :set -XOverloadedStrings inside GHCi

Fractional

This one was a suggestion from @ØrjanJohansen to enable us to write things like

I think you can get this working something like this:

> calculate $ "a" / 4.5
ExprDiv (ExprVar "a") (ExprNum 4.5)

It's much like Num for fractional values and the division - I think you know what comes by now:

instance Fractional Expr where
  fromRational r = ExprNum (fromRational r)
  a / b          = ExprDiv a b

That's it - please make sure to point me to things not 100% clear or misspelled.

How to evaluate Variables

You might ask how you could evaluate Variables.

As we are no longer interested in a resulting expression but only in it's value let's call it evaluate:

import Data.Maybe (fromMaybe)

evaluate :: [(String, Double)] -> Expr -> Double
evaluate env (ExprMul a b) = evaluate env a * evaluate env b
evaluate env (ExprAdd a b) = evaluate env a + evaluate env b
evaluate env (ExprDiv a b) = evaluate env a / evaluate env b
evaluate env (ExprSub a b) = evaluate env a - evaluate env b
evaluate env (ExprNeg a)   = negate $ evaluate env a
evaluate _   (ExprNum n)   = n
evaluate env (ExprVar v)   = fromMaybe 0 $ lookup v env

Most of this should be straight forward - the only really new thing is env: We need to know what value a variable has. So we pass in an environment with (variable,value) pairs. We can then use lookup together with fromMaybe to find values for variables.

An example could look like this:

> evaluate [("a",5)] (3*4+"a")
17.0

As you can see I just provided a single pair, matching "a" to 5 - and then use an expression using ExprVar "a" (here of course hidden using IsString and OverloadedStrings).

In case the algorithm will not find a matching variable lookup will return Nothing and this is where fromMaybe comes into play: I decided to default variables to 0 in this case and this is exactly what fromMaybe 0 :: Maybe Double -> Double does (here).

if you don't want no default-to-0 behaviour

In case you don't like it that this will return 0 for variables not in the environment you can change evaluate to be partial (or better: return Maybe Double) like this:

import Control.Applicative((<$>))
import Control.Monad (liftM2)

evaluate :: [(String, Double)] -> Expr -> Maybe Double
evaluate env (ExprMul a b) = liftM2 (*) (evaluate env a) (evaluate env b)
evaluate env (ExprAdd a b) = liftM2 (+) (evaluate env a) (evaluate env b)
evaluate env (ExprDiv a b) = liftM2 (/) (evaluate env a) (evaluate env b)
evaluate env (ExprSub a b) = liftM2 (-) (evaluate env a) (evaluate env b)
evaluate env (ExprNeg a)   = negate <$> evaluate env a
evaluate _   (ExprNum n)   = Just n
evaluate env (ExprVar v)   = lookup v env

This of course uses some heavy weaponary (liftM2 brining (*) into the Maybe monad and (<$>) doing the same with negate).

Please understand that I cannot write another big block of text to explain those in detail.

Basically those are just there because I am to lazy to pattern-match on the results of evaluate env a and evaluate env b to do handle 4 cases (Nothing, Nothing, Nothing, Just, ...) - I am only interested in Just,Just anyway and those do exactly this: do the operation in the Just cases and return Nothing everywhere else.

The complete code

For reference and easier copy&paste here is the complete code:

{-# LANGUAGE OverloadedStrings #-}

module Expressions where

import Data.Maybe (fromMaybe)
import Data.String (IsString(..))

data Expr = ExprNum Double -- constants
          | ExprVar String -- variables
          | ExprAdd Expr Expr
          | ExprSub Expr Expr
          | ExprNeg Expr -- The unary '-' operator
          | ExprMul Expr Expr
          | ExprDiv Expr Expr
          deriving Show

instance Num Expr where
  a + b          = ExprAdd a b
  a * b          = ExprMul a b
  negate a       = ExprNeg a
  fromInteger n  = ExprNum (fromInteger n)
  abs _          = undefined
  signum _       = undefined

instance Fractional Expr where
  fromRational r = ExprNum (fromRational r)
  a / b          = ExprDiv a b

instance IsString Expr where
  fromString     = ExprVar

evaluate :: [(String, Double)] -> Expr -> Double
evaluate env (ExprMul a b) = evaluate env a * evaluate env b
evaluate env (ExprAdd a b) = evaluate env a + evaluate env b
evaluate env (ExprDiv a b) = evaluate env a / evaluate env b
evaluate env (ExprSub a b) = evaluate env a - evaluate env b
evaluate env (ExprNeg a)   = negate $ evaluate env a
evaluate _   (ExprNum n)   = n
evaluate env (ExprVar v)   = fromMaybe 0 $ lookup v env

calculate :: Expr -> Expr
calculate (ExprMul a b) = operateOnNums ExprMul (*) a b
calculate (ExprAdd a b) = operateOnNums ExprAdd (+) a b
calculate (ExprDiv a b) = operateOnNums ExprDiv (/) a b
calculate (ExprSub a b) = operateOnNums ExprSub (-) a b
calculate (ExprNeg a)   = operateOnNum ExprNeg negate a
calculate a             = a


operateOnNums :: (Expr -> Expr -> Expr) ->  (Double -> Double -> Double) -> Expr -> Expr -> Expr
operateOnNums def f a b = let a' = calculate a
                              b' = calculate b
                          in case (a',b') of
                            (ExprNum a'', ExprNum b'') -> ExprNum (f a'' b'')
                            _                          -> def a' b'

operateOnNum :: (Expr -> Expr) ->  (Double -> Double) -> Expr -> Expr
operateOnNum def f a = let a' = calculate a
                       in case a' of
                         ExprNum a'' -> ExprNum (f a'')
                         _           -> def a'

some examples

> calculate $ 3*4+5
ExprNum 17.0

> calculate $ 3*4+"a"
ExprAdd (ExprNum 12.0) (ExprVar "a")

> calculate $ 3*"a"+5
ExprAdd (ExprMul (ExprNum 3.0) (ExprVar "a")) (ExprNum 5.0)

> calculate $ 3*4+"a"
ExprAdd (ExprMul (ExprNum 3.0) (ExprNum 4.0)) (ExprVar "a")

> calculate $ "a" / 4.5
ExprDiv (ExprVar "a") (ExprNum 4.5)

> evaluate [("a",5)] (3*4+"a")
17.0

which is (I think) what you wanted to start with

remarks:

Don't forget to enable OverloadedStrings in GHCi if you want to try this: - start it with ghci -XOverloadedStrings - :set -XOverloadedStrings inside GHCi

Upvotes: 14

Related Questions