How to multiply all elements of two lists with each other in Prolog

后端 未结 5 1122
终归单人心
终归单人心 2021-01-22 00:12

I am thinking how to multiply all elements of two list with each other. Then I want to put all results in List3. For example,

List1 = [1,3,5].
List         


        
相关标签:
5条回答
  • 2021-01-22 00:44

    Why not

    prod(L1, L2, LP) :-
        bagof(P, X^Y^(member(X, L1), member(Y, L2), P is X * Y), LP).
    
    0 讨论(0)
  • 2021-01-22 00:44

    Use dcg! "Cross product"—shown here—is just one of many applications. Proceed like this:

    :- meta_predicate xproduct(4,?,?,?).
    xproduct(P_4,As) -->
       xproduct(P_4,As,As).
    
    :- meta_predicate xproduct(4,?,?,?,?).
    xproduct(P_4,As,Bs) -->
       xproduct_aux1(As,Bs,P_4).                % use 1st argument indexing for As
    
    :- meta_predicate xproduct_aux1(?,?,4,?,?).
    xproduct_aux1([]    ,_ , _ ) --> [].
    xproduct_aux1([A|As],Bs,P_4) -->
       xproduct_aux2(Bs,[A|As],P_4).            % use 1st argument indexing for Bs
    
    :- meta_predicate xproduct_aux2(?,?,4,?,?).
    xproduct_aux2([],_,_) --> [].
    xproduct_aux2([B|Bs],As,P_4) -->
       xproduct_(As,[B|Bs],P_4).
    
    :- meta_predicate xproduct_(?,?,4,?,?).
    xproduct_([],_,_) --> [].
    xproduct_([A|As],Bs,P_4) -->
        xprod_(Bs,A,P_4),
        xproduct_(As,Bs,P_4).
    
    :- meta_predicate xprod_(?,?,4,?,?).
    xprod_([],_,_) --> [].
    xprod_([B|Bs],A,P_4) -->
        call(P_4,A,B),
        xprod_(Bs,A,P_4).
    

    Let's use clpfd and lambdas to run the query you provided in your question:

    :- use_module([library(clpfd),library(lambda)]).
    
    ?- phrase(xproduct(\X^Y^[Z|Zs]^Zs^(Z #= X*Y),[1,3,5],[2,6,7]),Fs).
    Fs = [2,6,7,6,18,21,10,30,35].
    

    Above lambdas use difference-lists explicitly; with phrase//1 we can also use them implicitly!

    ?- phrase(xproduct(\X^Y^phrase(([Z],{Z #= X*Y})),[1,3,5],[2,6,7]),Fs).
    Fs = [2,6,7,6,18,21,10,30,35].
    

    clpfd enables us to do very general queries. Thanks to @PauloMoura for his suggestion! Look!

    ?- phrase(xproduct(\X^Y^phrase(([Z],{Z #= X*Y})),As,Bs),
              [2,6,7,6,18,21,10,30,35]),
       maplist(labeling([]),[As,Bs]).
      As = [-2,-6,-7,-6,-18,-21,-10,-30,-35], Bs = [-1]
    ; As = [ 2, 6, 7, 6, 18, 21, 10, 30, 35], Bs = [ 1]
    ; As = [-1,-3,-5],                        Bs = [-2,-6,-7]
    ; As = [ 1, 3, 5],                        Bs = [ 2, 6, 7]
    ; As = [-1],                              Bs = [-2,-6,-7,-6,-18,-21,-10,-30,-35]
    ; As = [ 1],                              Bs = [ 2, 6, 7, 6, 18, 21, 10, 30, 35]
    ; false.
    
    0 讨论(0)
  • 2021-01-22 00:49

    Here is a rather straight-forward solution using library(lambda)

    product(Xs, Ys, Ps) :-
       maplist(Ys+\X^maplist({X,Ys}+\Y^YP^(YP=X*Y),Ys), Xs, PPs),
       append(PPs, Ps).
    

    So we have an outer-loop for Xs and an inner loop for Ys.

    ?- product([1,2,3],[4,5,6],Ps).
    Ps = [1*4,1*5,1*6,2*4,2*5,2*6,3*4,3*5,3*6].
    

    Replace (YP=X*Y) by (YP is X*Y) or (YP #= X*Y). Whatever you prefer.

    0 讨论(0)
  • 2021-01-22 00:53

    Well,First take a look on this question executing operation for each list element in swi-prolog and others to know how to do for-each operation on lists.
    Second, here is the code:

    prod(X,[],[]).
    prod(X,[HEAD|TAIL],L) :-  prod(X,TAIL,L1), W is X * HEAD, L = [W|L1].
    
    prod2([],Y,[]).
    prod2([HEAD|TAIL],Y,L) :- prod(HEAD,Y,L1), prod2(TAIL,Y,L2), append(L1,L2,L).
    

    output:

    ?- prod2([1,3,5] ,[2,6,7],G).
    G = [2, 6, 7, 6, 18, 21, 10, 30, 35] .
    
    0 讨论(0)
  • 2021-01-22 01:04

    A simple solution not requiring any Prolog extensions (but, of course, loosing the potential benefits of using CLP(FD)) would be:

    product(List1, List2, Product) :-
        % save a copy of the second list
        product(List1, List2, List2, Product).
    
    product([], _, _, []).
    product([X| Xs], List2, Rest2, Product) :-
        (   Rest2 == [] ->
            product(Xs, List2, List2, Product)
        ;   Rest2 = [Y| Ys],
            Z is X * Y,
            Product = [Z| Zs],
            product([X| Xs], List2, Ys, Zs)
        ).
    

    This solution is tail-recursive and doesn't leave spurious choice-points.

    0 讨论(0)
提交回复
热议问题