functions not in type classes

Lauri Alanko la@iki.fi
Fri, 18 Jan 2002 20:33:45 +0200


On Fri, Jan 18, 2002 at 12:27:09AM -0800, Ashley Yakeley wrote:
> Well, what classes should such functions as const, id and (.) be members 
> of?
> 
> const :: a -> b -> a;
> const x y = x;
> 
> id :: a -> a;
> id x = x;
> 
> (.) :: (b -> c) -> (a -> b) -> (a -> c);
> (.) f g x = f (g x);

Arrows, of course. :) In fact, this is directly from my personal,
somewhat tweaked arrow library:

class Arrow z where
    arr :: (a -> b) -> z a b
    -- at least two of >>>, >>>= and first must must be defined
    -- (preferably >>> and first, or things get slow...)
    (>>>) :: z a b -> z b c -> z a c
    a >>> b = a >>>= first b >>>= arr (\((a,_),_) -> a)
    (>>>=) :: z a b -> z (b,a) c -> z a c
    a >>>= b = save a >>> b
    first :: z a b -> z (a, c) (b, c)
    first a = (fst >>> a) >>>= arr (\(b,(a,c)) -> (b,c))
    id :: z a a
    id = arr (P.id)
    const :: a -> z q a
    const a = arr (P.const a)

The idea is that arrows that id-arrows and const-arrows can be given
specialized implementations. For instance, we can have a direct term
implementation for the arrows:

data Term z a b 
    = Arr (a -> b)
    | Lift (z a b)
    | forall q . Term z a q :>>> Term z q b
    | forall q r s . First (Term z a (q,s)) (Term z q r) (Term z (r,s) b)
    | Id (Term z a b)
    | Label String (Term z a b)
    | Const b
    | Null -- unsafe

instance Arrow z => Arrow (Term z) where
    arr f = Arr f
    a >>> b = a :>>> b
    first a = First Null a Null
    const = Const
    id = Id Null

And then one can optimize them right inside the Haskell program:

reduce :: Arrow z => Term z a b -> Term z a b
reduce (Const a :>>> Arr b) = reduce (Const (b a))
reduce (Arr a :>>> Const b) = reduce (Const b)
reduce (Arr a :>>> Arr b) = reduce (Arr (b . a))
-- ...

And after optimization run it again as a real arrow:

runTerm :: Arrow z => Term z a b -> z a b
runTerm (Arr f) = arr f
runTerm (Lift z) = z
runTerm (a :>>> b) = runTerm a >>> runTerm b
-- ...

I never actually pursued this idea to the end, though, so I don't know
if this would be useful in practice. But still, it's a neat idea, and
gives a reason why const should be in a class. :)


Lauri Alanko
la@iki.fi