/[PAMELA software]/gpamela/gptrd/gputrd.F
ViewVC logotype

Annotation of /gpamela/gptrd/gputrd.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.2 - (hide annotations) (download)
Tue Jun 21 02:42:35 2005 UTC (19 years, 5 months ago) by cafagna
Branch: MAIN
CVS Tags: v4r4, v4r5, v4r6, v4r7, v4r2, v4r3, v4r8, v4r9, v4r14, v4r12, v4r13, v4r10, v4r11, HEAD
Changes since 3.1: +5 -4 lines
Major modification to the geometry and to the random number chain

1 cafagna 3.1 *
2 cafagna 3.2 * $Id: gputrd.F,v 3.1.1.1 2002/07/11 16:02:01 cafagna Exp $
3     *
4     * $Log: gputrd.F,v $
5     * Revision 3.1.1.1 2002/07/11 16:02:01 cafagna
6     * First GPAMELA release on CVS
7 cafagna 3.1 *
8     *
9     *CMZ : 3.00/00 07/02/2002 12.41.53 by Unknown
10     *CMZ : 2.01/00 05/04/2000 14.35.18 by Marialuigia Ambriola
11     *CMZ : 2.00/00 29/02/2000 10.23.24 by Francesco Cafagna
12     *CMZ : 1.02/00 09/02/2000 17.22.16 by Francesco Cafagna
13     *CMZ : 1.00/02 04/04/96 16.47.16 by Francesco Cafagna
14     *-- Author : Francesco Cafagna 21/02/96
15     SUBROUTINE GPUTRD(IACT,IS,ID,IPA,IT,DELOSS,PATH,
16     + TRAPAR,NUMVOL,IMEC)
17     ************************************************************************
18     * *
19     * To collect and store the hit structure for TRD *
20     * *
21     * Variables definition: *
22     * IN: *
23     * IACT, integer specifing the action to be taken. It is the INWVOL *
24     * variable in GCTRAK common *
25     * IS , set number *
26     * ID , detector number *
27     * IPA , particle number *
28     * IT , track number *
29     * DELOSS, energy loss in the step *
30     * PATH , current track lenght *
31     * TRAPAR, track parameter, is the VECT vector in GCTRAK common *
32     * NUMVOL, integr array of numbers identifying the DETECTOR *
33     * IMEC , integer indicating the LOSS mecanism position inside NMEC *
34     * vector, zero if not present *
35     * *
36     * *
37     * Called by: GUSTEP *
38     * Author: Francesco Cafagna, 21/02/96 16.13.51 *
39     * *
40     ************************************************************************
41     #include "gphit.inc"
42     #include "gcunit.inc"
43     #include "gptotr.inc"
44     #if defined(GPAMELA_GARFIELD)
45     #include "gctrak.inc"
46     #include "gckine.inc"
47     #endif
48     *
49     INTEGER IACT,IS,ID,IPA,IT,NUMVOL(20),IMEC,IDHIT
50     REAL DELOSS,PATH,TRAPAR(7),VHIT(NHTRD)
51     LOGICAL SAVE
52     #if defined(GPAMELA_GARFIELD)
53     *
54     * Some variables need to call the GARFIELD interface
55     *
56     CHARACTER*20 CHJUNK
57     REAL GARXYZ(6),GARPAR(3),ECLTOT,RJUNK,RBJUNK(10)
58     INTEGER IFAIL,NCLUS,IJUNK,IWBUFF
59     #endif
60     *
61     * Track is inside a volume
62     *
63     IF(IACT.EQ.0) THEN
64     IF(IMEC.GT.0) THEN
65     SAVE = .TRUE.
66     VHIT(7) = DELOSS + VHIT(7)
67     ENDIF
68     ENDIF
69     *
70     * Entering a new volume or is a new track
71     *
72     IF(IACT.EQ.1) THEN
73     SAVE = .FALSE.
74     CALL VZERO(VHIT,NHTRD)
75     DO I=1,3
76     VHIT(I) = TRAPAR(I)
77     ENDDO
78     IF(IMEC.GT.0) THEN
79     SAVE = .TRUE.
80     VHIT(7) = DELOSS
81     ENDIF
82     VHIT(8) = PATH
83     VHIT(9) = IPA
84     VHIT(10)= TRAPAR(7)
85     IDHIT = -1
86     ENDIF
87     *
88     * Track is exiting current volume
89     *
90     IF(IACT.EQ.2) THEN
91     DO I=1,3
92     VHIT(I+3) = TRAPAR(I)
93     #if defined(GPAMELA_INTER)
94     * interactive case, we need the average position
95     VHIT(I) = (VHIT(I) + VHIT(I+3) )/2.
96     #endif
97     ENDDO
98     #if defined(GPAMELA_GARFIELD)
99     * Convert coordinates from the MARS to the local reference system
100     IF(IMEC.GT.0) THEN
101     CALL GMTOD(VHIT,GARXYZ,1)
102     CALL GMTOD(TRAPAR,GARXYZ(4),1)
103     C PRINT*,'GARXYZ,PATH=',(GARXYZ(I),I=1,6),PATH
104     * CALL GPTOGAR(GARXYZ,GARXYZ)
105     * CALL GPTOGAR(GARXYZ(4),GARXYZ(4))
106     *
107     * Get the particle infos
108     *
109     CALL GFPART(IPA,CHJUNK,IJUNK,GARPAR(1),GARPAR(2),
110     + RJUNK,RBJUNK,IWBUFF)
111     *
112     * Convert mass from GeV to Mev, calculate kinetic energy and convert it in MeV
113     *
114     GARPAR(3) =
115     + (SQRT(TRAPAR(7)**2+GARPAR(1)**2)-GARPAR(1))*1000.
116     GARPAR(1) = GARPAR(1)*1000.
117     *
118     * Let's calculate the clusters
119     *
120     CALL GPGACL(IPA,GARPAR,GARXYZ,ECLTOT,NCLUS)
121     *
122     * fill the hit structure (energy in GeV)
123     *
124     VHIT(13)=ECLTOT/1000.
125     C VHIT(14)=FLOAT(NCLUS)
126     VHIT(14)=INT(NCLUS)
127     C* ML: update the kinetic energy and then the momentum:
128     GEKINT=GEKIN-VHIT(13)
129     GEKIN=GEKINT
130     GETOT=GEKIN +AMASS
131     VECT(7)= SQRT((GETOT+AMASS)*GEKIN)
132     C Routine to find bin number in kinetic energy table stored in ELOW(NEKBIN)
133     CALL GEKBIN
134     C* END ML.
135     ENDIF
136     #endif
137     IF(IMEC.GT.0) THEN
138     SAVE = .TRUE.
139     VHIT(7) = DELOSS + VHIT(7)
140     ENDIF
141     VHIT(8) = PATH - VHIT(8)
142     *
143     * Store the hit
144     *
145     IF(IDHIT.EQ.-1) THEN
146     IF(TROK) THEN
147     VHIT(11)=ENPHTR*1.E-6
148     VHIT(12)=NPHTR
149     ELSE
150     WRITE(CHMAIL,10000)
151     CALL GMAIL(1,0)
152     ENDIF
153     IF(SAVE) CALL GSAHIT (IS,ID,IT,NUMVOL,VHIT,IDHIT)
154     IF (IDHIT.EQ.0) THEN
155     WRITE(CHMAIL,10100) IS,ID,IT
156     CALL GMAIL(1,0)
157     ENDIF
158     ELSE
159     WRITE(CHMAIL,10200) IS,ID,IT
160     CALL GMAIL(1,0)
161     ENDIF
162     ENDIF
163     *
164     * Track is exiting the set up
165     *
166     IF(IACT.EQ.3) THEN
167     *
168     * Check if the hit have been previously stored or not
169     *
170     IF(IDHIT.LT.0) THEN
171     DO I=1,3
172     VHIT(I+3) = TRAPAR(I)
173     #if defined(GPAMELA_INTER)
174     * interactive case, we need the average position
175     VHIT(I) = (VHIT(I) + VHIT(I+3) )/2.
176     #endif
177     ENDDO
178     IF(IMEC.GT.0) THEN
179     SAVE = .TRUE.
180     VHIT(7) = DELOSS + VHIT(7)
181     ENDIF
182     VHIT(8) = PATH - VHIT(8)
183     #if defined(GPAMELA_GARFIELD)
184     IF(IMEC.GT.0) THEN
185     * Convert coordinates from the MARS to the local reference system
186     CALL GMTOD(VHIT,GARXYZ,1)
187     CALL GMTOD(TRAPAR,GARXYZ(4),1)
188     * PRINT*,'GARXYZ,PATH=',(GARXYZ(I),I=1,6),PATH
189     * CALL GPTOGAR(GARXYZ,GARXYZ)
190     * CALL GPTOGAR(GARXYZ(4),GARXYZ(4))
191     *
192     * Get the particle infos
193     *
194     CALL GFPART(IPA,CHJUNK,IJUNK,GARPAR(1),GARPAR(2),
195     + RJUNK,RBJUNK,IWBUFF)
196     *
197     * Convert mass from GeV to Mev, calculate kinetic energy and convert it in MeV
198     *
199     GARPAR(3) =
200     + (SQRT(TRAPAR(7)**2+GARPAR(1)**2)-GARPAR(1))*1000.
201     GARPAR(1) = GARPAR(1)*1000.
202     *
203     * Let's calculate the clusters
204     *
205     CALL GPGACL(IPA,GARPAR,GARXYZ,ECLTOT,NCLUS)
206     *
207     * fill the hit structure (energy in GeV)
208     *
209     VHIT(13)=ECLTOT/1000.
210     C VHIT(14)=FLOAT(NCLUS)
211     VHIT(14)=INT(NCLUS)
212     C ML: update the kinetic energy and then th momentum:
213     GEKINT=GEKIN-VHIT(11)
214     GEKIN=GEKINT
215     GETOT=GEKIN +AMASS
216     VECT(7)= SQRT((GETOT+AMASS)*GEKIN)
217     C Routine to find bin number in kinetic energy table stored in ELOW(NEKBIN)
218     CALL GEKBIN
219     C END ML.
220     ENDIF
221     #endif
222     *
223     * Store the hit
224     *
225     IF(IDHIT.EQ.-1) THEN
226     IF(TROK) THEN
227     VHIT(11)=ENPHTR*1.E-6
228     VHIT(12)=NPHTR
229     ELSE
230     WRITE(CHMAIL,10300)
231     CALL GMAIL(1,0)
232     ENDIF
233     ENDIF
234     IF(SAVE) CALL GSAHIT (IS,ID,IT,NUMVOL,VHIT,IDHIT)
235     IF (IDHIT.EQ.0) THEN
236     WRITE(CHMAIL,10400) IS,ID,IT
237     CALL GMAIL(1,0)
238     ENDIF
239     ELSE
240     WRITE(CHMAIL,10500) IS,ID,IT
241     CALL GMAIL(1,0)
242     ENDIF
243     ENDIF
244    
245     10000 FORMAT(' GPUTRD error: TR process and his tuning will be ignored')
246     10100 FORMAT(' GPUTRD error: HIT have not be stored for SET='
247     + ,I4,', DET=',I4,', TRACK=',I6)
248     10200 FORMAT(' GPUTRD error: HIT have not be initialized for SET='
249     + ,I4,', DET=',I4,', TRACK=',I6)
250     10300 FORMAT(' GPUTRD error: TR process and his tuning will be ignored')
251     10400 FORMAT(' GPUTRD error: HIT have not be stored for SET='
252     + ,I4,', DET=',I4,', TRACK=',I6)
253     10500 FORMAT(' GPUTRD error: HIT have not be initialized for SET='
254     + ,I4,', DET=',I4,', TRACK=',I6)
255     RETURN
256     END

  ViewVC Help
Powered by ViewVC 1.1.23