ECCE @ EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyhistfe.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyhistfe.f
1 
2 C*********************************************************************
3 
4  SUBROUTINE pyhistfe(KF,X,Q2,XPQ)
5 
6 C...This is a dummy routine, where the user can introduce an interface
7 C...to his own external structure function parametrization.
8 C...Arguments in:
9 C...KF : 2212 for p, 211 for pi+; isospin conjugation for n and charge
10 C... conjugation for pbar, nbar or pi- is performed by PYSTFU.
11 C...X : x value.
12 C...Q2 : Q^2 value.
13 C...Arguments out:
14 C...XPQ(-6:6) : x * f(x,Q2), with index according to KF code,
15 C... except that gluon is placed in 0. Thus XPQ(0) = xg,
16 C... XPQ(1) = xd, XPQ(-1) = xdbar, XPQ(2) = xu, XPQ(-2) = xubar,
17 C... XPQ(3) = xs, XPQ(-3) = xsbar, XPQ(4) = xc, XPQ(-4) = xcbar,
18 C... XPQ(5) = xb, XPQ(-5) = xbbar, XPQ(6) = xt, XPQ(-6) = xtbar.
19 C...
20 C...One such interface, to the Diemos, Ferroni, Longo, Martinelli
21 C...proton structure functions, already comes with the package. What
22 C...the user needs here is external files with the three routines
23 C...FXG160, FXG260 and FXG360 of the authors above, plus the
24 C...interpolation routine FINT, which is part of the CERN library
25 C...KERNLIB package. To avoid problems with unresolved external
26 C...references, the external calls are commented in the current
27 C...version. To enable this option, remove the C* at the beginning
28 C...of the relevant lines.
29 C...
30 C...Alternatively, the routine can be used as an interface to the
31 C...structure function evolution program of Tung. This can be achieved
32 C...by removing C* at the beginning of some of the lines below.
33  common/ludat1/mstu(200),paru(200),mstj(200),parj(200)
34  SAVE /ludat1/
35  common/ludat2/kchg(500,3),pmas(500,4),parf(2000),vckm(4,4)
36  SAVE /ludat2/
37  common/pyhipars/mstp(200),parp(200),msti(200),pari(200)
38  SAVE /pyhipars/
39  dimension xpq(-6:6),xfdflm(9)
40  CHARACTER chdflm(9)*5,header*40
41  DATA chdflm/'UPVAL','DOVAL','GLUON','QBAR ','UBAR ','SBAR ',
42  &'CBAR ','BBAR ','TBAR '/
43  DATA header/'Tung evolution package has been invoked'/
44  DATA init/0/
45 
46  SAVE xfdflm, init ! Uzhi
47 
48 C...Proton structure functions from Diemoz, Ferroni, Longo, Martinelli.
49 C...Allowed variable range 10 GeV2 < Q2 < 1E8 GeV2, 5E-5 < x < .95.
50  IF(mstp(51).GE.11.AND.mstp(51).LE.13.AND.mstp(52).LE.1) THEN
51  xdflm=max(0.51e-4,x)
52  q2dflm=max(10.,min(1e8,q2))
53  IF(mstp(52).EQ.0) q2dflm=10.
54  DO 100 j=1,9
55  IF(mstp(52).EQ.1.AND.j.EQ.9) THEN
56  q2dflm=q2dflm*(40./pmas(6,1))**2
57  q2dflm=max(10.,min(1e8,q2))
58  ENDIF
59  xfdflm(j)=0.
60 C...Remove C* on following three lines to enable the DFLM options.
61 C* IF(MSTP(51).EQ.11) CALL FXG160(XDFLM,Q2DFLM,CHDFLM(J),XFDFLM(J))
62 C* IF(MSTP(51).EQ.12) CALL FXG260(XDFLM,Q2DFLM,CHDFLM(J),XFDFLM(J))
63 C* IF(MSTP(51).EQ.13) CALL FXG360(XDFLM,Q2DFLM,CHDFLM(J),XFDFLM(J))
64  100 CONTINUE
65  IF(x.LT.0.51e-4.AND.abs(parp(51)-1.).GT.0.01) THEN
66  cxs=(0.51e-4/x)**(parp(51)-1.)
67  DO 110 j=1,7
68  110 xfdflm(j)=xfdflm(j)*cxs
69  ENDIF
70  xpq(0)=xfdflm(3)
71  xpq(1)=xfdflm(2)+xfdflm(5)
72  xpq(2)=xfdflm(1)+xfdflm(5)
73  xpq(3)=xfdflm(6)
74  xpq(4)=xfdflm(7)
75  xpq(5)=xfdflm(8)
76  xpq(6)=xfdflm(9)
77  xpq(-1)=xfdflm(5)
78  xpq(-2)=xfdflm(5)
79  xpq(-3)=xfdflm(6)
80  xpq(-4)=xfdflm(7)
81  xpq(-5)=xfdflm(8)
82  xpq(-6)=xfdflm(9)
83 
84 C...Proton structure function evolution from Wu-Ki Tung: parton
85 C...distribution functions incorporating heavy quark mass effects.
86 C...Allowed variable range: PARP(52) < Q < PARP(53); PARP(54) < x < 1.
87  ELSE
88  IF(init.EQ.0) THEN
89  i1=0
90  IF(mstp(52).EQ.4) i1=1
91  ihdrn=1
92  nu=mstp(53)
93  i2=mstp(51)
94  IF(mstp(51).GE.11) i2=mstp(51)-3
95  i3=0
96  IF(mstp(52).EQ.3) i3=1
97 
98 C...Convert to Lambda in CWZ scheme (approximately linear relation).
99  alam=0.75*parp(1)
100  tpms=pmas(6,1)
101  qini=parp(52)
102  qmax=parp(53)
103  xmin=parp(54)
104 
105 C...Initialize evolution (perform calculation or read results from
106 C...file).
107 C...Remove C* on following two lines to enable Tung initialization.
108 C* CALL PDFSET(I1,IHDRN,ALAM,TPMS,QINI,QMAX,XMIN,NU,HEADER,
109 C* & I2,I3,IRET,IRR)
110  init=1
111  ENDIF
112 
113 C...Put into output array.
114  q=sqrt(q2)
115  DO 200 i=-6,6
116  fixq=0.
117 C...Remove C* on following line to enable structure function call.
118 C* FIXQ=MAX(0.,PDF(10,1,I,X,Q,IR))
119  200 xpq(i)=x*fixq
120 
121 C...Change order of u and d quarks from Tung to PYTHIA convention.
122  xps=xpq(1)
123  xpq(1)=xpq(2)
124  xpq(2)=xps
125  xps=xpq(-1)
126  xpq(-1)=xpq(-2)
127  xpq(-2)=xps
128  ENDIF
129 
130  RETURN
131  END