Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyfowo.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyfowo.f
1 
2 C*********************************************************************
3 
4 C...PYFOWO
5 C...Calculates the first few Fox-Wolfram moments.
6 
7  SUBROUTINE pyfowo(H10,H20,H30,H40)
8 
9 C...Double precision and integer declarations.
10  IMPLICIT DOUBLE PRECISION(a-h, o-z)
11  IMPLICIT INTEGER(i-n)
12  INTEGER pyk,pychge,pycomp
13 C...Parameter statement to help give large particle numbers.
14  parameter(ksusy1=1000000,ksusy2=2000000,ktechn=3000000,
15  &kexcit=4000000,kdimen=5000000)
16 C...Commonblocks.
17  common/pyjets/n,npad,k(4000,5),p(4000,5),v(4000,5)
18  common/pydat1/mstu(200),paru(200),mstj(200),parj(200)
19  common/pydat2/kchg(500,4),pmas(500,4),parf(2000),vckm(4,4)
20  SAVE /pyjets/,/pydat1/,/pydat2/
21 
22 C...Copy momenta for particles and calculate H0.
23  np=0
24  h0=0d0
25  hd=0d0
26  DO 110 i=1,n
27  IF(k(i,1).LE.0.OR.k(i,1).GT.10) goto 110
28  IF(mstu(41).GE.2) THEN
29  kc=pycomp(k(i,2))
30  IF(kc.EQ.0.OR.kc.EQ.12.OR.kc.EQ.14.OR.kc.EQ.16.OR.
31  & kc.EQ.18.OR.k(i,2).EQ.ksusy1+22.OR.k(i,2).EQ.39.OR.
32  & k(i,2).EQ.ksusy1+39) goto 110
33  IF(mstu(41).GE.3.AND.kchg(kc,2).EQ.0.AND.pychge(k(i,2)).EQ.0)
34  & goto 110
35  ENDIF
36  IF(n+np.GE.mstu(4)-mstu(32)-5) THEN
37  CALL pyerrm(11,'(PYFOWO:) no more memory left in PYJETS')
38  h10=-1d0
39  h20=-1d0
40  h30=-1d0
41  h40=-1d0
42  RETURN
43  ENDIF
44  np=np+1
45  DO 100 j=1,3
46  p(n+np,j)=p(i,j)
47  100 CONTINUE
48  p(n+np,4)=sqrt(p(i,1)**2+p(i,2)**2+p(i,3)**2)
49  h0=h0+p(n+np,4)
50  hd=hd+p(n+np,4)**2
51  110 CONTINUE
52  h0=h0**2
53 
54 C...Very low multiplicities (0 or 1) not considered.
55  IF(np.LE.1) THEN
56  CALL pyerrm(8,'(PYFOWO:) too few particles for analysis')
57  h10=-1d0
58  h20=-1d0
59  h30=-1d0
60  h40=-1d0
61  RETURN
62  ENDIF
63 
64 C...Calculate H1 - H4.
65  h10=0d0
66  h20=0d0
67  h30=0d0
68  h40=0d0
69  DO 130 i1=n+1,n+np
70  DO 120 i2=i1+1,n+np
71  cthe=(p(i1,1)*p(i2,1)+p(i1,2)*p(i2,2)+p(i1,3)*p(i2,3))/
72  & (p(i1,4)*p(i2,4))
73  h10=h10+p(i1,4)*p(i2,4)*cthe
74  h20=h20+p(i1,4)*p(i2,4)*(1.5d0*cthe**2-0.5d0)
75  h30=h30+p(i1,4)*p(i2,4)*(2.5d0*cthe**3-1.5d0*cthe)
76  h40=h40+p(i1,4)*p(i2,4)*(4.375d0*cthe**4-3.75d0*cthe**2+
77  & 0.375d0)
78  120 CONTINUE
79  130 CONTINUE
80 
81 C...Calculate H1/H0 - H4/H0. Output.
82  mstu(61)=n+1
83  mstu(62)=np
84  h10=(hd+2d0*h10)/h0
85  h20=(hd+2d0*h20)/h0
86  h30=(hd+2d0*h30)/h0
87  h40=(hd+2d0*h40)/h0
88 
89  RETURN
90  END