JHUGen MELA  v2.4.1
Matrix element calculations as used in JHUGen. MELA is an important tool that was used for the Higgs boson discovery and for precise measurements of its structure and interactions. Please see the website https://spin.pha.jhu.edu/ and papers cited there for more details, and kindly cite those papers when using this code.
Functions/Subroutines
NNPDFDriver.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine nnpdfdriver (gridfilename, lenfilename)
 
subroutine nninitpdf (irep)
 
subroutine readpdfset (gridfilename, lenfilename)
 
subroutine nnevolvepdf (x, Q, xpdf)
 
subroutine lh_polin2 (x1a, x2a, ya, m, n, x1, x2, y, dy)
 
subroutine lh_polint (xa, ya, n, x, y, dy)
 

Function/Subroutine Documentation

◆ lh_polin2()

subroutine lh_polin2 ( real(8), dimension(mmax)  x1a,
real(8), dimension(nmax)  x2a,
real(8), dimension(mmax,nmax)  ya,
integer  m,
integer  n,
real(8)  x1,
real(8)  x2,
real(8)  y,
real(8)  dy 
)

Definition at line 268 of file NNPDFDriver.f.

268  implicit none
269 !
270  integer m,n,nmax,mmax
271  integer j,k
272  parameter(nmax=1e3,mmax=1e3)
273 
274  real(8) dy,x1,x2,y,x1a(mmax),x2a(nmax),ya(mmax,nmax)
275  real(8) ymtmp(nmax),yntmp(nmax)
276 
277  do j=1,m
278  do k=1,n
279  yntmp(k)=ya(j,k)
280  enddo
281  call lh_polint(x2a,yntmp,n,x2,ymtmp(j),dy)
282  enddo
283  call lh_polint(x1a,ymtmp,m,x1,y,dy)
284 !
285  return

◆ lh_polint()

subroutine lh_polint ( real(8), dimension(nmax)  xa,
real(8), dimension(nmax)  ya,
integer  n,
real(8)  x,
real(8)  y,
real(8)  dy 
)

Definition at line 289 of file NNPDFDriver.f.

289  implicit none
290 !
291  integer n,NMAX
292 ! Largest anticipated value of n
293  parameter(nmax=1e3)
294  real(8) dy,x,y,xa(nmax),ya(nmax)
295  integer i,m,ns
296  real(8) den,dif,dift,ho,hp,w,c(nmax),d(nmax)
297  ns=1
298  dif=abs(x-xa(1))
299  do 11 i=1,n
300  dift=abs(x-xa(i))
301  if(dift.lt.dif) then
302  ns=i
303  dif=dift
304  endif
305  c(i)=ya(i)
306  d(i)=ya(i)
307  11 enddo
308  y=ya(ns)
309  ns=ns-1
310  do m=1,n-1
311  do i=1,n-m
312  ho=xa(i)-x
313  hp=xa(i+m)-x
314  w=c(i+1)-d(i)
315  den=ho-hp
316  if(den.eq.0) then
317  write(*,*)'failure in polint'
318  stop
319  endif
320  den=w/den
321  d(i)=hp*den
322  c(i)=ho*den
323  enddo
324  if(2*ns.lt.(n-m)) then
325  dy=c(ns+1)
326  else
327  dy=d(ns)
328  ns=ns-1
329  endif
330  y=y+dy
331  enddo
332 
333  return

◆ nnevolvepdf()

subroutine nnevolvepdf ( double precision  x,
double precision  Q,
double precision, dimension(-6:7)  xpdf 
)

Definition at line 138 of file NNPDFDriver.f.

138  implicit none
139 
140  integer i,j,ix,iq2,M,N,ipdf,fmax
141  integer minx,maxx,midx
142  integer minq,maxq,midq
143  double precision x,Q,xpdf(-6:7),Q2
144  double precision xmingrid,xch,x2,x1,dy,y
145  parameter(m=4, n=2)
146  parameter(xmingrid=1d-7, xch=1d-1)
147 
148  integer nmax,mmax
149  parameter(nmax=1e3,mmax=1e3)
150  integer ix1a(mmax), ix2a(nmax)
151  double precision x1a(mmax), x2a(nmax)
152  double precision ya(mmax,nmax)
153 
154  integer nfl,nx,nq2,mem,rep
155  double precision alphas
156  double precision xgrid(100),logxgrid(100)
157  double precision q2grid(50),logq2grid(50)
158  double precision pdfgrid(0:100,14,100,50)
159  logical hasphoton
160  common /nnpdf/nfl,nx,nq2,mem,rep,hasphoton,alphas,xgrid,logxgrid,
161  1 q2grid,logq2grid,pdfgrid
162 
163 
164  q2 = q*q
165 * check bounds
166  if (x.lt.xmingrid.or.x.lt.xgrid(1).or.x.gt.xgrid(nx)) then
167  write(6,*) "Parton interpolation: x out of range -- freezed"
168  if (x.lt.xgrid(1)) x = xgrid(1)
169  if (x.lt.xmingrid) x = xmingrid
170  if (x.gt.xgrid(nx))x = xgrid(nx)
171  endif
172  if (q2.lt.q2grid(1).or.q2.gt.q2grid(nq2)) then
173  write(6,*) "Parton interpolation: Q2 out of range -- freezed"
174  if (q2.lt.q2grid(1)) q2 = q2grid(1)
175  if (q2.gt.q2grid(nq2)) q2 = q2grid(nq2)
176  endif
177 
178  minx = 1
179  maxx = nx+1
180  10 continue
181  midx = (minx+maxx)/2
182  if (x.lt.xgrid(midx)) then
183  maxx=midx
184  else
185  minx=midx
186  endif
187  if ((maxx-minx).gt.1) go to 10
188  ix = minx
189 
190  minq = 1
191  maxq = nq2+1
192  20 continue
193  midq = (minq+maxq)/2
194  if (q2.lt.q2grid(midq)) then
195  maxq=midq
196  else
197  minq=midq
198  endif
199  if ((maxq-minq).gt.1) go to 20
200  iq2 = minq
201 
202 * Assign grid for interpolation. M, N -> order of polyN interpolation
203  do i=1,m
204  if(ix.ge.m/2.and.ix.le.(nx-m/2)) ix1a(i) = ix - m/2 + i
205  if(ix.lt.m/2) ix1a(i) = i
206  if(ix.gt.(nx-m/2)) ix1a(i) = (nx - m) + i
207 
208 * Check grids
209  if(ix1a(i).le.0.or.ix1a(i).gt.nx) then
210  write(6,*) "Error in grids! "
211  write(6,*) "I, IXIA(I) = ",i, ix1a(i)
212  call exit(-10)
213  endif
214  enddo
215 
216  do j=1,n
217  if(iq2.ge.n/2.and.iq2.le.(nq2-n/2)) ix2a(j) = iq2 - n/2 + j
218  if(iq2.lt.n/2) ix2a(j) = j
219  if(iq2.gt.(nq2-n/2)) ix2a(j) = (nq2 - n) + j
220 * Check grids
221  if(ix2a(j).le.0.or.ix2a(j).gt.nq2) then
222  write(6,*) "Error in grids! "
223  write(6,*) "J, IXIA(J) = ",j,ix2a(j)
224  call exit(-10)
225  endif
226  enddo
227 
228 * Define points where to evaluate interpolation
229 * Choose between linear or logarithmic (x,Q2) interpolation
230 
231  IF(x.LT.xch)THEN
232  x1=dlog(x)
233  ELSE
234  x1=x
235  ENDIF
236  x2=dlog(q2)
237 
238 * initialize output vector
239  do i=-6,7
240  xpdf(i) = 0
241  enddo
242 
243  fmax = 6
244  if (nfl.eq.14) fmax=7
245 
246  DO ipdf = -6,fmax,1
247 * Choose between linear or logarithmic (x,Q2) interpolation
248  DO i=1,m
249  IF(x.LT.xch)THEN
250  x1a(i)= logxgrid(ix1a(i))
251  ELSE
252  x1a(i)= xgrid(ix1a(i))
253  ENDIF
254  DO j=1,n
255  x2a(j) = logq2grid(ix2a(j))
256  ya(i,j) = pdfgrid(rep,ipdf+7,ix1a(i),ix2a(j))
257  enddo
258  enddo
259 
260 ! 2D polynomial interpolation
261  call lh_polin2(x1a,x2a,ya,m,n,x1,x2,y,dy)
262  xpdf(ipdf) = y
263  enddo
264 

◆ nninitpdf()

subroutine nninitpdf ( integer  irep)

Definition at line 50 of file NNPDFDriver.f.

50  implicit none
51  integer irep
52 
53  integer nfl,nx,nq2,mem,rep
54  double precision alphas
55  double precision xgrid(100),logxgrid(100)
56  double precision q2grid(50),logq2grid(50)
57  double precision pdfgrid(0:100,14,100,50)
58  logical hasphoton
59  common /nnpdf/nfl,nx,nq2,mem,rep,hasphoton,alphas,xgrid,logxgrid,
60  1 q2grid,logq2grid,pdfgrid
61 
62  if (irep.gt.mem.or.irep.lt.0d0) then
63  write(6,*) "Error: replica out of range [0,",mem,"]"
64  else
65  rep = irep
66  endif
67 

◆ nnpdfdriver()

subroutine nnpdfdriver ( character(len=lenfilename)  gridfilename,
integer  lenfilename 
)

Definition at line 19 of file NNPDFDriver.f.

19  implicit none
20  integer nfl,nx,nq2,mem,rep,lenfilename
21  double precision alphas
22  double precision xgrid(100),logxgrid(100)
23  double precision q2grid(50),logq2grid(50)
24  double precision pdfgrid(0:100,14,100,50)
25  logical hasphoton
26  common /nnpdf/nfl,nx,nq2,mem,rep,hasphoton,alphas,xgrid,logxgrid,
27  1 q2grid,logq2grid,pdfgrid
28 
29  character(len=lenfilename) gridfilename
30 *
31  nfl = 13
32  nx = 100
33  nq2 = 50
34  mem = 1
35  rep = 0
36  alphas = 0
37 *
38 * Logo
39  write(6,*) " ****************************************"
40  write(6,*) ""
41  write(6,*) " NNPDFDriver version 1.0.3"
42  write(6,*) " Grid: ", gridfilename
43  write(6,*) " ****************************************"
44 
45  call readpdfset(gridfilename,lenfilename)
46 

◆ readpdfset()

subroutine readpdfset ( character(len=lenfilename)  gridfilename,
integer  lenfilename 
)

Definition at line 71 of file NNPDFDriver.f.

71  implicit none
72  integer i,ix,iq,fl,imem,lenfilename
73  character(len=lenfilename) gridfilename
74  character(len=100) line
75 *
76  integer nfl,nx,nq2,mem,rep
77  double precision alphas
78  double precision xgrid(100),logxgrid(100)
79  double precision q2grid(50),logq2grid(50)
80  double precision pdfgrid(0:100,14,100,50)
81  logical hasphoton
82  common /nnpdf/nfl,nx,nq2,mem,rep,hasphoton,alphas,xgrid,logxgrid,
83  1 q2grid,logq2grid,pdfgrid
84 *
85  open (20, file=gridfilename, status='OLD')
86 * Read header
87  do i=1,1000
88  read(20,*) line
89  if (line(1:14).eq.'Parameterlist:') then
90  read(20,*) line, mem, line, alphas
91  exit
92  endif
93  enddo
94 
95 * Select driver
96  do i=1,1000
97  read(20,*) line
98  if (line(1:13).eq.'NNPDF20intqed') then
99  hasphoton = .true.
100  nfl = nfl + 1
101  read(20,*) line,line
102  exit
103  endif
104  if (line(1:13).eq.'NNPDF20int') then
105  hasphoton = .false.
106  read(20,*) line,line
107  exit
108  endif
109  enddo
110 *
111  read(20,*) nx
112  do ix=1,nx
113  read(20,*) xgrid(ix)
114  logxgrid(ix) = dlog(xgrid(ix))
115  enddo
116 *
117  read(20,*) nq2
118  read(20,*) line
119  do iq=1,nq2
120  read(20,*) q2grid(iq)
121  logq2grid(iq) = dlog(q2grid(iq))
122  enddo
123 *
124  read(20,*) line
125  do imem=0,mem
126  do ix=1,nx
127  do iq=1,nq2
128  read(20,*) ( pdfgrid(imem,fl,ix,iq), fl=1,nfl,1)
129  enddo
130  enddo
131  enddo
132 
133  close(20)
134 
lh_polint
subroutine lh_polint(xa, ya, n, x, y, dy)
Definition: NNPDFDriver.f:289
readpdfset
subroutine readpdfset(gridfilename, lenfilename)
Definition: NNPDFDriver.f:71
lh_polin2
subroutine lh_polin2(x1a, x2a, ya, m, n, x1, x2, y, dy)
Definition: NNPDFDriver.f:268