1 |
|
2 |
************************************************************* |
3 |
* |
4 |
* Routine to compute the NPOINT track intersection points |
5 |
* with planes of z-coordinate given by ZIN |
6 |
* given the track parameters |
7 |
* |
8 |
* The routine is based on GRKUTA, which computes the |
9 |
* trajectory of a charged particle in a magnetic field |
10 |
* by solving the equatoins of motion with Runge-Kuta method |
11 |
* |
12 |
* Variables that have to be assigned when the subroutine |
13 |
* is called: |
14 |
* |
15 |
* ZIN(1-NPOINT) ----> z coordinates of the planes |
16 |
* AL_P(1-5) ----> track-parameter vector |
17 |
* |
18 |
* NB !!! |
19 |
* The routine works properly only if the |
20 |
* planes are numbered in descending order starting from the |
21 |
* reference plane (ZINI) |
22 |
* |
23 |
************************************************************** |
24 |
|
25 |
SUBROUTINE TRACK(NPOINT,ZIN,XOUT,YOUT,AL_P,IFAIL) |
26 |
|
27 |
IMPLICIT DOUBLE PRECISION (A-H,O-Z) |
28 |
|
29 |
DIMENSION VECT(7),VECTINI(7),VOUT(7) |
30 |
DATA TOLL/1.d-8/ |
31 |
* tolerance in reaching the next plane during the tracking procedure |
32 |
* ----------------------------------------------- |
33 |
* I/O parameters |
34 |
PARAMETER (NPOINT_MAX=100) |
35 |
DIMENSION ZIN(NPOINT_MAX) |
36 |
DIMENSION XOUT(NPOINT_MAX),YOUT(NPOINT_MAX) |
37 |
DIMENSION AL_P(5) |
38 |
* ----------------------------------------------- |
39 |
DATA ZINI/23.5/ !z coordinate of the reference plane |
40 |
|
41 |
* ================================================================== |
42 |
* divide the track in two parts: below and above the reference plane |
43 |
* ================================================================== |
44 |
IUPDOWN=0 |
45 |
DO I=1,NPOINT |
46 |
IF(ZIN(I).LT.ZINI)THEN |
47 |
if(i.ne.1)IUPDOWN=I |
48 |
GOTO 88 |
49 |
ENDIF |
50 |
IUPDOWN=NPOINT+1 |
51 |
ENDDO |
52 |
88 CONTINUE |
53 |
|
54 |
* ================================================================== |
55 |
* track from reference plane DOWN |
56 |
* ================================================================== |
57 |
* parameters for GRKUTA |
58 |
IF(AL_P(5).NE.0) CHARGE=AL_P(5)/DABS(AL_P(5)) |
59 |
IF(AL_P(5).EQ.0) CHARGE=1. |
60 |
VOUT(1)=AL_P(1) |
61 |
VOUT(2)=AL_P(2) |
62 |
VOUT(3)=ZINI |
63 |
VOUT(4)=AL_P(3)*DCOS(AL_P(4)) |
64 |
VOUT(5)=AL_P(3)*DSIN(AL_P(4)) |
65 |
VOUT(6)=-1.*DSQRT(1.-AL_P(3)**2) |
66 |
IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5)) |
67 |
IF(AL_P(5).EQ.0.) VOUT(7)=1.E8 |
68 |
DO I=MAX(IUPDOWN,1),NPOINT |
69 |
step=vout(3)-zin(i) |
70 |
c$$$ print*,'DOWN ',i,' - Track from ', |
71 |
c$$$ $ vout(3),' to ',zin(i),' step ',step |
72 |
10 DO J=1,7 |
73 |
VECT(J)=VOUT(J) |
74 |
VECTINI(J)=VOUT(J) |
75 |
ENDDO |
76 |
11 continue |
77 |
CALL GRKUTA(CHARGE,STEP,VECT,VOUT) |
78 |
IF(VOUT(3).GT.VECT(3)) THEN |
79 |
IFAIL=1 |
80 |
PRINT *,'=== WARNING ===> tracciamento invertito (DOWN)' |
81 |
print*,'charge',charge |
82 |
print*,'vect',vect |
83 |
print*,'vout',vout |
84 |
print*,'step',step |
85 |
RETURN |
86 |
ENDIF |
87 |
Z=VOUT(3) |
88 |
IF(Z.LE.ZIN(I)+TOLL.AND.Z.GE.ZIN(I)-TOLL) GOTO 100 |
89 |
IF(Z.GT.ZIN(I)+TOLL) GOTO 10 |
90 |
IF(Z.LE.ZIN(I)-TOLL) THEN |
91 |
STEP=STEP*(ZIN(I)-VECT(3))/(Z-VECT(3)) |
92 |
DO J=1,7 |
93 |
VECT(J)=VECTINI(J) |
94 |
ENDDO |
95 |
GOTO 11 |
96 |
ENDIF |
97 |
100 XOUT(I)=VOUT(1) |
98 |
YOUT(I)=VOUT(2) |
99 |
ZIN(I)=VOUT(3) |
100 |
ENDDO |
101 |
|
102 |
|
103 |
|
104 |
* ================================================================== |
105 |
* track from refernce plane UP |
106 |
* ================================================================== |
107 |
* parameters for GRKUTA: |
108 |
* -opposite charge |
109 |
* -opposite momentum direction |
110 |
IF(AL_P(5).NE.0) CHARGE=-AL_P(5)/DABS(AL_P(5)) |
111 |
IF(AL_P(5).EQ.0) CHARGE=-1. |
112 |
VOUT(1)=AL_P(1) |
113 |
VOUT(2)=AL_P(2) |
114 |
VOUT(3)=ZINI |
115 |
VOUT(4)=-AL_P(3)*DCOS(AL_P(4)) |
116 |
VOUT(5)=-AL_P(3)*DSIN(AL_P(4)) |
117 |
VOUT(6)=1.*DSQRT(1.-AL_P(3)**2) |
118 |
IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5)) |
119 |
IF(AL_P(5).EQ.0.) VOUT(7)=1.E8 |
120 |
DO I=MIN((IUPDOWN-1),NPOINT),1,-1 |
121 |
step=vout(3)-zin(i) |
122 |
step = -step |
123 |
c$$$ print*,'UP ',i,' - Track from ', |
124 |
c$$$ $ vout(3),' to ',zin(i),' step ',step |
125 |
20 DO J=1,7 |
126 |
VECT(J)=VOUT(J) |
127 |
VECTINI(J)=VOUT(J) |
128 |
ENDDO |
129 |
22 continue |
130 |
CALL GRKUTA(CHARGE,STEP,VECT,VOUT) |
131 |
IF(VOUT(3).LT.VECT(3)) THEN |
132 |
IFAIL=1 |
133 |
PRINT *,'=== WARNING ===> tracciamento invertito (UP)' |
134 |
print*,'charge',charge |
135 |
print*,'vect',vect |
136 |
print*,'vout',vout |
137 |
print*,'step',step |
138 |
RETURN |
139 |
ENDIF |
140 |
Z=VOUT(3) |
141 |
IF(Z.LE.ZIN(I)+TOLL.AND.Z.GE.ZIN(I)-TOLL) GOTO 200 |
142 |
IF(Z.LT.ZIN(I)-TOLL) GOTO 20 |
143 |
IF(Z.GE.ZIN(I)+TOLL) THEN |
144 |
STEP=STEP*(ZIN(I)-VECT(3))/(Z-VECT(3)) |
145 |
DO J=1,7 |
146 |
VECT(J)=VECTINI(J) |
147 |
ENDDO |
148 |
GOTO 22 |
149 |
ENDIF |
150 |
200 XOUT(I)=VOUT(1) |
151 |
YOUT(I)=VOUT(2) |
152 |
ZIN(I)=VOUT(3) |
153 |
|
154 |
ENDDO |
155 |
|
156 |
RETURN |
157 |
END |
158 |
|