You selected repu0.pl


data_of_this_program([
  line('%-------------------------------------------------------%'),
  title('reputation model by Kreps and Wilson(1982).'),
  line('%-------------------------------------------------------%'),
  program_name('repu0.pl'),
  created(date('9-10 May 2003'),by('Kanto Gakuen University')),
  reference(author('Kreps, D. M. and R. Wilson (1982)')),
  reference(title('Reputation and imperfect information')),
  reference(journal('Journal of Economic Theory 27: 253-279.')),
  line('%-------------------------------------------------------%'),
  main_predicate:make_script
]).

:- data_of_this_program(X),forall(member(T,X),(nl,write(T))).


:- dynamic game_script /1.
:- dynamic game_script /2.
:- dynamic history_of_play /3.
:- dynamic reason_of_play /3.

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%    the enterant-monopolist game model
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

model_parameter(b(0.5)).
model_parameter(a(2)).

first_stage(10).
stage(T):-
   first_stage(N),
   anum_seq1(A,N),
   reverse(A,B),
   member(T,B).

player(1,entrant).
player(2,monopolist(Type)):- member(Type,[weak,strong]).
play(entrant,exit).
play(entrant,entry).
play(monopolist(_),X->acquiescence):-play(entrant,X).
play(monopolist(_),X->fight):-play(entrant,X).


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%    basic data of the game 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% scripts of the game plays
%(these are not always on the sequential equilibrium path.)

game_script(auto(0)).  % dummy data
game_script(no(1)).

game_script(no(1),history_of_play(1,entrant,exit)).
game_script(no(1),history_of_play(2,entrant,exit)).
game_script(no(1),history_of_play(3,entrant,entry)).
game_script(no(1),history_of_play(4,entrant,entry)).
game_script(no(1),history_of_play(5,entrant,entry)).
game_script(no(1),history_of_play(6,entrant,entry)).
game_script(no(1),history_of_play(7,entrant,exit)).
game_script(no(1),history_of_play(8,entrant,exit)).
game_script(no(1),history_of_play(9,entrant,exit)).
game_script(no(1),history_of_play(10,entrant,exit)).
game_script(no(1),history_of_play(1,monopolist(_),fight)).
game_script(no(1),history_of_play(2,monopolist(_),fight)).
game_script(no(1),history_of_play(3,monopolist(_),fight)).
game_script(no(1),history_of_play(4,monopolist(_),fight)).
game_script(no(1),history_of_play(5,monopolist(_),fight)).
game_script(no(1),history_of_play(6,monopolist(_),fight)).
game_script(no(1),history_of_play(7,monopolist(_),fight)).
game_script(no(1),history_of_play(8,monopolist(_),fight)).
game_script(no(1),history_of_play(9,monopolist(_),fight)).
game_script(no(1),history_of_play(10,monopolist(_),fight)).

set_script(N,Script):-
  abolish(history_of_play/3),
  game_script(N),
  findall(H,game_script(N,H),Script),
  forall(member(H,Script),assert(H)).



kth_entry(before(T),stage(T1),met_by(A)):-
   stage(T),
   history_of_play(T1,entrant,entry),
   T1 > T,
   history_of_play(T1,monopolist(_),A).

last_entry(before(T),stage(T1),met_by(A)):-
   kth_entry(before(T),stage(T1),met_by(A)),
   \+ (
     kth_entry(
       before(T),
       stage(T2),
       met_by(_)
     ),
     T2 > T,
     T1 > T2
   ).

next_stage(T D = P; D=(DZ=P)).


% alternative modeling.
%-----------------------------------

prob(L,[D],[]):-
   first_stage(L),
   initial_reputation(D).

prob(T,X,H):-
   next_stage(TB),
   prob_1(T 0,
   model_parameter(b(B)),
   D2 = B^T,
   max_of(D,[D1,D2]).

prob_1(_Tfight):-
   stage(T),
   history_of_play(T,entrant,DoX).
strategy(T,monopolist(weak),Case,DoX->DoY):-
   stage(T), 
   prob(T,[P|_],_),
   model_parameter(b(B)),
   D1 = B^(T-1),
   history_of_play(T,entrant,DoX),
   decision_rule(monopolist(weak),case([T,P,D1],Case),DoX->DoY).


%----------- case-based decision criteria

decision_rule(entrant,case([P,D],Case),exit):-
   Case = [current_belief(P) > critical_level(D)],
   P > D.
decision_rule(entrant,case([P,D],Case),entry):-
   Case = [current_belief(P) < critical_level(D)],
   P < D.
decision_rule(entrant,case([P,D],Case),Y):-
   Case = [
     current_belief(P) = critical_level(D), 
     random(X,'%'), critical_level(100/A,'%')
   ],
   P = D,
   model_parameter(a(A)),
   X is random(101),(nl,write(random(X))),
   (X > 100/A -> Y=entry; Y=exit),!. 

decision_rule(monopolist(weak),case([_,_,_],C),exit->fight):-
   C = ['to make exit and deter.'].
decision_rule(monopolist(weak),case([1,_,_],C),entry->acquiescence):-
   C = ['entry at last.'].
decision_rule(monopolist(weak),case([T,P,D],C),entry->fight):-
   C = [
     entry_at_stage(T) > 1,
     current_belief(P) > critical_level(D)
   ],
   T > 1,
   P > D.
decision_rule(monopolist(weak),case([T,P,D],C),entry->Z):-
   C = [
     entry_at_stage(T) > 1,
     current_belief(P) < critical_level(D),
     random(X,'%'), fight_prob(FightProb)
   ],
   T > 1,
   P < D,
   FightProb = ((1-D) * P)/((1-P) * D),
   PF is FightProb,
   X is random(101),(nl,write(random(X))),
   (X > 100 * PF -> Z=fight; Z=acquiescence),!. 


%----------- make a sequence of decision

strategy_path(J,S,DP):-
   player(_,J),
   play(J,S),
   findall(T,(stage(T),strategy(T,J,_,S)),DP).


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%    simulating strategies
%     with knowledge level explanations
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% by working the players' strategies above into play,
% this code generates a set of predicates of 
% history_of_play / 3 along the stages.


% ----  simulation at the behavior-level:
% make_script /0,1

create_new_script(N):-
   game_script(auto(N0)),
   \+ (game_script(auto(N1)),N1>N0),
   N is N0 + 1,
   assert(game_script(auto(N))).

init_script(N,M,M_not):-
   (var(M)->hear_user(type_of_monopolist(M));true),
   findall(Y, (player(_,monopolist(Y)),Y \= M),M_not),
    nl, write((M,M_not)),
   create_new_script(N).

make_script(N,T,J,Do):-
   H = history_of_play(T,J,Do),
   assert(H),
   assert(game_script(N,H)).

make_reason(N,T,J,Case):-
   R = reason_of_play(T,J,Case),
   assert(R),
   assert(game_script(N,R)).

make_script(M):-
   init_script(N,M,M_not),
   abolish(history_of_play/3),
   abolish(reason_of_play/3),
   forall(
     (
      stage(T),
      player(_,J),
      \+ (J=monopolist(TYM),member(TYM,M_not)) 
     ),
     (
      strategy(T,J,Case,Do),
      make_script(N,T,J,Do),
      make_reason(N,T,J,Case)
     )
   ),
   listing(history_of_play),
   hear_user(reason_of_play).

make_script:-
   hear_user(type_of_monopolist(M)),
   make_script(M).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%    user interface
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

% ----  inputs from user 

hear_user(type_of_monopolist(M)):-
   nl,
   write('Please specify the type of monopolist either weak or strong:'),
   read(M1),
   (\+ player(_,monopolist(M1))
     ->
      (
       nl,
       write(' no such type of monopolist. please re-try.'),
       hear_user(type_of_monopolist(M))
      )
     ; M = M1
   ).

hear_user(reason_of_play):-
   nl,
   write('Display the reasoning for the plays above? (all/spec/no):'),
   read(Y1),
   (member(Y1,[n,'N',no,'No','NO',q,quit,e,end])
        ->fail; true
   ),
   hear_user(reason_of_play(Y1)),!,
   nl,
   write('-----------end of explanation----------'),
   hear_user(reason_of_play).

hear_user(reason_of_play(Y1)):-
   (member(Y1,[y,'Y',yes,'Yes','YES'])
     ->
      (
       write('please re-enter as either all, stage, or no.'),
       hear_user(reason_of_play)
      )
     ;
      explain_reason_of_play(Y1)
   ).

hear_user((stage(S),player(J))):-
   hear_user(stage(S)),
   hear_user(player(J)).

hear_user(stage(Stage)):-
   nl,
   write('Type the number of the stage: '),
   read(S),
   (stage(S)->Stage=S;hear_user(stage(Stage))).

hear_user(player(Player)):-
   nl,
   write('Type the player: '),
   read(J),
   (
    (
     (player(J,N),Player=N);
     (player(_,J),Player=J)
    )
     ;hear_user(player(Player))
   ).


% ----  explanations for user 

explain_reason_of_play(All):-
   \+ var(All),
   All =all,
   forall(
     history_of_play(T,J,S),
     explain_reason_of_play(T,J,S,_)
   ).

explain_reason_of_play(Spec):-
   (
    (var(Spec);member(Spec,[spec,s]))
     ->
       hear_user((stage(S),player(J)))
     ;
      fail 
   ),
   explain_reason_of_play(S,J,_,_).

explain_reason_of_play(T,J,S,C):-
   history_of_play(T,J,S),
   reason_of_play(T,J,C),
   nl,
   write((J,at_stage:T,played:S)),
   nl,
   tab(1),
   write('because:'),
   forall(member(R,C),(nl,tab(2),write(R))).




%------------------------------------------------
%  mathematical utiliteis
%------------------------------------------------
max_of(X,[X]).
max_of(Z,[X|Y]):-
   max_of(Z1,Y),
   (X > Z1 -> Z=X; Z=Z1).
min_of(X,[X]).
min_of(Z,[X|Y]):-
   min_of(Z1,Y),
   (X < Z1 -> Z=X; Z=Z1).
dnum_seq([],N):-N<0,!.
dnum_seq([0],1).
dnum_seq([A|Q],N):-
   A is N - 1,
   length(Q,A),
   dnum_seq(Q,A).
anum_seq(Aseq,N):-dnum_seq(Dseq,N),sort(Dseq,Aseq).

dnum_seq1(Q,N):-
   M is N + 1,
   dnum_seq(Q0,M),
   subtract(Q0,[0],Q).
anum_seq1(Q,N):-
   M is N + 1,
   anum_seq(Q0,M),
   subtract(Q0,[0],Q).

return to front page.