ExtractableFunctors and Some HScheme Internals Explained
Ashley Yakeley
ashley@semantic.org
Wed, 04 Jun 2003 20:08:27 -0700
In article <16094.24499.796592.366278@tux-17.corp.peace.com>,
Tom Pledger <Tom.Pledger@peace.com> wrote:
> Here's my version of fmapM, which was inspired by something in Tim
> Sheard's paper "Generic Unification via Two-Level Types and
> Parameterized Modules".
Gosh well I came across something very similar completely independently:
class (Functor f) => ExtractableFunctor f where
{
fExtract :: forall g a. (FunctorApplyReturn g) =>
f (g a) -> g (f a);
};
See
<http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hbase/Source/HBase/Catego
ry/Functor.hs?rev=HEAD&content-type=text/vnd.viewcvs-markup>
Btw FunctorApplyReturn is a larger class than Monad (should be a
superclass IMO, but I'm not yet ready to define my own Monad class in
HBase). In addition to fmap it has
return' :: a -> f a
fApply :: f (a -> b) -> (f a -> f b)
...from which one can derive liftF2. This makes fExtract more general
and thus ExtractableFunctor more demanding; but I expect most of the
types that are your FunctorSeq would also be ExtractableFunctor.
So I've been using ExtractableFunctors in HScheme to handle recursive
binding macro "letrec":
data ZeroList a = MkZeroList;
data NextList t a = MkNextList a (t a);
These can be made ExtractableFunctors and allow lists where the type
indicates the length, for instance:
type List3 = NextList (NextList (NextList ZeroList));
I then use them to build up values of this type:
data MutualBindings f a v = forall t. (ExtractableFunctor t) =>
MkMutualBindings (t (f a)) (forall r. f r -> f (t v -> r));
So here "t" is the list type. "f" is my clever SymbolExpression type, an
instance of my equally clever FunctorLambda class. "a" is basically "m
SchemeObject" where m is an appropriate Monad. "v" is a reference to a
SchemeObject (simplifying here a certain amount).
Think of the SymbolExpression type as encoding lambda-terms. You can do
things such as find its free variables, etc.
The first part of the MkMutualBindings is a list of expressions found in
the "letrec" head. The second part is a function that abstracts based on
the variables listed. For instance:
(letrec
((a b) (b 3) (c a))
(+ c 1)
)
Support for this kind of recursive binding is actually more than R5RS
requires, but I thought it worth trying after I discovered how to write
the fixed-point function mfix for my continuation-passing monad.
The head of the letrec is parsed to make a MutualBindings. The first
part of the MkMutualBindings would be essentially a List3 (above) of
expressions representing "b", "3" and "a". The second part would be an
"abstracting" function that turns a SymbolExpression of anything "r" to
a SymbolExpression of a function that depended on a list of three
references, by abstracting on the symbols "a", "b", and "c".
You can kind of gloss it like this:
MkMutualBindings bindValues abstracter;
abstracter (f "(* a b c)") = f (\a b c -> "(* " ++ a ++ b ++ c ++ ")")
Having constructed the MutualBindings, I then call
foo (fExtract (fmap abstracter bindValues)) (abstracter body)
"foo" is what I'm working on currently. I had an earlier version that
only worked with the pure functional flavour of HScheme; I'm now
generalising it with mfix.
It's all in CVS...
<http://sourceforge.net/cvs/?group_id=47823>
--
Ashley Yakeley, Seattle WA