EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
dstfu.F
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file dstfu.F
1 ************************************************************************
2  SUBROUTINE dstfu(KF,X,Q2,XDPQ)
3 
4  IMPLICIT NONE
5 
6 C...Gives proton and neutron structure functions according to a few
7 C...different polarized parametrizations.
8 C...Note that what is coded is x times the probability distribution,
9 C...i.e. xdq(x,Q2) etc.
10 
11 *
12 * to avoid variable conflictions, a second keep element is necessary
13 * with the same common block name (see LEPTO2)
14 *
15 
16  COMMON /leptou/ cut(14),lst(40),parl(30),
17  & xlp,ylp,w2lp,q2lp,ulp
18  REAL cut,parl,xlp,ylp,w2lp,q2lp,ulp
19  INTEGER lst
20  SAVE /leptou/
21 
22  COMMON /arstrf/ kfsave(2),xsave(2),xq2sav(2),
23  + xpqsav(2,-6:6),xdpqsav(2,-6:6)
24  INTEGER kfsave
25  REAL xsave,xq2sav,xpqsav,xdpqsav
26  SAVE /arstrf/
27 
28 
29  INTEGER kf,kfl,kfa
30  REAL x,q2,xpq,xdpq,xdps
31  dimension xpq(-6:6),xdpq(-6:6)
32 
33 C...Reset structure functions.
34  DO 100 kfl=-6,6
35  xdpq(kfl)=0.
36  100 xdpqsav(1,kfl)=0.
37  xsave(1)=x
38  xq2sav(1)=q2
39  kfsave(1)=kf
40 
41 C...Check x and particle species.
42  IF(x.LE.0..OR.x.GE.1.) THEN
43  WRITE(6,5000) x
44  RETURN
45  ENDIF
46  kfa=iabs(kf)
47  IF(kfa.NE.2112.AND.kfa.NE.2212) THEN
48  WRITE(6,5100) kf
49  RETURN
50  ENDIF
51 
52 *... Put into output array
53  CALL parton(x,q2,xpq,xdpq)
54 
55 
56 C...Check positivity and reset above maximum allowed flavour.
57  DO 180 kfl=-6,6
58  IF(iabs(kfl).GT.lst(12)) THEN
59  xdpq(kfl)=0.
60  ENDIF
61  180 CONTINUE
62 
63 C... Isospin conjugation for neutron.
64 *HI>>
65  IF(kfa.EQ.2112.AND.lst(39).EQ.0) THEN
66 * IF(KFA.EQ.2112) THEN
67  xdps = xdpq(1)
68  xdpq(1) = xdpq(2)
69  xdpq(2) = xdps
70  xdps = xdpq(-1)
71  xdpq(-1) = xdpq(-2)
72  xdpq(-2) = xdps
73  ENDIF
74 
75 C...Charge conjugation for antiparticle.
76  IF(kf.LT.0) THEN
77  DO 170 kfl=1,6
78  xdps = xdpq(kfl)
79  xdpq(kfl) = xdpq(-kfl)
80  xdpq(-kfl) = xdps
81  170 CONTINUE
82  ENDIF
83 
84  DO 120 kfl=-6,6
85  120 xdpqsav(1,kfl)=xdpq(kfl)
86 
87 C...Formats for error printouts.
88  5000 FORMAT(' Error: x value outside physical range; x =',1p,e12.3)
89  5100 FORMAT(' Error: illegal particle code for structure function;',
90  &' KF =',i5)
91  5200 FORMAT(' Error: unknown structure function; KF, library, set =',
92  &3i5)
93 
94  RETURN
95  END