Despite being a fan of generic programming, I have my doubts about this
kind of automatic lifting. It works fine in "ordinary mathematics",
because there is no fear of confusion - one hardly ever deals with
functions as entities in their own right. (Witness "sigma sin(x) dx",
involving a term sin(x) and a dummy variable x, rather than the more
logical "sigma sin", involving the function.)

But in FP, of course, functions are first class citizens. So one may get
ambiguities on account of it being reasonable to treat a particular
function either as "program" or as "data" - with conflicting outcomes. I
don't immediately see a problem with automatic lifting of the first
argument of function application, as the original poster wanted, but I
have seen a problem in the past with "apposition", or conflation of
composition and application. Suppose one wants to streamline notation, so
that instead of having to write

  (f . g) $ x

one can write

  f @ g @ x

Here, "@" means either composition or application according to context. It
is supposed to be associative, so it isn't the same as normal Haskell $;
in particular,

  f @ g

is valid and represents the composition of f and g. You might see it as
automatically lifting all "base values" (eg :: Int) to functions (:: () ->
Int) and using composition everywhere. The problem arises with
higher-order appositions;

  thrice @ thrice

(where thrice = \ f -> f . f . f) might mean either application or
composition, and the two are different in this context.

Jeremy

[EMAIL PROTECTED]
  Oxford University Computing Laboratory,    TEL: +44 1865 283508
  Wolfson Building, Parks Road,              FAX: +44 1865 273839
  Oxford OX1 3QD, UK.
  URL: http://www.comlab.ox.ac.uk/oucl/people/jeremy.gibbons.html

On Fri, 28 Jan 2005, Jacques Carette wrote:

> Tomasz Zielonka <[EMAIL PROTECTED]> wrote:
> > It's not as bad as you think. You can do this:
> >
> >     {-# OPTIONS -fglasgow-exts #-}
> >
> >     module Apply where
> >
> >     class Apply f a b | f -> a, f -> b where
> >         apply :: f -> a -> b
> >
> >     instance Apply (a -> b) a b where
> >         apply f a = f a
> >
> >     instance Apply (a1 -> b1, a2 -> b2) (a1, a2) (b1, b2) where
> >         apply (f1, f2) (a1, a2) = (f1 a1, f2 a2)
> [snip]
>
> Very nice.  But in the scrap-your-boilerplate spirit, it would be nice if one 
> could instead say
>
> instance* Apply (T (a -> b)) a b where
>      apply (T f) a = T (f a)
>
> where instance* is an instance template, and T is a ``shape functor'' (in the 
> sense of polynomial functors specifying
> an y of algebra/coalgebra/bialgebra/dialgebra).  Or maybe even go for 
> analytic functors (a la Joyal).
>
> Well, I guess it's up to me to work out the theory... [based on the work of 
> (at least) Jay, Hinze, Jeuring, Laemmel,
> Jansson and Peyton-Jones ! ]
>
> Jacques
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to