Bjorn Lisper <[EMAIL PROTECTED]> writes:

> >    cos+sin        -- intent: \x->((cos x)+(sin x))
> >    cos(sin)       -- intent: \x->cos(sin(x))

> have equivalents in Fortran 90 and HPF, although with arrays rather than
> functions. For instance, one can write "A+B" to mean an array with value

But I'd look at this differently: Essentially it means to have
a typeclass Addable which is a superclass of Num and making vectors
instances of Addable. (If Fortran9x also allows multiplication,
we need no Addable and use Num directly.)

OTOH, something like this is used in Xlisp-stat, and I hate it :-)
(it does make programming harder, since I always have to think (or
even worse, to experiment) whether some function will map itself over
lists or not. (Xlisp-stat is even harder, since it uses lists as well
as vectors. As a result of this "niceness", I have to write all my
functions which might be passed as arguments to HOFs with a typecheck
in order to find out whether the system's functions (like minimizers
etc.) called them with a vector, a list, or a number).

If one really needs to add functions argumentwise in a programm, one
should IMHO use something like

data (Num b) =>  NumFunction a b = NumFunction (a->b)

instance (Num b) => Eq (NumFunction a b)
    where
    (NumFunction f) == (NumFunction g) = error "cannot eq funcs"

instance (Num b) => Show (NumFunction a b)
    where
    show (NumFunction f) = error "cannot show funcs"
    -- one should use something smarter here

instance (Num b) => Num (NumFunction a b)
    where
    (NumFunction f)+(NumFunction g) = NumFunction (\x->(f x)+(g x))
    (NumFunction f)*(NumFunction g) = NumFunction (\x->(f x)*(g x))
    (NumFunction f)-(NumFunction g) = NumFunction (\x->(f x)-(g x))
    negate (NumFunction f) = NumFunction (negate . f)
    abs (NumFunction f) = NumFunction (abs . f)
    signum (NumFunction f) = NumFunction (signum . f)
    fromInteger x = NumFunction (\_ -> fromInteger x)
    fromInt x = NumFunction (\_ -> fromInt x)

useFunc :: (Num b) => (NumFunction a b) -> a -> b
useFunc (NumFunction f) = f

-- example
h::NumFunction Double Double
h = (NumFunction cos) + (NumFunction sin)
-- useFunc h 0.7 gives 1.40905987
-- usefunc 3 4 gives 3
-- useFunc (1+h*3) 0.01 gives 4.0298495

Ralf

Reply via email to