]> git.uio.no Git - u/mrichter/AliRoot.git/blame - HBTAN/ltran12.F
Possibility to compile with Root v5-11-04/06
[u/mrichter/AliRoot.git] / HBTAN / ltran12.F
CommitLineData
ff4431bb 1 SUBROUTINE ltran12
2C
3
4c SUBROUTINE TRANS(icrf,irot)
5C==> TRANSformation to the Co-moving frame (icrf>0) and
6C Rotation to the system where (Pt || X),(irot=1).
7C-FSI ***************************************************
f5ab1a71 8 IMPLICIT REAL*8 (A-H,O-Z)
ff4431bb 9 COMMON/FSI_MOM/P1X,P1Y,P1Z,E1,P1, ! momenta in NRF
f5ab1a71 10 1 P2X,P2Y,P2Z,E2,P2
ff4431bb 11 COMMON/FSI_COOR/X1,Y1,Z1,T1,R1, ! 4-coord. of emis.
12 1 X2,Y2,Z2,T2,R2 ! points in NRF
13 COMMON/FSI_PRF/PPX,PPY,PPZ,AK,AKS, ! momenta in PRF
f5ab1a71 14 1 X,Y,Z,T,RP,RPS
15 COMMON/FSI_POC/AMN,AM1,AM2,CN,C1,C2,AC1,AC2
16 COMMON/FSI_P12/P12X,P12Y,P12Z,E12,P12,AM12,EPM
ff4431bb 17 COMMON/FSI_CVK/V,CVK
18C-FSI ***************************************************
19 COMMON /PAIR/P12T,V12Z,GAMZ,V12T,CPHI,SPHI
1a1e58ac 20
21
22C calculating Ri, Pi and Ei
23 R1=DSQRT(X1*X1+Y1*Y1+Z1*Z1)
24 R2=DSQRT(X2*X2+Y2*Y2+Z2*Z2)
f5ab1a71 25 P1S=P1X*P1X+P1Y*P1Y+P1Z*P1Z
26 P2S=P2X*P2X+P2Y*P2Y+P2Z*P2Z
ff4431bb 27 P1=DSQRT(P1S)
28 P2=DSQRT(P2S)
1a1e58ac 29 E1=DSQRT(AM1*AM1+P1S)
30 E2=DSQRT(AM2*AM2+P2S)
31C-----------------------------------------------------------------------
f5ab1a71 32 E12=E1+E2
33 P12X=P1X+P2X
34 P12Y=P1Y+P2Y
35 P12Z=P1Z+P2Z
36 P12S=P12X**2+P12Y**2+P12Z**2
1a1e58ac 37 AM12=DSQRT(E12**2-P12S)
f5ab1a71 38 EPM=E12+AM12
1a1e58ac 39 P12=DSQRT(P12S)
f5ab1a71 40 P112=P1X*P12X+P1Y*P12Y+P1Z*P12Z
41 H1=(P112/EPM-E1)/AM12
42 PPX=P1X+P12X*H1
43 PPY=P1Y+P12Y*H1
44 PPZ=P1Z+P12Z*H1
45 EE=(E12*E1-P112)/AM12
46 AKS=EE**2-AM1**2
47 AK=DSQRT(AKS)
1a1e58ac 48
49 RETURN
50 END
51C====
52C==== ===============================================================
53C==== ===============================================================
54C==== ===============================================================
55
56 subroutine BoostToPrf()
57 IMPLICIT REAL*8 (A-H,O-Z)
58 COMMON/FSI_CVK/V,CVK
59 COMMON/FSI_MOM/P1X,P1Y,P1Z,E1,P1, !part. momenta in NRF
60 1 P2X,P2Y,P2Z,E2,P2
61 COMMON/FSI_PRF/PPX,PPY,PPZ,AK,AKS,
62 1 X,Y,Z,T,RP,RPS
63 COMMON/FSI_COOR/X1,Y1,Z1,T1,R1, ! 4-coord. of emis. points in NRF
64 1 X2,Y2,Z2,T2,R2
65 COMMON/FSI_P12/P12X,P12Y,P12Z,E12,P12,AM12,EPM
66
ff4431bb 67 XS=X1-X2
68 YS=Y1-Y2
69 ZS=Z1-Z2
1a1e58ac 70 TS=T1-T2
ff4431bb 71 RS12=XS*P12X+YS*P12Y+ZS*P12Z
72 H1=(RS12/EPM-TS)/AM12
88cb7938 73 X=XS+P12X*H1
74 Y=YS+P12Y*H1
75 Z=ZS+P12Z*H1
76 T=(E12*TS-RS12)/AM12
77 RPS=X*X+Y*Y+Z*Z
78 RP=DSQRT(RPS)
1a1e58ac 79CW WRITE(6,38)'RP ',RP,'X ',X,Y,Z,T
8038 FORMAT(A7,E11.4,A7,4E11.4)
81
82 CVK=(P12X*PPX+P12Y*PPY+P12Z*PPZ)/(P12*AK)
83 V=P12/E12
84 return
85 end
86C==== ===============================================================
87C==== ===============================================================
ff4431bb 88
ff4431bb 89 SUBROUTINE LTR8(Z,T,BETA,GAMMA,ZT,TT)
90C===> Lorentz Transf. of Z(Pz) and T(E) to moving ref. frame.(REAL*8)
91CInp: Z,T-Zcoord,Time before tr., BETA,GAMMA- velocity, Lor.fact.
92COut: ZT,TT- " " after transformation.
93C==== ===============================================================
94 IMPLICIT REAL*8 (A-H,O-Z)
95 ZH=GAMMA*(Z-BETA*T)
96 TT=GAMMA*(T-BETA*Z)
97 ZT=ZH
f5ab1a71 98 RETURN
99 END
ff4431bb 100C====
88cb7938 101
ff4431bb 102 SUBROUTINE LTR4(Z,T,BETA,GAMMA,ZT,TT)
103C===> Lorentz Transf. of Z(Pz) and T(E) to moving ref. frame.(real*4)
104CInp: Z,T-Zcoord,Time before tr., BETA,GAMMA- velocity, Lor.fact.
105COut: ZT,TT- " " after transformation.
106C==== ===============================================================
107 ZH=GAMMA*(Z-BETA*T)
108 TT=GAMMA*(T-BETA*Z)
109 ZT=ZH
110 RETURN
111 END
112C====
113 SUBROUTINE ROT8(X,Y,SF,CF,XR,YR)
114C===> Rotation with the angle f. (REAL*8)
115CInp: X,Y-coord. before rotation; SF=sin(f), CF=cos(f),
116COut: XR,YR - coordinates after rotation.
117C==== =================================================
118 IMPLICIT REAL*8 (A-H,O-Z)
119 XH=X*CF+Y*SF !Y
120 YR=Y*CF-X*SF ! _-X'
121 XR=XH ! _- f
122 RETURN !------>
123 END ! X
124
88cb7938 125 SUBROUTINE SETPDIST(R)
126C=====Just sets distance between particles
127 IMPLICIT REAL*8 (A-H,O-Z)
128 COMMON/FSI_PRF/PPX,PPY,PPZ,AK,AKS, ! momenta in PRF
129 1 X,Y,Z,T,RP,RPS
1a1e58ac 130 RP=R
131 RPS=R*R
88cb7938 132 RETURN
133 END