Re: Higher-order function application

2000-08-24 Thread William Lee Irwin III

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




Higher-order function application

2000-08-23 Thread Tim Sweeney

In Haskell, only a single notion of "function application" exists, where a
function f::t-u is passed a parameter of type t, returning a result of type
u.  Example function calls are:

1+2
sin 3.14
map sin [1:2:3]

However, a higher-order notion of function application seems sensible in
many cases.  For example, consider the following expressions, which Haskell
rejects, despite an "obvious" programmer intent:

cos+sin-- intent: \x-((cos x)+(sin x))
cos(sin)   -- intent: \x-cos(sin(x))
(cos,sin)(1,2) -- intent: cos(1),sin(2)
(+)(1,2)   -- intent: (+)(1)(2)
cos [1:2:3]-- intent: map cos [1:2:3]

From this intuition, let's postulate that it's possible for a compiler to
automatically accept such expressions by translating them to the more
verbose "intent" listed above, using rules such as:

1. Operator calls like (+) over functions translate to lambda abstractions
as in the "cos+sin" example.

2. A pair of functions f::t-u, g::v-w acts as a single function from pairs
to pairs, (f,g)::(t,u)-(v,w).

3. Translating function calling into function composition, like "cos(sin)".

4. Automatic currying when a pair is passed to a curried function.

5. Automatic uncurrying when a function expecting a parameter of type (t,u)
is passed a single value of type t.

6. Applying a function f:t-u to a list x::[t] translates to "map f x".

I wonder, are these rules self-consistent?  Are they unambiguous in all
cases?  Are there other rules we can safely add?

It also seems that every statement above is simply a new axiom at the type
checker's disposal.  For example, to describe the general notion of
"cos+sin" meaning "\x-(cos(x)+sin(x))", we say:

for all types t,u,v,
for all functions f,g :: t-u,
    for all functions h ::u-u-v,
h (f,g) = \x-h(f(x),g(x)).

Is this "higher order function application" a useful notion, and does any
research exist on the topic?

-Tim





Re: Higher-order function application

2000-08-23 Thread Ch. A. Herrmann

Hi Tim,

Tim 6. Applying a function f:t-u to a list x::[t] translates to
Tim "map f x".

the problem is that we loose much of the strength the Haskell type
system provides and a lot of programming errors will remain
undetected.

What you can do is write a preprocessor that provides a
nicer syntax for you.

Cheers
-- 
 Christoph Herrmann
 E-mail:  [EMAIL PROTECTED]
 WWW: http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html




Re: Higher-order function application

2000-08-23 Thread Bjorn Lisper

Tim Sweeney:
Is this "higher order function application" a useful notion, and does any
research exist on the topic?

The answer to the first question is "yes, when it matches the intuition of
the programmer". Your two first examples:

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
A(I)+B(I) for all indices I, and A(B) for the array with elements A(B(I))
(provided B is an integer array whose elements all are valid indices for
A). This feature is widely used in array languages, where it is seen as an
intuitive and convenient notation to express array operations. I definitely
believe it could be useful also for operations over other data structures.

The answer to the second question is "surprisingly little". There is, for
instance, no formal description to be found of the Fortran 90 array
operations and how they type.  But it is quite straightforward to define
type systems and type checking algorithms for this, when the language is
explicitly typed. One example is

@InProceedings{Thatte-ScalingA,
  author =   {Satish Thatte},
  title ={Type Inference and Implicit Scaling},
  booktitle ={ESOP'90 -- 3rd European Symposium on Programming},
  editor =   {G. Goos and J. Hartmanis},
  number =   432,
  series =   {Lecture Notes in Computer Science},
  year = 1990,
  publisher ={Springer-Verlag},
  address =  {Copenhagen, Denmark},
  month =may,
  pages ={406--420}
}

where a type system for an APL-inspired overloading in an FP-like language
is described. This approach is based on subtyping.

A student of mine is pursuing another, more direct approach, where a
coercive type system is used to resolve the overloading at compile time
through a combined rewrite and type check. He did this for an explicitly
typed variant of Core ML, and this is reported in his Licentiate thesis
("file://ftp.it.kth.se/Reports/paradis/claest-licthesis.ps.gz"):

@PHDTHESIS{claest-lic,
AUTHOR = {Claes Thornberg},
TITLE = {Towards Polymorphic Type Inference with Elemental Function 
Overloading},
SCHOOL = it,
ADDRESS = {Stockholm},
YEAR = {1999},
TYPE = {Licentiate thesis},
MONTH = may,
NOTE = {Research Report } # rep-id # {99:03}
}

@STRING{it = "Dept.\ of Teleinformatics, KTH"}

@STRING{rep-id = "TRITA-IT R "}

When the type system is implicit (inference rather than checking), however,
less is known. You can do some tricks with the Haskell class system (for
instance, defining functions between instances of Num to be instances of
Num themselves, which then lets you overload numerical operations like "+")
but this solution has some restrictions and is also likely to lead to
run-time overheads. We would like to have something better.

Finally, there is an interesting discussion of this overloading business,
for array- and data parallel languages, in

@ARTICLE{Sip-Blel-Coll-Lang,
AUTHOR = {Jay M. Sipelstein and Guy E. Blelloch},
TITLE = {Collection-Oriented Languages},
JOURNAL = {Proc.\ {IEEE}},
YEAR = {1991},
VOLUME = {79},
NUMBER = {4},
PAGES = {504--523},
MONTH = apr
}

For instance, they bring up the possible conflicts which may occur when
trying to resolve this overloading for operations over nested data
structures. (A witness is length l, where l :: [[a]]: should it be just
length l, or resolved into map length l?)

Björn Lisper




Re: Higher-order function application

2000-08-23 Thread Ralf Muschall

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