]> git.uio.no Git - u/mrichter/AliRoot.git/blame - ISAJET/code/twokin.F
fixed a complation warning about not brace-enclosing the sub-elements of
[u/mrichter/AliRoot.git] / ISAJET / code / twokin.F
CommitLineData
0795afa3 1#include "isajet/pilot.h"
2 SUBROUTINE TWOKIN(AMI1,AMI2,AM1,AM2)
3C
4C Given P,PT,TH,PHI, and initial and final masses AMI1, AMI2,
5C AM1,AM2, set X1, X2, SHAT, etc.
6C
7#if defined(CERNLIB_IMPNONE)
8 IMPLICIT NONE
9#endif
10#include "isajet/itapes.inc"
11#include "isajet/primar.inc"
12#include "isajet/jetpar.inc"
13#include "isajet/qcdpar.inc"
14#include "isajet/const.inc"
15C
16 REAL AMI1,AMI2,AM1,AM2,P1PL,P1MN,P2PL,P2MN,E1,E2,PPL,PMN,
17 $ PI1PL,PI1MN,PI2PL,PI2MN,ANEFF,AMASS,ALAMFN
18C
19 E1=SQRT(P(1)**2+AM1**2)
20 E2=SQRT(P(2)**2+AM2**2)
21C
22C For 32-bit machines must use large and small components
23C carefully, with pbig*psmall = pt**2+am**2.
24C
25 IF(CTH(1).GT.0.) THEN
26 P1PL=E1+P(1)*CTH(1)
27 P1MN=(PT(1)**2+AM1**2)/P1PL
28 ELSE
29 P1MN=E1-P(1)*CTH(1)
30 P1PL=(PT(1)**2+AM1**2)/P1MN
31 ENDIF
32 IF(CTH(2).GT.0.) THEN
33 P2PL=E2+P(2)*CTH(2)
34 P2MN=(PT(2)**2+AM2**2)/P2PL
35 ELSE
36 P2MN=E2-P(2)*CTH(2)
37 P2PL=(PT(2)**2+AM2**2)/P2MN
38 ENDIF
39C
40C Initial light cone momenta. Not symmetric if AMI1 /= AMI2.
41C
42 PPL=P1PL+P2PL
43 PMN=P1MN+P2MN
44 SHAT=PPL*PMN
45 ALAMFN=SQRT((SHAT-AMI1**2-AMI2**2)**2-4.*(AMI1*AMI2)**2)
46 PI1PL=(SHAT+AMI1**2-AMI2**2+ALAMFN)/(2.*PMN)
47 PI1MN=AMI1**2/PI1PL
48 PI2MN=(SHAT+AMI2**2-AMI1**2+ALAMFN)/(2.*PPL)
49 PI2PL=AMI2**2/PI2MN
50 X1=PI1PL/ECM
51 X2=PI2MN/ECM
52C
53C t=(p1-pi1)**2, u=(p1-pi2)**2
54C
55 THAT=AM1**2+AMI1**2-P1PL*PI1MN-P1MN*PI1PL
56 UHAT=AM1**2+AMI2**2-P1PL*PI2MN-P1MN*PI2PL
57C
58C Q**2 variable from Field, Fox, Wolfram
59C
60 QSQ=2.*SHAT*THAT*UHAT/(SHAT**2+THAT**2+UHAT**2)
61 QSQ=AMAX1(QSQ,(AM1+AM2)**2)
62 ANEFF=4.+QSQ/(QSQ+AMASS(5)**2)+QSQ/(QSQ+AMASS(6)**2)
63 ALFQSQ=12.*PI/((33.-2.*ANEFF)*ALOG(QSQ/ALAM2))
64 RETURN
65 END