On Wed, Dec 01, 1999 at 02:05:04PM +0000, Jerzy Karczmarczuk wrote:
> José Romildo Malaquias:
> 
> > One of the algorithms I have to implement is the
> > addition of symbolic expressions. It should have
> > two symbolic expressions as arguments and should
> > produce a symbolic expression as the result. But
> > how the result is produced is depending on series
> > of flags that control how the expressions is to
> > be manipulated. This set of flags should then be
> > passed as a third argument to addition function.
> > This is the correct way of doing it. But, being
> > a Mathematics application, my system should preserve
> > the tradicional Math notation (that is, infix
> > operators with suitable associations defined). So
> > my symbolic expression type should be an instance
> > of the Num class so that the (+) operator can
> > be overloaded for it. But, as the function has
> > now three arguments, it cannot be a binary operator
> > anymore.
> 
> ... then about Monads e algumas outras coisinhas mais
> ou menos bonitas.
> 
> ==
> 
> I don't fully understand the issue. If it is only 
> a syntactic problem, and for a given chunk, say,
> a module, your set of flags is fixed, and does not change
> between one expression and another, you can always define

No, it is not only a syntatic problem and the set of flags is
not fixed. Indeed it may change in the course of some
computation. Some algorithms will set some flags based on
the values of other flags during the computation. It may be
the case that the same function is recursively applied
with a different set of flags.

A simple example of the style of programming am talking
about can be seen in the following example (in Hugs98,
loaded with the extensions):
-------------------
module Context where

data Context = Context { num_num :: Int, branch :: Bool }

som :: (?c :: Context) => Rational -> Rational -> Rational
som x y
      | num_num ?c > 0 = x + y
      | otherwise      = x - y

mul :: (?c :: Context) => Rational -> Rational -> Rational
mul x y
      | num_num ?c > 0 = x * y
      | otherwise      = x / y

f :: (?c :: Context) => Rational -> Rational
f x = let a = som x 2
          n = num_num ?c
          b = mul x 5 with ?c = Context { num_num = - n, branch = True }
      in mul a b

run = dlet ?c = Context { num_num = 3, branch = False }
      in f 8

main = putStr (show run)
-------------------

Note that som, mul and f uses the context and f also evaluates a
subexpression in a new context. main evaluates (f 8) in an initial
context.

> 
> add flagSet x y = ...-- your addition function--
> 
> and then overload
> 
> x+y = add myCurrentEnv x y
> 
> in this module.

So, your sugestion will not work for me.

> (I can't resist complaining once more about
> the inadequacy of the Num class hierarchy in Haskell ...;
> one will have to do the same in the Rational or Floating
> instance definitions, which is clumsy).
> 
> Jerzy Karczmarczuk
> Caen, France

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

Reply via email to