Operations on user-defined data types

I have a data type

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 a (3* 4 + 5)

data type Expr

it should return 17

, and if the expression includes a variable:, (3 * x)

it should returnExprMul (ExprNum 3) (ExprVar "x")

I've tried doing it like this:

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 cannot fulfill it. What am I doing wrong here?

Another thing I want to know about is that if the user enters a value in type Expr and I need to convert it to string format, that is, if the user enters

ExprAdd (ExprNum 1) (ExprVar "x")

      

I want to get the result like this

1+x

      

I tried to use Read

but I can't seem to complete it.

Please if someone can help. Thank.

+1


source to share


1 answer


Considering your question and your examples, I think we can do it in a good way using some types of classes to get syntactic sugar.

You can find the complete code at the end, but as Luke gave me a good argument without explaining what to start with.

First we have to take care of some minor issues in your implementation calculate

, and then we can start looking for syntactic sugar to enable input, for example (3* 4 + 5) :: Expr

.

realization calculate

It wasn't 100% to me, but I think you want yours to calculate

have this signature:

calculate :: Expr -> Expr

      

Most of the time you see things like evaluate :: Expr -> Maybe Double

, but I think in this case (because you want it to 3 * x

be ExprMul (ExprNum 3) (ExprVar "x")

), we really want to just simplify the terms by using calculate

.

So, try to simplify things.

For form expressions ExprNum

and ExprVar

there is nothing we can do to simplify things as they are, so let's be honest:

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

      

If you haven't seen the syntax a@(ExprNum _)

before it just comes in handy for matching (ExprNum _)

, but remember to match the set expression in a

.

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

calculate (ExprMul a b) = a * b

      

The problem is your right side. a * b

It won't work now as it (*)

should have operands in Num

, but Expr

not yet.

Of course, we really want to get your product, if we can - this means that both a

and b

really are numbers - or in this case ExprNum

.

The easiest way to test this (I can think of) is to recursively simplify both operands a

and b

and then use the expression case

:

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'

      

Take a look at this step by step:

  • first it simplifies a

    both b

    in a'

    and out b'

    with calculate

    recursivley
  • then if both of these numbers ( ExprNum

    ), they give the product of their values โ€‹โ€‹as anotherExprNum

  • if they are not both ExprNum

    , it just gives ExprMul

    using the simplified term

The latter indicates that there is a bit of magic going on - since we are providing simplified terms, the algorithm will try to simplify the subterms even if the variable is around, and we cannot get a full estimate.

refactoring bits

Now we can do the same with other expressions such as ExprDiv

, ExprAdd

... but I did not want to repeat the material over and over again, so let's reorganize it:

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 the same as what we did above, even if it may seem a little more complicated. Again we are only checking if we can simplify the subterms (two for operateOnNums

and only one for operateOnNum

) into expressions ExprNum

, and if applicable, the value for the function f

(these will be real-valued operations - for example, (*)

for ExprMul

or negate

for ExprNeg) and if not use

def (meaning *defaults*) to wrap the simplified subterms into

Expr `again.

Calculate yourself look pretty nice now (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.

including syntactic sugar: implementation of some types of classes

Num

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

.

There is now a base class type with a name Num

that provides us with exactly this facility. You basically have to tell the Haskell, how to make a large enough subset of basic mathematical operators such as *

, +

, .. along with a function fromIntegral

that will translate numbers such as 0

, 1

, 2

, ... in Expr

.

What really pleased that we have these statements, and even fromIntegral

longer in the form of our convenient type constructors ExprMul

, ExprAdd

.. and ExprNum

.

So let's make an Expr

instance 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 I fooled with functions abs

and signum

. If you like, you can implement them too if you add other cases to them Expr

and add the function accordingly calculate

, but for the examples they provided OP, they really aren't needed here.

However, 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 can evaluate something like this:

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

      

OverloadedStrings should be translated "a"

using fromString

from IsString

instead of just compiling it to [char]

, so let's implement IsString

- it's very simple again since we already have it fromString

in the form ExprVar

:

instance IsString Expr where
  fromString = ExprVar

      

Don't forget to include OverloadedStrings

s {-# LANGUAGE OverloadedStrings #-}

in the source. In GHCi you may want - run it with ghci -XOverloadedStrings

 - :set -XOverloadedStrings

inside GHCi

Fractional

This was a suggestion from @ ร˜rjanJohansen so that we can write things like

I think you can get it to work something like this:

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

      

This is very similar Num

for fractional values โ€‹โ€‹and division - I think you know which is coming up to now:

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

      

What is it - please remember to point me out things that are not 100% clear or written.

How to evaluate variables

You may ask how you can evaluate variables.

Since we are no longer interested in the resulting expression, but only in this value, 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

      

Much of this should be straight forward - the only new thing is env

: We need to know what value a variable has. So we go through an environment with pairs (variables, values). We can then use it lookup

together with fromMaybe

to find values โ€‹โ€‹for the variables.

An example might look like this:

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

      

As you can see, I just provided one pair, matching "a"

with 5

- and then using an expression using ExprVar "a"

(here, of course, hidden with IsString

and OverloadedStrings

).

In case the algorithm does not find a matching variable lookup

, it will return Nothing

, in which case it will be involved fromMaybe

: in this case, I decided to use the default variables 0

, and that's exactly what fromMaybe 0 :: Maybe Double -> Double

(here).

if you don't want any default behavior for

If you don't like what this will return 0

for non-environment variables, you can change evaluate

both partial (or better: return Maybe Double

) as follows:

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 weapons ( liftM2

brining (*)

in monad Maybe

and (<$>)

doing the same with negate

).

Please understand that I cannot write another large block of text to explain this in detail.

Basically it is only because I have to be lazy in comparison with templates based on the results evaluate env a

and evaluate env b

to handle 4 cases ( Nothing, Nothing

, Nothing, Just

, ...) - I am only interested in anyway Just,Just

, and they do just that: perform the operation in the cases Just

and return Nothing

everywhere.

Complete code

For reference and easier copy and paste, here's 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'

      

a few 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 include OverloadedStrings

in GHCi if you want to try: - run it with ghci -XOverloadedStrings

 - :set -XOverloadedStrings

inside GHCi

+13


source







All Articles