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

Reply via email to