ECCE @ EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
hirobo.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file hirobo.f
1 
2 C*********************************************************************
3 C THIS SUBROUTINE IS ONLY FOR THE USE OF HIJING TO ROTATE OR BOOST
4 C THE FOUR MOMENTUM ONLY
5 C*********************************************************************
6 
7  SUBROUTINE hirobo(THE,PHI,BEX,BEY,BEZ)
8 
9 C...Purpose: to perform rotations and boosts.
10  IMPLICIT DOUBLE PRECISION(d)
11  common/lujets/n,k(9000,5),p(9000,5),v(9000,5)
12  SAVE /lujets/
13  common/ludat1/mstu(200),paru(200),mstj(200),parj(200)
14  SAVE /ludat1/
15  dimension rot(3,3),pr(3),vr(3),dp(4),dv(4)
16 
17 C...Find range of rotation/boost. Convert boost to double precision.
18  imin=1
19  IF(mstu(1).GT.0) imin=mstu(1)
20  imax=n
21  IF(mstu(2).GT.0) imax=mstu(2)
22  dbx=bex
23  dby=bey
24  dbz=bez
25 
26 C...Check range of rotation/boost.
27  IF(imin.GT.mstu(4).OR.imax.GT.mstu(4)) THEN
28  CALL luerrm(11,'(LUROBO:) range outside LUJETS memory')
29  RETURN
30  ENDIF
31 
32 C...Rotate, typically from z axis to direction (theta,phi).
33  IF(the**2+phi**2.GT.1e-20) THEN
34  rot(1,1)=cos(the)*cos(phi)
35  rot(1,2)=-sin(phi)
36  rot(1,3)=sin(the)*cos(phi)
37  rot(2,1)=cos(the)*sin(phi)
38  rot(2,2)=cos(phi)
39  rot(2,3)=sin(the)*sin(phi)
40  rot(3,1)=-sin(the)
41  rot(3,2)=0.
42  rot(3,3)=cos(the)
43  DO 130 i=imin,imax
44  IF(k(i,1).LE.0) goto 130
45  DO 110 j=1,3
46  110 pr(j)=p(i,j)
47  DO 120 j=1,3
48  120 p(i,j)=rot(j,1)*pr(1)+rot(j,2)*pr(2)+rot(j,3)*pr(3)
49  130 CONTINUE
50  ENDIF
51 
52 C...Boost, typically from rest to momentum/energy=beta.
53  IF(dbx**2+dby**2+dbz**2.GT.1e-20) THEN
54  db=sqrt(dbx**2+dby**2+dbz**2)
55  IF(db.GT.0.99999999d0) THEN
56 C...Rescale boost vector if too close to unity.
57  CALL luerrm(3,'(LUROBO:) boost vector too large')
58  dbx=dbx*(0.99999999d0/db)
59  dby=dby*(0.99999999d0/db)
60  dbz=dbz*(0.99999999d0/db)
61  db=0.99999999d0
62  ENDIF
63  dga=1d0/sqrt(1d0-db**2)
64  DO 150 i=imin,imax
65  IF(k(i,1).LE.0) goto 150
66  DO 140 j=1,4
67  140 dp(j)=p(i,j)
68  dbp=dbx*dp(1)+dby*dp(2)+dbz*dp(3)
69  dgabp=dga*(dga*dbp/(1d0+dga)+dp(4))
70  p(i,1)=dp(1)+dgabp*dbx
71  p(i,2)=dp(2)+dgabp*dby
72  p(i,3)=dp(3)+dgabp*dbz
73  p(i,4)=dga*(dp(4)+dbp)
74  150 CONTINUE
75  ENDIF
76 
77  RETURN
78  END