There has been a recent exchange on [EMAIL PROTECTED] 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:

 
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:
[EMAIL PROTECTED]

Reply via email to