using composition with multiple argument functions

Dean Herington heringto@cs.unc.edu
Fri, 01 Feb 2002 13:45:39 -0500


--------------3ACCDB33A3FCEC45D905D456
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

There has been a recent exchange on pragprog@yahoogroups.com about
expressing composition of functions where the inner function takes more
than one argument.  (When the inner function takes a single argument,
the (.) operator does quite nicely, of course.)  Here's a way, using
Haskell language extensions (options "-98" for Hugs, "-fglasgow-exts"
for GHC) to express such composition:

class Composable f g r | f g -> r where
  ( # ) :: f -> g -> r

instance Composable (a->z) a z
 where   f # g  = f g
instance Composable (b->z) (a->b) (a->z)
 where  (f # g) a = f (g a)
instance Composable (c->z) (a->b->c) (a->b->z)
 where  (f # g) a b = f (g a b)
instance Composable (d->z) (a->b->c->d) (a->b->c->z)
 where  (f # g) a b c = f (g a b c)
instance Composable (e->z) (a->b->c->d->e) (a->b->c->d->z)
 where  (f # g) a b c d = f (g a b c d)
instance Composable (f->z) (a->b->c->d->e->f) (a->b->c->d->e->z)
 where  (f # g) a b c d e = f (g a b c d e)

notelem :: (Eq a) => a -> [a] -> Bool
notelem = not # elem


However, I don't understand why the following fails to compile:

instance Composable (c->d->z) (a->b->(c,d)) (a->b->z)
 where  (f # g) a b = let (c,d) = g a b in f c d

f1, g1 :: a -> a -> (a,a)
f1 c d = (d,c)
g1 a b = (a,b)
h1 :: (a -> a -> (a,a)) -> (a -> a -> (a,a)) -> (a -> a -> (a,a))
h1 = f1 # g1

Hugs reports:

ERROR "Composition.hs" (line 52): Cannot justify constraints in
explicitly typed binding
*** Expression    : h1
*** Type          : (a -> a -> (a,a)) -> (a -> a -> (a,a)) -> a -> a ->
(a,a)
*** Given context : ()
*** Constraints   : Composable (b -> b -> (b,b)) (c -> c -> (c,c)) ((a
-> a -> (a,a)) -> (a -> a -> (a,a)) -> a -> a -> (a,a))

GHC's report is wordier but seems to be saying about the same thing.

Anyone have any ideas?

--Dean Herington


John Hughes wrote:

>      From: Martin DeMello
>
>      I played about a bit with the (.) operator, but couldn't
>      manage, frinstance,
>      to express
>
>        notelem :: Eq a => a -> [a] -> Bool
>        notelem = \x -> not . (elem x)
>
>      without the lambda.
>
> Simple!     notelem = (not.) . elem (opinions differ on whether or not
> this is readable...) John Hughes
>
>
> To unsubscribe from this group, send an email to:
> pragprog-unsubscribe@yahoogroups.com

--------------3ACCDB33A3FCEC45D905D456
Content-Type: text/html; charset=us-ascii
Content-Transfer-Encoding: 7bit

<!doctype html public "-//w3c//dtd html 4.0 transitional//en">
<html>
<body bgcolor="#FFFFFF">
There has been a recent exchange on pragprog@yahoogroups.com about expressing
composition of functions where the inner function takes more than one argument.&nbsp;
(When the inner function takes a single argument, the (.) operator does
quite nicely, of course.)&nbsp; Here's a way, using Haskell language extensions
(options "-98" for Hugs, "-fglasgow-exts" for GHC) to express such composition:
<p>class Composable f g r | f g -> r where
<br>&nbsp; ( # ) :: f -> g -> r
<p>instance Composable (a->z) a z
<br>&nbsp;where&nbsp;&nbsp; f # g&nbsp; = f g
<br>instance Composable (b->z) (a->b) (a->z)
<br>&nbsp;where&nbsp; (f # g) a = f (g a)
<br>instance Composable (c->z) (a->b->c) (a->b->z)
<br>&nbsp;where&nbsp; (f # g) a b = f (g a b)
<br>instance Composable (d->z) (a->b->c->d) (a->b->c->z)
<br>&nbsp;where&nbsp; (f # g) a b c = f (g a b c)
<br>instance Composable (e->z) (a->b->c->d->e) (a->b->c->d->z)
<br>&nbsp;where&nbsp; (f # g) a b c d = f (g a b c d)
<br>instance Composable (f->z) (a->b->c->d->e->f) (a->b->c->d->e->z)
<br>&nbsp;where&nbsp; (f # g) a b c d e = f (g a b c d e)
<p>notelem :: (Eq a) => a -> [a] -> Bool
<br>notelem = not # elem
<br>&nbsp;
<p>However, I don't understand why the following fails to compile:
<p>instance Composable (c->d->z) (a->b->(c,d)) (a->b->z)
<br>&nbsp;where&nbsp; (f # g) a b = let (c,d) = g a b in f c d
<p>f1, g1 :: a -> a -> (a,a)
<br>f1 c d = (d,c)
<br>g1 a b = (a,b)
<br>h1 :: (a -> a -> (a,a)) -> (a -> a -> (a,a)) -> (a -> a -> (a,a))
<br>h1 = f1 # g1
<p>Hugs reports:
<p>ERROR "Composition.hs" (line 52): Cannot justify constraints in explicitly
typed binding
<br>*** Expression&nbsp;&nbsp;&nbsp; : h1
<br>*** Type&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; : (a
-> a -> (a,a)) -> (a -> a -> (a,a)) -> a -> a -> (a,a)
<br>*** Given context : ()
<br>*** Constraints&nbsp;&nbsp; : Composable (b -> b -> (b,b)) (c -> c
-> (c,c)) ((a -> a -> (a,a)) -> (a -> a -> (a,a)) -> a -> a -> (a,a))
<p>GHC's report is wordier but seems to be saying about the same thing.
<p>Anyone have any ideas?
<p>--Dean Herington
<br>&nbsp;
<p>John Hughes wrote:
<blockquote TYPE=CITE>
<blockquote 
style="PADDING-RIGHT: 0px; PADDING-LEFT: 5px; MARGIN-LEFT: 5px; BORDER-LEFT: #000000 2px solid; MARGIN-RIGHT: 0px">
<div 
  style="BACKGROUND: #e4e4e4; FONT: 10pt arial; font-color: black"><b>From:</b>
<a href="mailto:martindemello@yahoo.com" title="martindemello@yahoo.com">Martin
DeMello</a></div>
&nbsp;
<br><tt>I played about a bit with the (.) operator, but couldn't manage,
frinstance,</tt>
<br><tt>to express</tt>
<p><tt>&nbsp; notelem :: Eq a => a -> [a] -> Bool</tt>
<br><tt>&nbsp; notelem = \x -> not . (elem x)</tt>
<p><tt>without the lambda.</tt></blockquote>
<font face="Courier">Simple!</font>&nbsp;<font face="Courier">&nbsp;&nbsp;&nbsp;
notelem = (not.) . elem</font>&nbsp;<font face="Courier">(opinions differ
on whether or not this is readable...)</font>&nbsp;<font face="Courier">John
Hughes</font>
<p><br><tt>To unsubscribe from this group, send an email to:</tt>
<br><tt>pragprog-unsubscribe@yahoogroups.com</tt></blockquote>

</body>
</html>

--------------3ACCDB33A3FCEC45D905D456--