]> git.uio.no Git - u/mrichter/AliRoot.git/blob - HBTAN/ltran12.F
Bug Corrected
[u/mrichter/AliRoot.git] / HBTAN / ltran12.F
1
2        SUBROUTINE ltran12
3 C
4
5 c      SUBROUTINE TRANS(icrf,irot)
6 C==>  TRANSformation to the Co-moving frame  (icrf>0) and
7 C     Rotation to the system where (Pt || X),(irot=1).
8 C-FSI ***************************************************
9       IMPLICIT REAL*8 (A-H,O-Z)
10       COMMON/FSI_MOM/P1X,P1Y,P1Z,E1,P1,  ! momenta in NRF
11      1               P2X,P2Y,P2Z,E2,P2
12       COMMON/FSI_COOR/X1,Y1,Z1,T1,R1, ! 4-coord. of emis. 
13      1                X2,Y2,Z2,T2,R2  ! points in NRF
14       COMMON/FSI_PRF/PPX,PPY,PPZ,AK,AKS, ! momenta in PRF
15      1               X,Y,Z,T,RP,RPS
16       COMMON/FSI_POC/AMN,AM1,AM2,CN,C1,C2,AC1,AC2
17       COMMON/FSI_P12/P12X,P12Y,P12Z,E12,P12,AM12,EPM
18       COMMON/FSI_CVK/V,CVK
19 C-FSI ***************************************************
20       COMMON /PAIR/P12T,V12Z,GAMZ,V12T,CPHI,SPHI
21       
22       icrf=1
23       irot=1
24       
25 C---> Particle energies ---------
26       P1S=P1X*P1X+P1Y*P1Y+P1Z*P1Z
27       P2S=P2X*P2X+P2Y*P2Y+P2Z*P2Z
28       E1=DSQRT(AM1*AM1+P1S)
29       E2=DSQRT(AM2*AM2+P2S)
30 C---> Pair parameters -----------
31       E12=E1+E2       ! Energy
32       P12X=P1X+P2X    ! Px
33       P12Y=P1Y+P2Y    ! Py
34       P12Z=P1Z+P2Z    ! Pz
35       P12S=P12X**2+P12Y**2+P12Z**2
36       P12 =DSQRT(P12S)! Momentum
37       V12 =P12/E12    ! Velocity
38       CTH =P12Z/P12   ! cos(theta)
39       STH =DSQRT(1.D0-CTH**2) !sin
40       V12Z=V12*CTH    ! Longit. V
41       GAMZ=1.D0/DSQRT(1.D0-V12Z**2)
42 C--      V12T=V12*STH    ! Transv. V in CMS (not needed)
43       P12TS=P12X*P12X+P12Y*P12Y
44       P12T=DSQRT(P12TS) !Pt
45 C===> Azimuthal rotation (Pt||X) ============
46       IF(V12T.NE.0.D0) THEN
47         CPHI=P12X/P12T  ! cos(phi)
48         SPHI=P12Y/P12T  ! sin(phi)
49         IF((irot.eq.1)) THEN 
50           CALL ROT8(P1X,P1Y,SPHI,CPHI,P1X,P1Y)       
51           CALL ROT8(P2X,P2Y,SPHI,CPHI,P2X,P2Y)
52           CALL ROT8(X1,Y1,SPHI,CPHI,X1,Y1)       
53           CALL ROT8(X2,Y2,SPHI,CPHI,X2,Y2) 
54         END IF             
55       ELSE ! Rotation impossible 
56        CPHI=2.D0 ! to avoid
57        SPHI=2.D0 ! using it !  
58       END IF             
59 C===> Co-moving ref. frame       ============
60       IF(icrf.gt.0) THEN
61         CALL LTR8(P1Z,E1,V12Z,GAMZ,P1Z,E1a)
62         CALL LTR8(P2Z,E2,V12Z,GAMZ,P2Z,E2a)
63         P1S=P1X*P1X+P1Y*P1Y+P1Z*P1Z
64         P2S=P2X*P2X+P2Y*P2Y+P2Z*P2Z
65         E1=DSQRT(AM1*AM1+P1S)
66         E2=DSQRT(AM2*AM2+P2S)
67         CALL LTR8(Z1,T1,V12Z,GAMZ,Z1,T1)
68         CALL LTR8(Z2,T2,V12Z,GAMZ,Z2,T2)
69       END IF        
70 C===> Pair reference frame       ============
71       P1=DSQRT(P1S)
72       P2=DSQRT(P2S)
73       E12=E1+E2
74       P12X=P1X+P2X
75       P12Y=P1Y+P2Y
76       P12Z=P1Z+P2Z
77       P12S=P12X**2+P12Y**2+P12Z**2
78       P12 =DSQRT(P12S)
79       AM12S=E12*E12-P12S
80       AM12=DSQRT(AM12S)
81       EPM=E12+AM12
82       P112=P1X*P12X+P1Y*P12Y+P1Z*P12Z
83       H1=(P112/EPM-E1)/AM12
84       PPX=P1X+P12X*H1
85       PPY=P1Y+P12Y*H1
86       PPZ=P1Z+P12Z*H1
87       EE=(E12*E1-P112)/AM12
88       AKS=EE**2-AM1**2
89       AK=DSQRT(AKS)
90       CVK=(P12X*PPX+P12Y*PPY+P12Z*PPZ)/(P12*AK)
91       V=P12/E12 
92       V12T=P12T/SQRT(AM12S+P12TS) ! transverse velocity in LCMS   
93 C---> Coordinates -----------------------------
94       XS=X1-X2
95       YS=Y1-Y2
96       ZS=Z1-Z2
97       TS=T1-T2  
98       RS12=XS*P12X+YS*P12Y+ZS*P12Z
99       H1=(RS12/EPM-TS)/AM12
100
101       X=XS+P12X*H1
102       Y=YS+P12Y*H1
103       Z=ZS+P12Z*H1
104       T=(E12*TS-RS12)/AM12
105       RPS=X*X+Y*Y+Z*Z
106       RP=DSQRT(RPS)
107
108
109       RETURN
110       END
111 C====       
112       SUBROUTINE LTR8(Z,T,BETA,GAMMA,ZT,TT)
113 C===> Lorentz Transf. of Z(Pz) and T(E) to moving ref. frame.(REAL*8) 
114 CInp: Z,T-Zcoord,Time before tr., BETA,GAMMA- velocity, Lor.fact.
115 COut: ZT,TT- "    "   after transformation.
116 C==== ===============================================================
117       IMPLICIT REAL*8 (A-H,O-Z)
118       ZH=GAMMA*(Z-BETA*T)     
119       TT=GAMMA*(T-BETA*Z)
120       ZT=ZH
121       RETURN
122       END
123 C====       
124       
125       SUBROUTINE LTR4(Z,T,BETA,GAMMA,ZT,TT)
126 C===> Lorentz Transf. of Z(Pz) and T(E) to moving ref. frame.(real*4) 
127 CInp: Z,T-Zcoord,Time before tr., BETA,GAMMA- velocity, Lor.fact.
128 COut: ZT,TT- "    "   after transformation.
129 C==== ===============================================================
130       ZH=GAMMA*(Z-BETA*T)     
131       TT=GAMMA*(T-BETA*Z)
132       ZT=ZH
133       RETURN
134       END
135 C====           
136       SUBROUTINE ROT8(X,Y,SF,CF,XR,YR)
137 C===> Rotation with the angle f. (REAL*8)
138 CInp: X,Y-coord. before rotation; SF=sin(f), CF=cos(f),
139 COut: XR,YR - coordinates after rotation.
140 C==== =================================================
141       IMPLICIT REAL*8 (A-H,O-Z)
142       XH=X*CF+Y*SF !Y              
143       YR=Y*CF-X*SF !   _-X'   
144       XR=XH        ! _- f      
145       RETURN       !------>
146       END          !     X
147
148       SUBROUTINE SETPDIST(R)
149 C=====Just sets distance between particles
150       IMPLICIT REAL*8 (A-H,O-Z)
151       COMMON/FSI_PRF/PPX,PPY,PPZ,AK,AKS, ! momenta in PRF
152      1               X,Y,Z,T,RP,RPS
153       RPS=R
154       RP=R*R
155       RETURN
156       END
157
158
159
160
161
162
163
164
165
166
167
168