Skip to content

Commit

Permalink
simplification (the prob of
Browse files Browse the repository at this point in the history
mc_sample(survives_action(a,[a,b,c],0,c),1000,P). is 0.312, too high, it
should be 17/63=0.26984126984)
  • Loading branch information
friguzzi committed Jun 19, 2016
1 parent 533dbad commit 5ceddfd
Showing 1 changed file with 51 additions and 47 deletions.
98 changes: 51 additions & 47 deletions examples/inference/truel.pl
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
The firing order is a, b and c. Each truelist can shoot at another truelist
or at the sky (deliberate miss). The truelist have these probabilities of
hitting the target (if they are not aiming at the sky): a 1/3, b 2/3 and c 1.
The aim for each truelist is kill all the other truelists.
The question is: what should a do to maximize his probability of living?
Aim at b, c or the sky?
Note that the best strategy for the other truelists and situations is
Expand All @@ -14,18 +15,18 @@
*/

/** <examples>
?- best_strategy(a,[b,c],[a,b,c],S).
?- best_strategy(a,[a,b,c],S).
% What is the best action for a?
% S= ($).
?- mc_sample(survives_action(a,[b,c],0,[a,b,c],b),1000,P).
% S= sky
?- mc_sample(survives_action(a,[a,b,c],0,b),1000,P).
% What is the probability that a survives if it aims at b?
% P = 0.256
?- mc_sample(survives_action(a,[b,c],0,[a,b,c],c),1000,P).
% P = 0.267
?- mc_sample(survives_action(a,[a,b,c],0,c),1000,P).
% What is the probability that a survives if it aims at c?
% P = 0.292
?- mc_sample(survives_action(a,[b,c],0,[a,b,c],'$'),1000,P).
% P = 0.312
?- mc_sample(survives_action(a,[a,b,c],0,sky),1000,P).
% What is the probability that a survives if it aims at the sky?
% P = 0.383
% P = 0.39682539682
*/
:- use_module(library(mcintyre)).

Expand All @@ -39,58 +40,56 @@

:- begin_lpad.
/**
* best_strategy(+A:atom,+Rest:list,+L:list,-S:atom).
* best_strategy(+A:atom,+L:list,-S:atom).
*
* The best strategy for truelist A with Rest remaining to shoot and
* L still alive is to aim at S (with '$' for the sky).
* The best strategy for truelist A with
* L still alive is to aim at S (with sky for the sky).
*
*/
best_strategy(A,Rest,L,S):-
best_strategy(A,L,S):-
delete(L,A,L1),
append(L1,['$'],L2),
maplist(ev_action(A,Rest,L),L2,LP),
append(L1,[sky],L2),
maplist(ev_action(A,L,0),L2,LP),
sort(LP,LP1),
reverse(LP1,[_P-S|_]).


/**
* ev_action(+A:atom,+Rest:list,+L:list,+S:atom,-C:couple).
* ev_action(+A:atom,+L:list,+T:term,+S:atom,-C:couple).
*
* Tuelist A with Rest to shoot, L still alive performing action S survives
* Tuelist A with L still alive performing action S in turn T survives
* with probability P in C=P-S.
*
*/
ev_action(A,Rest,L,S,P-S):-
mc_sample(survives_action(A,Rest,0,L,S),1000,P).
ev_action(A,L,T,S,P-S):-
mc_sample(survives_action(A,L,T,S),1000,P).

/**
* survives_action(+A:atom,+Rest0:list,+T:term,+L0:list,+S:atom)
* survives_action(+A:atom,+L0:list,+T:term,+S:atom)
*
* A survives truel performing action S at round T with Rest0 to shoot in
* the round and L0 still alive
* A survives truel performing action S with L0 still alive in turn T
*
*/
survives_action(A,Rest0,T,L0,S):-
shoot(A,S,Rest0,L0,T,Rest,L1),
survives_round(Rest,L1,A,T).
survives_action(A,L0,T,S):-
shoot(A,S,L0,T,L1),
remaining(L1,A,Rest),
survives_round(Rest,L1,A,T).

/**
* shoot(+H:atom,+S:atom,+Rest0:list,+L0:list,+T:term,-Rest:list,-L:list).
* shoot(+H:atom,+S:atom,+L0:list,+T:term,-L:list).
*
* When H shoots at S with Rest0 to shoot in round T and L0 still alive,
* the truelist to shoot in the round become Rest and the truelist still
* alive L
*/
shoot(H,S,Rest0,L0,T,Rest,L):-
(S='$' ->
L=L0,
Rest=Rest0
shoot(H,S,L0,T,L):-
(S=sky ->
L=L0
;
(hit(T,H) ->
delete(L0,S,L),
delete(Rest0,S,Rest)
delete(L0,S,L)
;
L=L0,
Rest=Rest0
L=L0
)
).

Expand Down Expand Up @@ -124,31 +123,36 @@
survives_round([],L,A,T):-
survives(L,A,s(T)).

survives_round([H|Rest],L0,A,T):-
base_best_strategy(H,Rest,L0,S),
shoot(H,S,Rest,L0,T,Rest1,L1),
survives_round([H|_Rest],L0,A,T):-
base_best_strategy(H,L0,S),
shoot(H,S,L0,T,L1),
remaining(L1,H,Rest1),
member(A,L1),
survives_round(Rest1,L1,A,T).


/**
* base_best_strategy(+A:atom,+Rest:list,+T:list,-S:atom).
* base_best_strategy(+A:atom,+T:list,-S:atom).
*
* the best action for A when Rest follow him in the round and
* T is the list of surviving truelist, is S (with '$' for the sky)
* the best action for A when
* T is the list of surviving truelist, is S
*
* These are the strategies that are easy to find (most intuitive)
*
*/
base_best_strategy(b,[c],[b,c],c).
base_best_strategy(c,[],[b,c],b).
base_best_strategy(a,[c],[a,c],c).
base_best_strategy(c,[],[a,c],a).
base_best_strategy(a,[b],[a,b],b).
base_best_strategy(b,[],[a,b],a).
base_best_strategy(b,[c],[a,b,c],c).
base_best_strategy(c,[],[a,b,c],b).
base_best_strategy(b,[b,c],c).
base_best_strategy(c,[b,c],b).
base_best_strategy(a,[a,c],c).
base_best_strategy(c,[a,c],a).
base_best_strategy(a,[a,b],b).
base_best_strategy(b,[a,b],a).
base_best_strategy(b,[a,b,c],c).
base_best_strategy(c,[a,b,c],b).

remaining([A|Rest],A,Rest):-!.

remaining([_|Rest0],A,Rest):-
remaining(Rest0,A,Rest).

:- end_lpad.

Expand Down

0 comments on commit 5ceddfd

Please sign in to comment.