You selected trade.pl

headline:-
   write('% --------------------------------------------------------- %'),nl,
   write('%     simulating common knowledge and speculative trade.    %'),nl,
   write('% --------------------------------------------------------- %'),nl,
   write(' trader/5 to simulate the trade negotiation procces.'),nl,
   write('  trader(Type,Agent,Time_and_State,ProbWin,Reply).'),nl,
   write('  ex.1,'),nl,
   write('   ?- trader(sophist,J,S,Q,D).'),nl,
   write('  ex.2,'),nl,
   write('   ?- trader(rational,J,(T,S),Q,D).'),nl.
me:-
   write('% file: trade.pl.'),nl,
   write('% created: 16-19 Jan 2003.'),nl,
   write('% modified: 22-26 Jan 2003.'),nl,
   write('% modified: 11 Feb 2003.'),nl,
   write('% author: Kenryo INDO (Kanto Gakuen University) '),nl,
   write('% url: http://www.us.kanto-gakuen.ac.jp/indo/front.html'),nl.
references:-
   write('% references:'),nl,
   write('% [1] Aumann, R. J. (1976). Agreeing to disagree.'),nl,
   write('%   Annals of Statistics 4: 1236-1239.'),nl,
   write('% [2] Geanakoplos, J. (1992). Common knowledge.'),nl,
   write('%   Journal of Economic Perspective  6: 53-82.'),nl,
   write('%   also in R. J. Aumann and S. Hart (eds.),'),nl,
   write('%   Handbook of Game Theory 2: 1437-1496, 1994.'),nl,
   write('% [3] Milgrom, P. and N. Stokey (1982). Information, trade '),nl,
   write('%   and common knowledge. Journal of Economic Theory 26: 17-27.'),nl,
   write('% [4] Sebenius, J. K. Geanakoplos, J. (1983). Dont bet on it:'),nl,
   write('%   contingent agreements with aymmetric information.'),nl,
   write('%   Journal of American Statistical Association 78(382): 424-426.'),
   nl.

:- dynamic  true_state/1.
:- dynamic  said/3.
:- dynamic  said/4.

:- headline.

model_of_trader(X):-
   member(X,[ex_ante,naive,sophist,rational]).

uts(S):-
   update_true_state(S).
update_true_state(S):-
   state(S),
   abolish(true_state/1),
   assert(true_state(S)).

make_public(S):-
   state(S),
   assert(said(public,0,is_impossible(S))).

%
% -------------------------------------------------  %
%  knowledge operators via possibility correspondences. 
% -------------------------------------------------  %
% added: 25 Jan 2003. 
% However, these four predicates are not used in trade.pl
know_event_when(J,E,K):-
   agent(J),
   event(E),
   setof(S,
     H^(
      partition(J,S,H),
      subset(H,E)
     ),
   K).
dont_know_event_when(J,E,DK):-
   agent(J),
   event(DK),
   DK \= [],
   event(E),
   E \= [],
   \+ know_event_when(J,E,DK).
think_possible_when(J,E,P):-
   agent(J),
   event(E),
   setof(S,
     H^(
      partition(J,S,H),
      intersection(H,E,M),
      M\=[]
     ),
   P).
think_impossible_when(J,E,U):-
   think_possible_when(J,E,P),
   all_states(O),
   subtract(O,P,U),
   U\=[],
   event(U).
%
% -------------------------------------------------  %
%  state, agent, information (partition),
%  and possibility correspondences
% -------------------------------------------------  %
true_state(s3).
all_agents([1,2]).
all_states([s1,s2,s3,s4,s5]).
agent(J):-all_agents(Is),member(J,Is).
state(S):-all_states(Ss),member(S,Ss).
%
%                state   s1 s2 s3 s4 s5
% ---------------------------------------------
%  Partition of 1 (P1)    1a  1b  1b  1c  1c
%  Partition of 2 (P2)    2x  2x  2y  2y  2z
% ---------------------------------------------
%  Fig.2 partitions of Milgrom and Stokey's example.
%
%/*
partition(1,s1,[s1]).
partition(1,S,[s2,s3]):-member(S,[s2,s3]).
partition(1,S,[s4,s5]):-member(S,[s4,s5]).
partition(2,S,[s1,s2]):-member(S,[s1,s2]).
partition(2,S,[s3,s4]):-member(S,[s3,s4]).
partition(2,s5,[s5]).
%*/
%
% a nested example inspired by Rubinstein and Wolinsky(1990)
% which induce speculative trades everywhere. 
%
/*
partition(1,s1,[s1,s2,s3,s5]).
partition(1,S,[s2,s3]):-member(S,[s2,s3]).
partition(1,s4,[s4,s5]).
partition(1,s5,[s5]).
partition(2,s1,[s1]).
partition(2,s2,[s1,s2]).
partition(2,S,[s3,s4]):-member(S,[s3,s4]).
partition(2,s5,[s1,s3,s4,s5]).
%
*/
think(J,S,is_impossible(O)):-
   agent(J),
   state(S),
   state(O),
   \+ think(J,S,is_possible(O)).
think(J,S,is_possible(O)):-
   agent(J),
   state(S),
   partition(J,S,H),
   member(O,H),
   \+ said(public,0,is_impossible(O)).
think(J,S,K):-
   K = think(_J1,O,_O1),
   think(J,S,is_possible(O)),
   K.
%
test_think(S,S1,X,M):-
   X=[S1,S2,S3,S4,S5,S6],
   (M==fix->(
    S1=s1,
    S2=s1,
    S3=s2,
    S4=s3,
    S5=s4,
    S6=s5
   );true),
   think(1, S1,
     think(2, S2,
       think(1, S3,
         think(2, S4,
           think(1, S5,
             think(2, S6,
               is_possible(S)
             ) 
           )
         )
       )
     )
   ).
%
%            probability of transfer
%     sate     q1(1->2)   q2(2->1)    p(q2|S)    p(S)   
%    -----------------------------------------------------
%      s1       .20        .05         1/5       .25    
%      s2       .05        .15         3/4       .20    
%      s3       .05        .05         1/2       .10    
%      s4       .15        .05         1/4       .20    
%      s5       .05        .20         4/5       .25    
%    -----------------------------------------------------
%    Fig.1 trade example of Milgrom and Stokey(1982).

% -------------------------------------------------  %
%  probability and game payoffs of the trade
% -------------------------------------------------  %
%
%/*
probability(w1,s1, 0.20).
probability(w1,s2, 0.05).
probability(w1,s3, 0.05).
probability(w1,s4, 0.15).
probability(w1,s5, 0.05).
probability(w2,s1, 0.05).
probability(w2,s2, 0.15).
probability(w2,s3, 0.05).
probability(w2,s4, 0.05).
probability(w2,s5, 0.20).
%*/
/*
probability(w1,s1, 0.10).
probability(w1,s2, 0.05).
probability(w1,s3, 0.15).
probability(w1,s4, 0.15).
probability(w1,s5, 0.05).
probability(w2,s1, 0.05).
probability(w2,s2, 0.15).
probability(w2,s3, 0.15).
probability(w2,s4, 0.05).
probability(w2,s5, 0.10).
*/
test_prob(P):-
    findall(A,probability(_W,_S,A),Ps),
    sum(Ps,P).
probability(S, P):-
    state(S),
    findall(A,probability(_W,S,A),Ps),
    sum(Ps,P).
%
% game_outcome and payoff
% -----------------------------------------------------------  %
payoff(agent(J),win,1):-agent(J).
payoff(agent(J),loose,-1):-agent(J).
game_outcome(w1,agent(1),loose).
game_outcome(w1,agent(2),win).
game_outcome(w2,agent(1),win).
game_outcome(w2,agent(2),loose).
%
% expected payoff (if no information is available)
% -----------------------------------------------------------  %
expected_payoff(J,S,E):-
    game_outcome(W,agent(J),O),
    probability(W,S,P),
    payoff(agent(J),O,U),
    E is P * U.
expected_payoff(J,V):-
    agent(J),
    findall(E,
      (
       expected_payoff(J,_S,E)
      ),
    H),
    sum(H,V).
%
% conditional probability and conditional expectation
% -----------------------------------------------------------  %
probability_of_event(W,E,P):-
    event(E1), % conditionalization by event specified directly
    (var(E)->E = E1; sort(E,E1)),
    G = member(S,E1),
    findall(A,(probability(W,S,A),G),Ps),
    sum(Ps,P).
probability_of_event(W,E,P,G):-
    \+ var(G), % conditionalization via constraints indirectly
    G=(Goal,M,[W,S,A]),  % constraints with params
    findall([S1,A1],
      (
       (M=do->(W=W1,S=S1,A=A1);true),
       probability(W1,S1,A1),
       Goal
      ),
    Xs),
    findall(S,member([S,A],Xs),E0),
    findall(A,member([S,A],Xs),Ps),
    sort(E0,E),
    sum(Ps,P).
%
% below was not used in trade.pl
conditional_probability(S,P,E):-
    state(S),
    event(E1), 
    (var(E)->E = E1; sort(E,E1)),
    findall(A,conditional_probability(_W,S,A,E),Ps),
    sum(Ps,P).
conditional_probability(W,S,P,E):-
    probability(W,S,P1),
    event(E1),
    (var(E)->E = E1; sort(E,E1)),
    (\+ member(S,E)
     -> P=0
     ;
      (
       probability_of_event(W,E,P0),
       P is P1 / P0
      )
    ).
conditional_probability(W,S,P,E,G):-
    probability(W,S,P1),
    event(E1),
    (var(E)->E = E1; sort(E,E1)),
    (\+ member(S,E)
     -> P=0
     ;
      (
       probability_of_event(_W0,E,P0,G),
       P is P1 / P0
      )
    ).
%
conditional_expected_payoff(J,S,V,H):-
    game_outcome(W,agent(J),O),
    conditional_probability(W,S,P,H),
    payoff(agent(J),O,U),
    V is P * U.
conditional_expected_payoff(J,V,H):-
    agent(J),
    event(H),
    findall(E,
      (
       conditional_expected_payoff(J,_S,E,H)
      ),
    V0),
    sum(V0,V).
%
% -------------------------------------------------  %
%  ex ante expectation of win
% -------------------------------------------------  %
win_prob(J,S, Q):-
    state(S),
    game_outcome(W,agent(J),win),
    probability(W,S,Q1),
    probability(S,P0),
    Q is Q1 / P0.
win_prob(J,S, Q):-
    true_state(0),
    win_prob(J,S, Q).
win_prob_on_event(J,H, Q):-
    event(H),
    \+ H = [],
    probability_of_event(_,H,P0),
    game_outcome(W,agent(J),win),
    probability_of_event(W,H,P1),
    Q is P1 / P0.
%
% -------------------------------------------------  %
%  decision criteria (common)
% -------------------------------------------------  %
is_probability(Q):-
   (
    (
     number(Q),
     Q >= 0,
     Q =< 1
    )
    -> true;
    (
     write('invalid value of probability.'),
     fail
    )
   ).
decision(Q,D):-
    is_probability(Q),
    (
     Q > 0.5 -> D = ok;
     Q = 0.5 -> D = indifferent;
     D = reject
    ).
%
% -------------------------------------------------  %
%  model of trader (1) --- naive expectation
% -------------------------------------------------  %
trader(naive,J,S,Q,D):-
    state(S),
    partition(J,S,H),
    win_prob_on_event(J,H, Q),
    decision(Q,D).
%
% -------------------------------------------------  %
%  model of trader (2) --- 2nd order expectation
%   with a sort of certainty reasoning 
% -------------------------------------------------  %
trader(sophist,J,S,Q,D):-
   trader(naive,J,S,Q,D0),
   (
    (
     D0 = ok,
     partition(J,S,H),
     \+ (
      member(S1,H),
      agent(J1),
      J1 \= J,
      trader(naive,J1,S1,_Q1,reject),
      write(trader(naive,J1,S1,_Q1,reject))
     )
    )
    ->
     D = D0
    ;
     D=reject
   ).
%
% -------------------------------------------------  %
%  model of trader (3) --- 
%  expectation under common knowledge of rationality 
% -------------------------------------------------  %
% iterative message exchange reveals private information. 
trader(rational,J,(T,S),Q,D):-
   state(S),
   time(T/N),
   T > 0,
   agent(J),
   move(J,T/N,yes),
   %T1 is T - 1,
   delay(T,1,T1),
   partition(J,T1/N,S,H),
   win_prob_on_event(J,H, Q),
   decision(Q,D).
%
%-----------------------------------------------
/*  the supporting evidence of state   */
%-----------------------------------------------
is_consistent_with_information(T,S,O):-
   time(T/_N),
   state(S),
   state(O),
   agent(J),
   trader(rational,J,(T,S),_Q,D),  % real.
   trader(rational,J,(T,O),_Q1,D).  % expected.
%
%*********************************
/* cited from ck01.pl  */
%*********************************
%
% -------------------------------------------------  %
%  event, (static) knowledge, and reachability
% -------------------------------------------------  %
event(E):-
   all_states(O),
   subset_of(E,_N,O).
know(J,S,E):-
   agent(J),
   state(S),
   partition(J,S,H),
   event(E),
   subset(H,E).
% 
% -------------------------------------------------  %
%  common knowledge via meet of partitions
% -------------------------------------------------  %
meet_of_partitions([J],[S],H):-
   partition(J,S,H).
meet_of_partitions([J|Js],[S|Ss],M):-
   meet_of_partitions(Js,Ss,M1),
   partition(J,S,H),
   \+ cyclic(J/Js,S/Ss),
   \+ subset(H,M1),
   intersection(M1,H,H12),
   H12 \= [],
   union(H,M1,M2),
   sort(M2,M).
%
%-----------------------------------------------
/*  time and  act of agent : message process   */
%-----------------------------------------------
time(0/N):- last_time(N).
time(T/N):- last_time(N),length(L,N), nth1(T,L,T).
all_times(Ts):- findall(T,time(T),Ts).
delay(T,1,T1):- all_times(Ts), nth0(T,Ts,T/N),T\=N,nth1(T,Ts,T1/N).
delay(T,1,T1):- last_time(T), T1 is T - 1.
delay(T,D,T1):- \+var(D), D >1,delay(T,1,T2), D1 is D - 1, delay(T2,D1,T1).

last_time(7).
move(J,0/N,no):-
   time(0/N), 
   agent(J).
move(J,T/N,yes):-
   time(T/N), 
   T > 0,
   %T1 is T - 1,
   delay(T,1,T1),
   agent(J),
   all_agents(Is),
   length(Is,NL),
   J is T1 mod NL + 1.
%
%-----------------------------------------------
/*  dynamic knowledge updated by messages   */
%-----------------------------------------------
partition(J,T/N,S,H):-
   time(T/N),
   partition(J,S,H1),
   remove_impossible_states(J,T/N,S,H1,H).
%
know(J,T/N,S,E):-
   time(T/N),
   agent(J),
   state(S),
   partition(J,T/N,S,H),
   % remove_impossible_states(J,T/N,S,E,H), 
   (length(H,1)->E=H;true),
   event(E),
   subset(H,E).
%
remove_impossible_states(J,T/N,S,E,H):-
   time(T/N),
   agent(J),
   state(S),
   event(E),
   findall(X,
      think(J,T/N,S,is_impossible(X)),
   D),
   subtract(E,D,F),
   sort(F,H).
%
think(J,T/N,S,is_impossible(O)):-
   agent(J),
   time(T/N),
   state(S),
   state(O),
   \+ think(J,T/N,S,is_possible(O)).
%
think(J,0/N,S,is_possible(O)):-
   time(0/N),
   think(J,S,is_possible(O)).
think(J,T/N,S,is_possible(O)):-
   time(T/N),
   T \= 0,
   %T1 is T - 1,
   delay(T,1,T1),
   think(J,T1/N,S,is_possible(O)),
   is_consistent_with_information(T,S,O).
%
%-----------------------------------------------
/*  utilities   */
%-----------------------------------------------
bag0([],_A,0).
bag0([C|B],A,N):-
   length([C|B],N),
   bag0(B,A,_N1),
   member(C,A).
zeros(Zero,N):-bag0(Zero,[0],N).
ones(One,N):-bag0(One,[1],N).
%
% subset_of/3 : subset-enumeration 
% -----------------------------------------------------------  %
subset_of(A,N,As):-
   length(As,L),
   length(D,L),
   list_projection(D,As,B),
   length(B,N),
   sort(B,A).
% a sequence of binary choice for a list:
%--------------------------------------------------
list_projection([],[],[]).
list_projection([X|Y],[_A|B],C):-
   X = 0,
   list_projection(Y,B,C).
list_projection([X|Y],[A|B],[A|C]):-
   X = 1,
   list_projection(Y,B,C).
% sum
% -----------------------------------------------------------  %
sum([],0).
sum([X|Members],Sum):-
   sum(Members,Sum1),
  %number(X),
   Sum is Sum1 + X.
%
% product
% -----------------------------------------------------------  %
product([],1).
product([X|Members],Z):-
   product(Members,Z1),
  %number(X),
   Z is Z1 * X.
%
% weighted sum
% -----------------------------------------------------------  %
product_sum([],[],[],0).
product_sum([P|Q],[A|B],[E|F],V):-
    length(Q,N),
    length(B,N),
    product_sum(Q,B,F,V1),
    E is P * A,
    V is V1 + E.

% -------------------------------------------------  %
% alias -- if you like
% -------------------------------------------------  %
pr(W,S,P):-
    probability(W,S,P).
xpf(J,S,E):-
    expected_payoff(J,S,E).
prev(W,E,P):-
    probability_of_event(W,E,P).
prev(W,E,P,G):-
    probability_of_event(W,E,P,G).
cpr(W,S,P,E):-
    conditional_probability(W,S,P,E).
cxpf(J,S,V,H):-
    conditional_expected_payoff(J,S,V,H).
cxpf(J,V,H):-
    conditional_expected_payoff(J,V,H).
%
icwi(T,S,O):-
   is_consistent_with_information(T,S,O).
mops(Js,Ss,M):-
   meet_of_partitions(Js,Ss,M).
% it is relatively difficult to find a path of enumerating states.
test_mops(B,C,N):-
   mops([1,2,3,1,2,3,1],B,C),
   length(C,N).
rimps(J,T/N,S,E,H):-
   remove_impossible_states(J,T/N,S,E,H).
%
%----a utility but not used
%
display_trader(S,[Type1,Type2],[P1,P2],X):-
   write('%----------------------------------% '),
   nl,
   write('  Under the true state '),
   write(S),
   write(','),
   nl,
   write(' the traders of a pair of types <'),
   write((Type1,Type2)),
   write('>  '),
   nl,
   write(' and each of who has the expectation of win  '),
   write((P1,P2)),
   nl,
   write(' respectively, '),
   write(X),
   write('.'),
   nl,
   write('%----------------------------------% '),
   nl.
%
%end


return to front page.