EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
lystfu.F
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file lystfu.F
1 
2 C **********************************************************************
3 
4  SUBROUTINE lystfu(KF,X,Q2,XPQ)
5 
6  IMPLICIT NONE
7 
8 C...Interface to PYSTFU in PYTHIA 5.7 to get parton density distributions,
9 C...i.e. momentum weighted probability distributions xq(x,Q2), xg(x,Q2).
10 C...Also gives intrinsic charm and beauty distributions.
11 *
12 * to avoid variable conflictions, a second keep element is necessary
13 * with the same common block name (see LEPTO2)
14 *
15  include "lepto2.inc"
16  include "ludat1.inc"
17  include "pypars.inc"
18  include "arstrf.inc"
19 
20 c$$$ COMMON /LEPTOU/ CUT(14),LST(40),PARL(30),
21 c$$$ & XLP,YLP,W2LP,Q2LP,ULP
22 c$$$ REAL CUT,PARL,XLP,YLP,W2LP,Q2LP,ULP
23 c$$$ INTEGER LST
24 c$$$ SAVE /LEPTOU/
25 c$$$
26 c$$$ COMMON/LUDAT1/MSTU(200),PARU(200),MSTJ(200),PARJ(200)
27 c$$$ INTEGER MSTU,MSTJ
28 c$$$ REAL PARU,PARJ
29 c$$$ SAVE /LUDAT1/
30 c$$$
31 c$$$ COMMON/PYPARS/MSTP(200),PARP(200),MSTI(200),PARI(200)
32 c$$$ INTEGER MSTP,MSTI
33 c$$$ REAL PARP,PARI
34 c$$$ SAVE /PYPARS/
35 c$$$
36 c$$$ COMMON /ARSTRF/ KFSAVE(2),XSAVE(2),XQ2SAV(2),
37 c$$$ + XPQSAV(2,-6:6),XDPQSAV(2,-6:6)
38 c$$$ INTEGER KFSAVE
39 c$$$ REAL XSAVE,XQ2SAV,XPQSAV,XDPQSAV
40 c$$$ SAVE /ARSTRF/
41 
42 
43  REAL xcorr,xpyst,x,q2,xpq,xdpq
44  INTEGER kfl,kf
45  dimension xdpq(-6:6),xpq(-6:6),xpyst(-25:25)
46 
47 C...Reset arrays etc.
48  DO 100 kfl=-6,6
49  xpq(kfl)=0.0
50  100 xpqsav(1,kfl)=0.
51  xsave(1)=x
52  xq2sav(1)=q2
53  kfsave(1)=kf
54 C...Check x and particle species.
55  IF(x.LE.0..OR.x.GE.1.) THEN
56 C WRITE(MSTU(11),5000) X
57  WRITE(*,5000) x
58  RETURN
59  ENDIF
60 
61  IF(lst(15).EQ.-4.OR.lst(15).EQ.-5) THEN
62 C...Intrinsic charm/bottom quark distribution in the proton...
63  IF(q2.LT.1.) RETURN
64 C...from Phys. Lett 93B (1980) 451,
65 C...Amount of intrinsic charm PARL(12)=BETA^2
66  xpq(4)=x**3*1800.*parl(12)*
67  & ((1.-x)/3.*(1.+10.*x+x**2)+2.*x*(1.+x)*log(x))
68 C...plus first order QCD-correction parametrized with polynomia
69  IF(x.LT.0.9) THEN
70  xcorr=0.22024e-1*x-0.77833e-1*x**2-0.47292*x**3+
71  & 2.104*x**4-2.1698*x**5-0.84891*x**6+1.8882*x**7+
72  & 0.8989*x**8-2.1072*x**9+0.76351*x**10
73  ELSE
74  xcorr=-1.
75  ENDIF
76 C...and a Q2 dependence on that
77 CJR XCORR=1.125*XCORR*0.190424*EXP(1.15*LOG(LOG(Q2)))
78  IF(q2.GT.1) THEN
79  xcorr=1.125*xcorr*0.190424*exp(1.15*log(log(q2)))
80  ELSE
81  xcorr=1.125*xcorr*0.190424
82  ENDIF
83 C...smooth cut-off of the structure function !
84  xpq(4)=max(xpq(4)+xcorr,xpq(4)/q2)
85  xpq(-4)=xpq(4)
86  IF(lst(15).EQ.-5) THEN
87 C... Intrinsic bottom assumed to have the same shape as zeroth
88 C... approximation but suppressed by (mc/mb)**2=0.1 approximately
89  xpq(5)=xpq(4)*0.1
90  xpq(-5)=xpq(5)
91  xpq(4)=0.
92  xpq(-4)=0.
93  ENDIF
94  ELSE
95 C... Parton densities from PYSTFU in PYTHIA 5.7
96 * PEPSI>>
97  IF(lst(15).LT.100.or.lst(15).gt.1000) THEN !bs> add gt. 1000
98  CALL pystfu(kf,x,q2,xpyst)
99  DO 110 kfl=-6,6
100  110 xpq(kfl)=xpyst(kfl)
101  ELSE
102  CALL parton(x,q2,xpq,xdpq)
103  ENDIF
104 * PEPSI<<
105  ENDIF
106 
107  DO 120 kfl=-6,6
108  120 xpqsav(1,kfl)=xpq(kfl)
109 C... Formats for error printouts.
110  5000 FORMAT(' Error in LYSTFU: x =',1p,e12.4,' outside physical range')
111 
112  RETURN
113  END