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

        This is achievable in Haskell as well.
        See http://holomorphy.com/~wli/scripts/FunctionAlgebra.hs

On Thu, Aug 24, 2000 at 04:04:45AM +0200, Ralf Muschall wrote:
} 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.)

        Well, the separation of the various operations and perhaps
making things more mathematically sensible was part of the basic algebra
proposal. The mailing list archives should give you an idea of what
issues were involved with this.

On Thu, Aug 24, 2000 at 04:04:45AM +0200, Ralf Muschall wrote:
} 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).

        The system of type classes can also yield something that is also
perhaps a little confusing, and without the recourse of reflection and
dynamic whatever wizardry. See the below.

On Thu, Aug 24, 2000 at 04:04:45AM +0200, Ralf Muschall wrote:
} 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)

        [snip]

I believe I had something on the order of this in my (by now older) post
on "Function Algebra". My formulation has the advantage that a number of
other things may be done more directly. For instance:

FunctionAlgebra> (+1) + (*2) $ 3.0
10.0
FunctionAlgebra> sin + cos $ 1.0
1.38177
FunctionAlgebra> ((+) + (*) $ 1) 2
5
FunctionAlgebra> cos sin
<<function>>
FunctionAlgebra> cos sin $ 2.0
0.6143


And a disadvantage:
FunctionAlgebra> 1 2
1
FunctionAlgebra> ((+) + (*) $ 1) 2 $ 3
5

Another thing is that the transformer (a->) of kind (*->*) is irrelevant.
The only thing that matters is enough "algebraic" character getting
inherited by the result type.  Witness the following:

> instance Num a => Num [a] where
>       f + g = zipWith (+) f g
>       f * g = zipWith (*) f g
>       f - g = zipWith (-) f g
>       negate f = map negate f
>       abs f = map abs f
>       signum f = map signum f
>       fromInt i = [i]
>       fromInteger n = [n]

with silly examples like
ListNumbers> [1..3] + [5..8]
[6,8,10]
ListNumbers> [2..5] * [9..12]
[18,30,44,60]
ListNumbers> -[1..10]
[-1,-2,-3,-4,-5,-6,-7,-8,-9,-10]
ListNumbers> (map (\n -> reverse [n..n^2]) [2..6]) - (map (\n -> [n..n^2]) [1..5])
[[3],[7,5,3],[13,11,9,7,5,3,1],[21,19,17,15,13,11,9,7,5,3,1,-1,-3],[31,29,27,25,23,21,19,17,15,13,11,9,7,5,3,1,-1,-3,-5,-7,-9]]
ListNumbers> reverse 2
[2]

I think we can all see where this is going.
It's generalizable to all constructors of class Functor and that are
zippable and have a unary constructor. Unfortunately, the existing
class structure makes this phenomenally difficult to do without nasties
like overlapping instances. In hugs, minus some setup code, this yields

instance (Eq (f a), Show (f a), Num a, Functor f, Zippable f, HasUnaryCon f) => Num (f 
a) where
        f + g = fmap (uncurry (+)) $ fzip f g
        f * g = fmap (uncurry (*)) $ fzip f g
        f - g = fmap (uncurry (-)) $ fzip f g
        negate f = fmap negate f
        abs f = fmap abs f
        signum f = fmap signum f
        fromInteger i = unaryCon . fromInteger $ i

The nasty language feature (overlapping instances) would not be
required given some slight modifications to the Prelude, but thus far
hugs can handle this.
See http://holomorphy.com/~wli/scripts/FunctorAlgebra.hs

Cheers,
Bill

Reply via email to