3

问:我们怎样才能摆脱SICStus Prolog中的maplist开销(如 SWI 的开销) ?apply_macros

A:目标扩展。


首先,我们定义我们需要的辅助谓词。下面我们使用 SICStus Prolog 4.5.0。

:- 模块(maplist_macros, [maplist/2, maplist/3, maplist/4, maplist/5, maplist/6, maplist/7, maplist/8, maplist/9])。

:- meta_predicate maplist(1,?), maplist(2,?,?), maplist(3,?,?,?), maplist(4,?,?,?,?), maplist(5,?,? ,?,?,?), maplist(6,?,?,?,?,?,?), maplist(7,?,?,?,?,?,?,?), maplist(8,?, ?,?,?,?,?,?,?)。

:- use_module(library(lists), [append/2, same_length/2])。
:- 使用模块(库(ordsets))。

callable_arglists_appended(C0, New, C1) :-
   C0 =.. Parts0,
   附加([零件 0|新],零件 1),
   C1 =.. 零件 1。

:- 动态 expand_goal_aux/1。
my_expand_goal(目标,扩展):-
   断言((expand_goal_aux(目标):-目标)),
   收回((expand_goal_aux(目标):- Expanded0)),
   strip_module(扩展0,_,扩展)。

strip_module(MGoal_0,模块,Goal_0):-
   aux_strip_module(MGoal_0,Goal_0,lambda,模块)。% 拉姆达?!

aux_strip_module(MG_0,G_0,M0,M):-
   (非变量(MG_0),
      MG_0 = (M1:MG1_0)
   -> aux_strip_module(MG1_0,G_0,M1,M)
   ; MG_0 = G_0,
      M0 = M
   )。

:- 动态 maplist_aux_count/1。
maplist_aux_count(0)。

现在进入目标扩展:

% 生成专门的 `maplist/N'
目标扩展(目标0,_Layout0,FromModule,FromModule:目标,[]):-
   目标0 =.. [地图列表,Rel0 | 参数],
   可调用(Rel0),
   参数 = [_|_],
   !,
   % get count # of aux preds 到目前为止生成并增加它
   收回(maplist_aux_count(C)),
   C1 是 C+1,
   断言(maplist_aux_count(C1)),

   % 构建谓词函子 `AuxPred'
   number_chars(C, C_chars),
   atom_chars(C_atom, C_chars),
   atom_concat(maplist_aux_, C_atom, AuxPred), % 例如, maplist_aux_3

   % 强制所有相关列表具有相同的长度
   列表:maplist(same_length(Args), [Vars_E,Nils]),
   列表:maplist(列表:cons,Vars_E,Vars_Es,Vars_E_Es),
   列表:maplist(=([]),尼尔斯),

   % 在正确的模块中扩展目标(`FromModule')
   strip_module(Rel0,_,Rel1),
   callable_arglists_appended(Rel1, [Vars_E], Rel2),
   my_expand_goal(FromModule:Rel2, Rel),

   % 找出需要穿线的变量
   term_variables(Rel, Vars_Schema),
   list_to_ord_set(Vars_Schema, VSet_Schema),
   list_to_ord_set(Vars_E, VSet_E),
   ord_subtract(VSet_Schema, VSet_E, VSet_Actual),

   % 使用适当的参数构建新谓词的调用
   callable_arglists_appended(AuxPred, [Args,VSet_Actual], 目标),

   % 被调用者子句(新谓词)
   callable_arglists_appended(AuxPred, [Nils, VSet_Actual], Head0), % 事实
   callable_arglists_appended(AuxPred, [Vars_E_Es,VSet_Actual], Head1), % 规则
   callable_arglists_appended(AuxPred, [Vars_Es, VSet_Actual], Rec1), %

   % 将生成的子句转储到文件中
   atom_concat('/tmp/x', C_atom, FileName), % TODO: 获取实际的 tmpfilnam
   打开(文件名,写,S),
   描绘子句(S,(Head0 :- true)),
   描绘子句(S,(Head1:- Rel,Rec1)),
   关闭(S),

   % 在适当的模块中编译临时文件
   编译(从模块:文件名)。

到目前为止一切都很好;)所以这就是问题所在......

如何确保目标扩展变体与它替换的谓词完全相同?

(我有一种预感,它不是,但我不能完全确定它......)


简单示例用例 #1

allequal(Xs) :- maplist(=(_), Xs).

变成

allequal(A) :- maplist_aux_0(A, _).

maplist_aux_0([], _).
maplist_aux_0([A|B], C) :- C=A, maplist_aux_0(B, C).
4

1 回答 1

3

最简单的解决方案可能是扩展为do/2,类似于library(lists)SICStus 中用于实现的方法maplist/n

/* -*- Mode:Prolog; coding:iso-8859-1; indent-tabs-mode:nil; prolog-indent-width:8; prolog-paren-indent:4; tab-width:8; -*- */

/*
   Replacement for maplist from library lists, that inlines the calls when possible.

   In your code, instead of doing:

   :- use_module(library(lists),[maplist/2, maplist/3, ... other non-maplist things ...]).

   Do:

   :- use_module(library(lists),[... other non-maplist things ...]).
   :- use_module(maplist_inliner, [maplist/2,maplist/3]).

 */
:- module(maplist_inliner, [maplist/2,maplist/3]).

% We can not import (and reexport) maplist/2 etc from the module 'lists' (because
% our goal_expansion will only be used from our own predicates, not predicates we reexport).
% Instead we use thin wrappers for those cases where we are unable to inline the calls to maplist.
% However, these will never be used, because we always fallback to expanding to a plain lists:maplist/n call.
:- use_module(library(lists), []).

:- meta_predicate maplist(1, +).
:- meta_predicate maplist(2, +, +).
% TODO: Add more arities

% A thin wrapper around lists:maplist/2. See module documentation for rationale.
maplist(G_1, L1) :-
        lists:maplist(G_1, L1).

% A thin wrapper around lists:maplist/3. See module documentation for rationale.
maplist(G_2, L1, L2) :-
        lists:maplist(G_2, L1, L2).


get_module(X, ModuleContext, G, M) :-
        var(X),
        !,
        G = X,
        M = ModuleContext.
get_module(M1:X, _ModuleContext, G, M) :-
        !,
        get_module(X, M1, G, M).
get_module(X, ModuleContext, G, M) :-
        !,
        G = X,
        M = ModuleContext.

:- if(fail).
goal_expansion(G, Layout0, ModuleContext, Expansion, Layout1) :-
        writeq(goal_expansion(G,Layout0,ModuleContext,Expansion,Layout1)),
        nl,
        fail.
:- endif.

goal_expansion(maplist(G, L1), _Layout0, ModuleContext, Expansion, Layout1) :-
        callable(G),
        get_module(G, ModuleContext, G_1, M),
        callable(G_1),
        atom(M),
        !,
        Layout1 = [],           % No source info
        inline_maplist_2(G_1, M, L1, Expansion).
goal_expansion(maplist(G, L1), _Layout0, ModuleContext, Expansion, Layout1) :-
        !,
        Layout1 = [],           % No source info
        Expansion = lists:maplist(ModuleContext:G,L1).


goal_expansion(maplist(G, L1, L2), _Layout0, ModuleContext, Expansion, Layout1) :-
        callable(G),
        get_module(G, ModuleContext, G_2, M),
        callable(G_2),
        atom(M),
        !,
        Layout1 = [],           % No source info
        inline_maplist_3(G_2, M, L1, L2, Expansion).
goal_expansion(maplist(G, L1, L2), _Layout0, ModuleContext, Expansion, Layout1) :-
        !,
        Layout1 = [],           % No source info
        Expansion = lists:maplist(ModuleContext:G,L1,L2).


inline_maplist_2(G_1, M, L1, Expansion) :-
        G_1 =.. [F|ClosureArgs],
        append([F|ClosureArgs], [X], G_ClosureArgs_X),
        BodyGoal =.. G_ClosureArgs_X,
        Expansion =
        (foreach(X,L1),
         param(G_1)
        do
         M:BodyGoal
        ).

inline_maplist_3(G_2, M, L1, L2, Expansion) :-
        G_2 =.. [F|ClosureArgs],
        append([F|ClosureArgs], [X1,X2], G_ClosureArgs_X1_X2),
        BodyGoal =.. G_ClosureArgs_X1_X2,
        Expansion =
        (foreach(X1,L1),
         foreach(X2,L2),
         param(G_2)
        do
         M:BodyGoal
        ).

例子

/* -*- Mode:Prolog; coding:iso-8859-1; indent-tabs-mode:nil; prolog-indent-width:8; prolog-paren-indent:4; tab-width:8; -*- */

:- use_module(maplist_inline, [maplist/2,maplist/3]).

p_1(X1) :-
        writeq(call(p_1(X1))).

p_2(X1, X2) :-
        writeq(call(p_2(X1,X2))).


p_3(X1, X2, X3) :-
        writeq(call(p_3(X1,X2,X3))).


test(L1) :-
        ClosureArg1 = 'a',
        maplist(p_2(ClosureArg1), L1).


test(L1, L2) :-
        maplist(p_2, L1, L2).


test_1(L1, Arg) :-
        maplist(p_2(Arg), L1).



test_1(L1, L2, Arg) :-
        maplist(p_3(Arg), L1, L2).


test_noinline(L1, L2, Arg) :-
        G_2 = p_3(Arg),         % Inliner will not see this
        maplist(G_2, L1, L2).

使用consult/1listing/1显示会发生什么:

bash$ /usr/local/sicstus4.5.0/bin/sicstus
SICStus 4.5.0 (x86_64-darwin-17.7.0): Thu Jan 17 17:17:35 CET 2019
Licensed to SICS
| ?- consult(test).
% ...
| ?- listing.
maplist_inliner:maplist(A, B) :-
        lists:maplist(A, B).

maplist_inliner:maplist(A, B, C) :-
        lists:maplist(A, B, C).

p_1(A) :-
        writeq(call(p_1(A))).

p_2(A, B) :-
        writeq(call(p_2(A,B))).

p_3(A, B, C) :-
        writeq(call(p_3(A,B,C))).

test(A) :-
        B=a,
        (   foreach(C, A),
            fromto(B, D, D, _)
        do  p_2(D, C)
        ).

test(A, B) :-
        (   foreach(C, A),
            foreach(D, B)
        do  p_2(C, D)
        ).

test_1(A, B) :-
        (   foreach(C, A),
            fromto(B, D, D, _)
        do  p_2(D, C)
        ).

test_1(A, B, C) :-
        (   foreach(D, A),
            foreach(E, B),
            fromto(C, F, F, _)
        do  p_3(F, D, E)
        ).

test_noinline(A, B, C) :-
        D=p_3(C),
        lists:maplist(user:user:D, A, B).

谨防。我没有测试这个超过几分钟。

于 2019-02-28T17:41:22.267 回答