Lazy evaluation in Mercury
Fergus Henderson
fjh at cs.mu.OZ.AU
Wed Mar 10 10:43:39 AEDT 1999
This started off on the Clean mailing list, but I'm cross-posting to the
mercury-users mailing list too.
On 08-Mar-1999, Zuurbier, E. - AMSXE <Erik.Zuurbier at KLM.NL> wrote:
> > > But what about the other way around? What would a Mercury
> > > programmer do with lazy Clean algorithms to implement them
> > > in Mercury? If it is a mere syntax conversion, or some straight
> > > forward transformation, that is great. Tell me where I can read more
> > > about it.
> >
> > It is indeed basically just a syntax conversion. See
> > <http://www.cs.mu.oz.au/~lee/papers/eq/>, in particular section 7 of
> > the tech report there. This deals with adding support for functions
> > and lazy evaluation to NU-Prolog, via a simple pre-processor.
> >
> This is not what I mean. Rather: What would a programmer do today
> with Mercury as it is today, when given a (Clean/Haskell) algorithm
> that makes use of laziness. For instance the algorithms in the famous
> paper "Why Functional Programming Matters" by John Hughes.
Oh, the programmer would apply the kind of syntactic transformation described
above by hand. If you only need call-by-name rather than call-by-need,
then it is quite straight-forward to do this -- the transformation is
quite simple.
> Does Mercury (today) have specific logic features that easily make up
> for the absence of lazy evaluation? Would John Hughes' algorithms be
> easy to code in Mercury today?
Yes, particularly if you only need call-by-name.
You can define a module with the following interface:
:- module lazy.
:- interface.
% lazy(T) is an abstract type representing a
% lazily-evaluated value of type T
:- type lazy(T).
% :- inst lazy.
% convert a value from type T to lazy(T)
:- func val(T) = lazy(T).
:- mode val(in) = out(lazy) is det.
% construct a lazily-evaluated lazy(T) from a closure.
:- func delay((func) = T) = lazy(T).
:- mode delay((func) = out is det) = out(lazy) is det.
% force the evaluation of a lazy(T), and return the result as type T.
:- func force(lazy(T)) = T.
:- mode force(in(lazy)) = out is det.
Then you use the type `lazy(T)' instead of `(T)' whenever you want
lazy evaluation. The only thing you then need to do is to insert
some explicit calls to convert between these, i.e. writing `value(X)'
or `delay((func) = R :- R = X)' to convert from T to lazy(T) eagerly
or lazily, respectively, and writing `force(X)' to convert from lazy(T)
to a T. The type checker will tell you when you need those.
With this interface, you can for example use
:- type lazy_list(T) ---> [] ; [T | lazy(lazy_list(T))].
to implement lazy lists.
You can implement this interface quite easily:
% Mercury doesn't have abstract insts, so we have to put these insts
% in the interface. (The user can't make any non-abstract use
% of them, fortunately, because the type is abstract.)
:- inst lazy == lazy(ground).
:- inst lazy(I) ---> value(I) ; closure((func) = out(I) is det).
:- implementation.
:- type lazy(T) ---> value(T) ; closure((func) = T).
val(X) = value(X).
delay(X) = closure(X).
force(value(X)) = X.
force(closure(F)) = apply(F).
This implementation does have a couple of drawbacks. One is that
attempts to unify two values of type lazy(T) will not do the right
thing. The other is that it only gives you call-by-name rather
than call-by-need.
However, it is possible to remedy those drawbacks. I enclose a
complete implementation below. I must confess that I haven't tested
it yet, but it compiles, and therefore it probably works ;-)
This is also IMHO a very good candidate for the standard library.
Cheers,
Fergus.
P.S. I expect that this would probably be quite a bit less efficient
than lazy evaluation in Haskell or Clean. One reason is that
in the current implementation of Mercury, promise_only_solution/1
(which we need to use in the implementation of force/1)
imposes a significant and unnecessary efficiency cost.
Another reason is simply that in Haskell and Clean, lazy evaluation
is implemented at a much lower level, and compilers go to great lengths
to optimize it.
%-----------------------------------------------------------------------------%
:- module lazy.
:- interface.
% a lazily-evaluted value of type T
:- type lazy(T).
% convert a value from type T to lazy(T)
:- func val(T) = lazy(T).
:- mode val(in) = out(lazy) is det.
% construct a lazily-evaluated lazy(T) from a closure.
:- func delay((func) = T) = lazy(T).
:- mode delay((func) = out is det) = out(lazy) is det.
% force the evaluation of a lazy(T), and return the result as type T.
:- func force(lazy(T)) = T.
:- mode force(in(lazy)) = out is det.
% The following may be needed occaisionally, in case
% the compiler can't infer the right higher-order inst...
:- func inst_cast(lazy(T)) = lazy(T).
:- mode inst_cast(in) = out(lazy) is det.
%---------------------------------------------------------------------%
% implementation details
:- inst lazy(I) ---> value(I) ; closure((func) = out(I) is det).
:- inst lazy == lazy(ground).
:- implementation.
% Note that we use a user-defined equality predicate to ensure
% that unifying two lazy(T) values will do the right thing.
:- type lazy(T) ---> value(T) ; closure((func) = T)
where equality is equal_values.
:- pred equal_values(lazy(T), lazy(T)).
:- mode equal_values(in, in) is semidet.
equal_values(X, Y) :-
force(inst_cast(X)) = force(inst_cast(Y)).
:- pragma c_code(inst_cast(F::in) = (F2::out(lazy)),
[will_not_call_mercury, thread_safe], "F = F2;").
%---------------------------------------------------------------------%
val(X) = value(X).
delay(F) = closure(F).
% If the compiler were to evaluate calls to delay/1 at compile time,
% it could put the resulting closure/1 term in read-only memory,
% which would make destructively updating it rather dangerous.
% So we'd better not let the compiler inline delay/1.
:- pragma no_inline(delay/1).
%---------------------------------------------------------------------%
% The call to promise_only_solution is needed to tell the
% compiler that force will return equal answers given
% arguments that are equal but that have different representations.
force(Lazy) = promise_only_solution(do_force(Lazy)).
:- pred do_force(lazy(T), T).
:- mode do_force(in(lazy), out) is cc_multi.
% The pragma promise_pure is needed to tell the compiler that
% do_force is pure, even though it calls impure code.
:- pragma promise_pure(do_force/2).
do_force(Lazy, Value) :-
(
Lazy = value(Value)
;
Lazy = closure(Func),
Value = apply(Func),
% Destructively update the closure with a new
% closure that immediately returns the same value,
% to avoid having to recompute the same result
% next time.
NewFunc = ((func) = Result :- Result = Value),
impure update_closure(Lazy, NewFunc)
).
:- impure pred update_closure(T1, T2).
:- mode update_closure(in, in) is det.
% Note that the implementation of this impure predicate relies on
% some implementation details of the Mercury implementation.
:- pragma c_code(
update_closure(MercuryTerm::in, NewValue::in),
[will_not_call_mercury],
"{
/* strip off tag bits */
Word *ptr = (Word *) strip_tag(MercuryTerm);
/* destructively update value */
*ptr = NewValue;
}").
%-----------------------------------------------------------------------------%
--
Fergus Henderson <fjh at cs.mu.oz.au> | "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3 | -- the last words of T. S. Garp.
More information about the users
mailing list