92 Function ctq6pdf (Iparton, X, Q)
93 Implicit Double Precision (a-h,o-z)
96 > / ctqpar2 / nx, nt, nfmx
97 > / qcdtable / alambda, nfl, iorder
102 If (x .lt. 0d0 .or. x .gt. 1d0)
Then
103 print *,
'X out of range in Ctq6Pdf: ', x
106 If (q .lt. alambda)
Then
107 print *,
'Q out of range in Ctq6Pdf: ', q
110 If ((iparton .lt. -nfmx .or. iparton .gt. nfmx))
Then
113 print *,
'Warning: Iparton out of range in Ctq6Pdf! '
114 print *,
'Iparton, MxFlvN0: ', iparton, nfmx
124 print *,
'Warning: Ctq6Pdf is NaN!'
125 print *,
'Iparton, MxFlvN0, X, Q: ', iparton, nfmx, x, q
130 if (warn) warn = .false.
138 Implicit Double Precision (a-h,o-z)
139 parameter(isetmax0=5)
140 Character Flnm(Isetmax0)*6, nn*3, Tablefile*40
141 Data (flnm(i), i=1,isetmax0)
142 > /
'cteq6m',
'cteq6d',
'cteq6l',
'cteq6l',
'ctq61.'/
143 Data isetold, isetmin0, isetmin1, isetmax1 /-987,1,100,140/
144 Data isetmin2,isetmax2 /200,240/
148 If(iset.ne.isetold)
then
150 If (iset.ge.isetmin0 .and. iset.le.3)
Then
151 tablefile=flnm(iset)//
'.tbl'
152 Elseif (iset.eq.4)
Then
153 tablefile=flnm(iset)//
'1.tbl'
154 Elseif (iset.ge.isetmin1 .and. iset.le.isetmax1)
Then
155 write(nn,
'(I3)') iset
156 tablefile=flnm(1)//nn//
'.tbl'
157 Elseif (iset.ge.isetmin2 .and. iset.le.isetmax2)
Then
158 write(nn,
'(I3)') iset
159 tablefile=flnm(5)//nn(2:3)//
'.tbl'
161 print *,
'Invalid Iset number in SetCtq6 :', iset
164 Open(iu, file=
'pdfs/'//tablefile
165 . ,status=
'OLD', err=100)
172 100 print *,
' Data file ', tablefile,
' cannot be opened '
179 Implicit Double Precision (a-h,o-z)
181 parameter(mxx = 96, mxq = 20, mxf = 5)
182 parameter(mxpqx = (mxf + 3) * mxq * mxx)
184 > / ctqpar1 / al, xv(0:mxx), tv(0:mxq), upd(mxpqx)
185 > / ctqpar2 / nx, nt, nfmx
186 > / xqrange / qini, qmax, xmin
187 > / qcdtable / alambda, nfl, iorder
188 > / masstbl / amass(6)
190 Read (nu,
'(A)') line
191 Read (nu,
'(A)') line
192 Read (nu, *) dr, fl, al, (amass(i),i=1,6)
197 Read (nu,
'(A)') line
198 Read (nu, *) nx, nt, nfmx
200 Read (nu,
'(A)') line
201 Read (nu, *) qini, qmax, (tv(i), i =0, nt)
203 Read (nu,
'(A)') line
204 Read (nu, *) xmin, (xv(i), i =0, nx)
207 tv(iq) = log(log(tv(iq) /al))
214 nblk = (nx+1) * (nt+1)
215 npts = nblk * (nfmx+3)
216 Read (nu,
'(A)') line
217 Read (nu, *, iostat=iret) (upd(i), i=1,npts)
228 INQUIRE (unit=n, opened=ex)
234 stop
' There is no available I/O unit. '
239 SUBROUTINE polint (XA,YA,N,X,Y,DY)
241 IMPLICIT DOUBLE PRECISION (a-h, o-z)
244 dimension xa(n),ya(n),c(nmax),d(nmax)
249 IF (dift.LT.dif)
THEN
286 Implicit Double Precision (a-h,o-z)
288 parameter(mxx = 96, mxq = 20, mxf = 5)
289 parameter(mxqx= mxq * mxx, mxpqx = mxqx * (mxf+3))
292 > / ctqpar1 / al, xv(0:mxx), tv(0:mxq), upd(mxpqx)
293 > / ctqpar2 / nx, nt, nfmx
294 > / xqrange / qini, qmax, xmin
296 dimension fvec(4), fij(4)
297 dimension xvpow(0:mxx)
298 Data onep / 1.00001 /
305 if(ientry .eq. 0)
then
310 xvpow(i) = xv(i)**xpow
322 11
If (ju-jlx .GT. 1)
Then
324 If (x .Ge. xv(jm))
Then
335 If (jlx .LE. -1)
Then
336 print
'(A,1pE12.4)',
'Severe error: x <= 0 in PartonX6! x = ', x
338 ElseIf (jlx .Eq. 0)
Then
340 Elseif (jlx .LE. nx-2)
Then
344 Elseif (jlx.Eq.nx-1 .or. x.LT.onep)
Then
351 print
'(A,1pE12.4)',
'Severe error: x > 1 in PartonX6! x = ', x
359 If (jlx.Ge.2 .and. jlx.Le.nx-2)
Then
383 sdet = s12*s34 - s1213*s2434
385 const5 = (s34*sy2-s2434*sy3)*tmp/s12
386 const6 = (s1213*sy2-s12*sy3)*tmp/s34
394 12
If (ju-jlq .GT. 1)
Then
396 If (tt .GE. tv(jm))
Then
406 Elseif (jlq .LE. nt-2)
Then
416 If (jlq.GE.1 .and. jlq.LE.nt-2)
Then
435 tdet = t12*t34 - tmp1*tmp2
442 If (iprtn .GE. 3)
Then
447 jtmp = ((ip + nfmx)*(nt+1)+(jq-1))*(nx+1)+jx+1
451 j1 = jtmp + it*(nx+1)
459 fij(2) = upd(j1+1) * xv(1)**2
460 fij(3) = upd(j1+2) * xv(2)**2
461 fij(4) = upd(j1+3) * xv(3)**2
465 Call polint (xvpow(0), fij(1), 4, ss, fx, dfx)
467 If (x .GT. 0d0) fvec(it) = fx / x**2
469 ElseIf (jlx .Eq. nx-1)
Then
472 Call polint (xvpow(nx-3), upd(j1), 4, ss, fx, dfx)
482 g1 = sf2*const1 - sf3*const2
483 g4 = -sf2*const3 + sf3*const4
485 fvec(it) = (const5*(upd(j1)-g1)
486 & + const6*(upd(j1+3)-g4)
487 & + sf2*sy3 - sf3*sy2) / s23
497 Call polint (tv(0), fvec(1), 4, tt, ff, dfq)
499 ElseIf (jlq .GE. nt-1)
Then
501 Call polint (tv(nt-3), fvec(1), 4, tt, ff, dfq)
509 g1 = ( tf2*t13 - tf3*t12) / t23
510 g4 = (-tf2*t34 + tf3*t24) / t23
512 h00 = ((t34*ty2-tmp2*ty3)*(fvec(1)-g1)/t12
513 & + (tmp1*ty2-t12*ty3)*(fvec(4)-g4)/t34)
515 ff = (h00*ty2*ty3/tdet + tf2*ty3 - tf3*ty2) / t23