1/*
    2Computing the probability of success of an attack to the Bitcoin protocol
    3From Damiano Azzolini, Fabrizio Riguzzi, Evelina Lamma, Elena Bellodi, 
    4and Riccardo Zese.  
    5Modeling bitcoin protocols with probabilistic logic programming. 
    6PLP 2018 http://ceur-ws.org/Vol-2219/paper6.pdf
    7 
    8*/
    9:- use_module(library(mcintyre)).   10:- mc.   11:- begin_lpad.   12
   13% progress function
   14attacker_progress_poisson(X):poisson(X,Lambda):-
   15   Lambda is 10*0.3/0.7.
   16attacker_progress_negative_binomial(X):negative_binomial(X,10,0.3).
   17
   18move(T,1):0.7; move(T,-1):0.3.
   19
   20% catch up function
   21walk(InitialPosition):-
   22  	walk(InitialPosition,0).
   23
   24walk(0,_).
   25walk(X,T0):-
   26    X > 0, 
   27    X < 100, %threshold for not winning
   28    move(T0,Move),
   29    T1 is T0+1,
   30    X1 is X+Move,
   31    walk(X1,T1).
   32
   33success_poisson:-
   34    attacker_progress_poisson(A),
   35    V is 10 - A,
   36    (   V = 0 ->  
   37    	true;
   38    	walk(V)
   39    ).
   40
   41success_negative_binomial:-
   42    attacker_progress_negative_binomial(A),
   43    V is 10 - A,
   44    (   V = 0 ->  
   45    	true;
   46    	walk(V)
   47    ).
   48
   49:- end_lpad.

?- mc_prob(success_poisson,Prob). ?- mc_prob(success_negative_binomial,Prob). */