7:- use_module(library(mcintyre)). 8:- if(current_predicate(use_rendering/1)). 9:- use_rendering(c3). 10:- endif. 11:- mc. 12
13:- begin_lpad. 14
15citations(AverageCit,_,Cit):poisson(Cit,AverageCit).
16
17h_index(NumPapers,AverageCit,HIndex):-
18 numlist(1,NumPapers,Papers),
19 maplist(citations(AverageCit),Papers,Citations),
20 sort(0, @>=, Citations, Sorted),
21 compute_index(Sorted,1,HIndex).
22
23compute_index([0|_],_,0):-!.
24
25compute_index([],I0,I):-!,
26 I is I0-1.
27
28compute_index([I|_T],I,I):-!.
29
30compute_index([H|_T],I0,I):-
31 H<I0,!,
32 I is I0-1.
33
34compute_index([H|T],I0,I):-
35 H>I0,
36 I1 is I0+1,
37 compute_index(T,I1,I).
38
39
40
41:- end_lpad. 42
43h_vs_avg_cit(Papers,MaxAvg,Chart):-
44 findall(E,(
45 between(1,MaxAvg,N),mc_expectation(h_index(Papers,N,T),10,T,E)
46 ),V),
47 numlist(1,MaxAvg,X),
48 findall(N,(between(1,MaxAvg,N0),N is 5+N0),Dep),
49 Chart=c3{data:_{x:x, columns:[[x|X],['Expected h-index'|V],['Dependency'|Dep]]}}.
?-
mc_sample_arg_first(h_index(200,10,H),1000,H,HList)
,density(HList,Dens,[nbins(20)])
. compute the distribution of the h_index given that the authors wrote 200 papers and each paper receives on average 10 citations ?-mc_expectation(h_index(200,10,H),1000,H,HExp)
. compute the expected value of the h_index given that the authors wrote 200 papers and each paper receives on average 10 citations ?-mc_sample_arg_first(citations(10,200,Cit),1000,Cit,CitList)
,density(CitList,Dens,[nbins(20)])
. ?-h_vs_avg_cit(100,40,Chart)
. Plot of the depedency of the expected h-index as a function of the average number of citations per article (max 40) given that there are 100 papers. The graphs shows that the expected h-index is directly proportional to the average number of citations (expected h-index=avg. n. cit. +5) */