[m-dev.] Laziness modules

Ralph Becket rafe at csse.unimelb.edu.au
Fri May 8 10:52:56 AEST 2009


Thanks for the feedback, Peter.

Peter Moulder, Tuesday,  5 May 2009:
> On Tue, May 05, 2009 at 05:04:53PM +1000, Ralph Becket wrote:
> > I put a couple of modules providing support for lazy computation
> > together at the weekend.  Is there any interest in adding these to the
> > library?  Laziness gives us what in the C# and Java worlds they call
> > "enumerables" and are using to good effect.
> 
> Can you comment on how this compares with
> mercury-extras/lazy_evaluation/ ?

I'm embarrassed to say I'd forgotten about that.  Fergus'
lazy.m module is better; my lazy_list.m module has more
functionality.

I propose adding Fergus' lazy.m and my lazy_list.m (with fixes)
to the standard library.
> version) corresponds to list.take_upto rather than list.take.  That
> seems unfortunate.
> 
> Similarly lazy_list.drop (in the new version; not present in
> lazy_evaluation).

I've renamed them to {take,drop}_upto for consistency.
> 
> lazy_list.take_while doesn't exactly correspond to list.takewhile:
> list.takewhile is a predicate and has an additional AfterList argument
> (the rest of the list).  However, I think I'd ignore list.takewhile
> here.
> 
> ints: Consider either documenting that the result is undefined if Hi
> is int.max_int, or make it work if Hi is int.max_int.
> 
> ints_with_step:
> 
>   Similar issue as with ints, except there are more Hi values with
>   that issue if Step > 1.
> 
>   The documentation is unclear, btw: a literal reading is that Max =
>   Hi.  (Adding the word `such' would suffice for me.)
> 
>   Also, my reading of the documentation is that ints_with_step(10, 1,
>   -1) returns a non-empty list.
> 
>   However you resolve that, consider explicitly drawing attention to
>   the behaviour if Step is non-positive.
> 
>   Copy-and-paste bug s/ints/ints_with_step/ in documentation.
> 
>   Consider using Mercury-style `=<' rather than `<=' in the
>   documentation.

Fixed all of these.

> > multiple_of(X, Y) :- Y mod X = 0.
> 
> Suggest s/mod/rem/.  (I know it's intended to be simple rather than
> efficient, but I don't consider mod as clearly simpler than rem.
> Though I've no strong objection to mod if you prefer it.)

Done.

Here's the updated lazy_list.m module:

%-----------------------------------------------------------------------------%
% lazy_list.m
% Ralph Becket <rafe at csse.unimelb.edu.au>
% Fri Apr 17 15:50:59 EST 2009
% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
%
% Simple lazy list evaluation.
%
%-----------------------------------------------------------------------------%

:- module lazy_list.

:- interface.

:- import_module int.
:- import_module lazy.
:- import_module list.

    % The type of lazy lists.
    %
:- type lazy_list(T)
    --->    empty_lazy_list
    ;       lazy_list(T, lazy(lazy_list(T))).

    % The lazy list constructor.
    %
:- func cons(T, (func) = lazy_list(T)) = lazy_list(T).

    % The lazy list deconstructor.
    %
:- pred decons(lazy_list(T)::in, T::out, lazy_list(T)::out) is semidet.

    % Convert between ordinary lists and lazy lists.
    %
:- func list_to_lazy_list(list(T)) = lazy_list(T).

:- func lazy_list_to_list(lazy_list(T)) = list(T).

    % Append, map, filter, fold, take, drop for lazy lists.
    %
:- func lazy_list(T) ++ lazy_list(T) = lazy_list(T).

:- func map(func(T1) = T2, lazy_list(T1)) = lazy_list(T2).

:- func filter(pred(T)::in(pred(in) is semidet), lazy_list(T)::in) =
        (lazy_list(T)::out) is det.

:- func filter_out(pred(T)::in(pred(in) is semidet), lazy_list(T)::in) =
        (lazy_list(T)::out) is det.

:- func foldl(func(T1, T2) = T2, lazy_list(T1), T2) = T2.

:- func foldr(func(T1, T2) = T2, lazy_list(T1), T2) = T2.

:- func foldr_lazy(func(T1, lazy(T2)) = T2, lazy_list(T1), T2) = T2.

    % take_upto(N, Xs) is the first N items of Xs or Xs itself if it has
    % fewer than N items.
    %
:- func take_upto(int, lazy_list(T)) = lazy_list(T).

    % drop_upto(N, Xs) is the remainder of Xs after the first N items have
    % been removed or the empty list if Xs has fewer than N items.
    %
:- func drop_upto(int, lazy_list(T)) = lazy_list(T).

    % The following take or drop elements of a lazy_list while/until
    % an item satisfying some condition is found.
    %
:- func take_while(pred(T)::in(pred(in) is semidet), lazy_list(T)::in) =
        (lazy_list(T)::out) is det.

:- func drop_while(pred(T)::in(pred(in) is semidet), lazy_list(T)::in) =
        (lazy_list(T)::out) is det.

:- func take_until(pred(T)::in(pred(in) is semidet), lazy_list(T)::in) =
        (lazy_list(T)::out) is det.

:- func drop_until(pred(T)::in(pred(in) is semidet), lazy_list(T)::in) =
        (lazy_list(T)::out) is det.

% Lazy integer sequences.

    % ints(Lo, Hi) is the lazy_list [Lo, Lo + 1, ..., Hi].
    %
:- func ints(int, int) = lazy_list(int).

    % ints(Lo, Hi, Step) is the lazy_list [Lo, Lo + Step, ..., Max]
    % where Max is the largest integer =< Hi.
    % The result is empty_lazy_list if Hi < Lo.
    % The result is undefined if Step is negative.
    %
:- func ints_with_step(int, int, int) = lazy_list(int).

    % ints_from(Lo) is the lazy_list [Lo, Lo + 1, ...].
    %
:- func ints_from(int) = lazy_list(int).

    % ints_with_step(Lo, Step) is the lazy_list [Lo, Lo + Step, ...].
    % The result is undefined if Step is negative.
    %
:- func ints_from_with_step(int, int) = lazy_list(int).

%-----------------------------------------------------------------------------%

:- implementation.

%-----------------------------------------------------------------------------%

cons(X, Susp) = lazy_list(X, delay(Susp)).

%-----------------------------------------------------------------------------%

decons(lazy_list(X, LLXs), X, force(LLXs)).

%-----------------------------------------------------------------------------%

list_to_lazy_list([]) = empty_lazy_list.

list_to_lazy_list([X | Xs]) =
    lazy_list(X, delay((func) = list_to_lazy_list(Xs))).

%-----------------------------------------------------------------------------%

lazy_list_to_list(empty_lazy_list) = [].

lazy_list_to_list(lazy_list(X, LXs)) = [X | lazy_list_to_list(force(LXs))].

%-----------------------------------------------------------------------------%

empty_lazy_list ++ Ys = Ys.

lazy_list(X, LXs) ++ Ys = cons(X, (func) = force(LXs) ++ Ys).

%-----------------------------------------------------------------------------%

map(_, empty_lazy_list) = empty_lazy_list.

map(F, lazy_list(X, LXs)) = cons(F(X), (func) = map(F, force(LXs))).

%-----------------------------------------------------------------------------%

filter(_, empty_lazy_list) = empty_lazy_list.

filter(P, lazy_list(X, LXs)) =
    ( if P(X) then
        cons(X, (func) = filter(P, force(LXs)))
      else
        filter(P, force(LXs))
    ).

%-----------------------------------------------------------------------------%

filter_out(_, empty_lazy_list) = empty_lazy_list.

filter_out(P, lazy_list(X, LXs)) =
    ( if P(X) then
        filter_out(P, force(LXs))
      else
        cons(X, (func) = filter_out(P, force(LXs)))
    ).

%-----------------------------------------------------------------------------%

foldl(_, empty_lazy_list, A) = A.

foldl(F, lazy_list(X, LXs), A) = foldl(F, force(LXs), F(X, A)).

%-----------------------------------------------------------------------------%

foldr(_, empty_lazy_list, A) = A.

foldr(F, lazy_list(X, LXs), A) = F(X, foldr(F, force(LXs), A)).

%-----------------------------------------------------------------------------%

foldr_lazy(_, empty_lazy_list, A) = A.

foldr_lazy(F, lazy_list(X, LXs), A) =
    F(X, delay((func) = foldr_lazy(F, force(LXs), A))).

%-----------------------------------------------------------------------------%

take_upto(N, Xs) =
    ( if N > 0, Xs = lazy_list(X, LXs) then
        cons(X, (func) = take_upto(N - 1, force(LXs)))
      else
        empty_lazy_list
    ).

%-----------------------------------------------------------------------------%

drop_upto(N, Xs) =
    ( if N > 0, Xs = lazy_list(_, LXs) then
        drop_upto(N - 1, force(LXs))
      else
        Xs
    ).

%-----------------------------------------------------------------------------%

take_while(_, empty_lazy_list) = empty_lazy_list.

take_while(P, lazy_list(X, LXs)) =
    ( if P(X) then
        cons(X, (func) = take_while(P, force(LXs)))
      else
        empty_lazy_list
    ).

%-----------------------------------------------------------------------------%

drop_while(_, empty_lazy_list) = empty_lazy_list.

drop_while(P, Xs @ lazy_list(X, LXs)) =
    ( if P(X) then
        drop_while(P, force(LXs))
      else
        Xs
    ).

%-----------------------------------------------------------------------------%

take_until(_, empty_lazy_list) = empty_lazy_list.

take_until(P, lazy_list(X, LXs)) =
    ( if P(X) then
        empty_lazy_list
      else
        cons(X, (func) = take_until(P, force(LXs)))
    ).

%-----------------------------------------------------------------------------%

drop_until(_, empty_lazy_list) = empty_lazy_list.

drop_until(P, Xs @ lazy_list(X, LXs)) =
    ( if P(X) then
        Xs
      else
        drop_until(P, force(LXs))
    ).

%-----------------------------------------------------------------------------%

ints(Lo, Hi) =
    ( if ( Lo =< Hi ; Lo = int.max_int ) then
        cons(Lo, (func) = ints(Lo + 1, Hi))
      else
        empty_lazy_list
    ).

ints_with_step(Lo, Hi, Step) =
    ( if Lo =< Hi then
        ( if int.max_int - Step < Lo then
            cons(Lo, (func) = empty_lazy_list)
          else
            cons(Lo, (func) = ints_with_step(Lo + Step, Hi, Step))
        )
      else
        empty_lazy_list
    ).

ints_from(Lo) =
    cons(Lo, (func) = ints_from(Lo + 1)).

ints_from_with_step(Lo, Step) =
    cons(Lo, (func) = ints_from_with_step(Lo + Step, Step)).

%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at csse.unimelb.edu.au
Administrative Queries: owner-mercury-developers at csse.unimelb.edu.au
Subscriptions:          mercury-developers-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the developers mailing list