(file) Return to mc_shms_hut.f CVS log (file) (dir) Up to [HallC] / simc_gfortran / shms

  1 jones 1.2 	subroutine mc_shms_hut (m2,p,x_fp,dx_fp,y_fp,dy_fp,ms_flag,
  2                > wcs_flag,
  3                > decay_flag,dflag,resmult,spec,ok_hut,zinit,pathlen,
  4                > spectr)
  5 gaskelld 1.1 C----------------------------------------------------------------------
  6              C
  7 jones    1.2 C Monte-Carlo of SHMS detector hut.
  8 gaskelld 1.1 C	Note that we only pass on real*4 variables to the subroutine.
  9              C	This will make life easier for portability.
 10              C----------------------------------------------------------------------
 11              
 12              	implicit 	none
 13              
 14 jones    1.2 	include '../shms/struct_shms.inc'
 15 gaskelld 1.1 	include '../spectrometers.inc'
 16 jones    1.2 	include '../shms/hut.inc'
 17 gaskelld 1.1 
 18              C Math constants
 19              
 20              	real*8 pi,d_r,r_d,root
 21              
 22              	parameter (pi = 3.141592654)
 23              	parameter (d_r = pi/180.)
 24              	parameter (r_d = 180./pi)
 25              	parameter (root = 0.707106781)		!square root of 1/2
 26              
 27 jones    1.2 	logical*4 cer_flag
 28              	logical*4 vac_flag
 29                      parameter (cer_flag = .true.) ! TRUE means 1st Cerenkov (Ar/Ne) is in front of chambers
 30                      parameter (vac_flag = .false.) ! FALSE means helium bag replaces 1st Cerenkov (Ar/Ne) 
 31              
 32              c	common /hutflag/ cer_flag,vac_flag
 33              
 34 gaskelld 1.1 C all parameters, later to take from .parm files
 35              C The arguments
 36              
 37              	real*8	p,m2			!momentum and mass of particle
 38              	real*8	x_fp,y_fp,dx_fp,dy_fp	!Focal plane values to return
 39              	logical	ms_flag, wcs_flag	!particle, m_scat, wc_smear
 40              	logical	ok_hut			!true if particle makes it
 41              	logical decay_flag,dflag
 42 jones    1.2 	real*8	xcal,ycal		!Position of track at calorimeter.
 43 gaskelld 1.1 	real*8 pathlen
 44 jones    1.2 	real*8 resmult				!DC resolution factor
 45 gaskelld 1.1 	real*8 zinit
 46 jones    1.2         real*4 spec(58)
 47 gaskelld 1.1 
 48              c external function
 49              	real*8 gauss1
 50              C Local declarations.
 51              
 52 jones    1.2 	integer*4	spectr	!spectrometer number (for tune-dependent stuff)
 53 gaskelld 1.1 	integer*4	i,iplane,jchamber,npl_off
 54              	integer*4	chan	/1/
 55              
 56              	real*8	radw,drift
 57              c need real*4 for cernlib routine lfut
 58              	real*4	xdc(12),ydc(12),zdc(12)		!positions at d.c. planes
 59              	real*4	x0,y0,dx,dy			!track fitting temporaries
 60              	real*4	badf				!temporaries
 61              
 62              	real*8  tmpran1,tmpran2
 63              	real*8   nsig_max
 64              	real*8 hdc_del_plane
 65              	parameter (nsig_max=99.0d0)
 66              c mkj
 67              	logical use_det_cut
 68              	parameter (use_det_cut=.true.)
 69 jones    1.2 !	parameter (use_det_cut=.false.)
 70 gaskelld 1.1 
 71              C ================================ Executable Code =============================
 72              
 73              C Initialize some variables
 74              
 75 jones    1.2 !	write (6,*) x_fp, y_fp, dx_fp, dy_fp, cerflag
 76 gaskelld 1.1 	hdc_del_plane = hdc_thick + hdc_wire_thick + hdc_cath_thick
 77              
 78              C Initialize ok_hut to zero
 79              
 80              	ok_hut = .false.
 81              c
 82              	resmult= 1.0
 83              
 84 jones    1.2 
 85 gaskelld 1.1 C Initialize the xdc and ydc arrays to zero
 86              
 87              	do i=1,12
 88              	  xdc(i) = 0.
 89              	  ydc(i) = 0.
 90              	enddo
 91              
 92              C------------------------------------------------------------------------------C
 93              C                           Top of loop through hut                            C
 94              C------------------------------------------------------------------------------C
 95              
 96 jones    1.2 
 97                      if (cer_flag) then
 98 gaskelld 1.1 	drift = hcer_1_zentrance
 99              	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
100 jones    1.2 	   radw = hfoil_exit_thick/hfoil_exit_radlen
101              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
102              	 radw = hcer_entr_thick/hcer_entr_radlen
103              	 if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
104              	 drift = hcer_1_zmirror - hcer_1_zentrance-hcer_mirglass_thick/2
105              	 radw = drift/hcer_1_radlen
106              	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
107              	if(ms_flag ) call musc_ext(m2,p,radw,drift,
108                   > dydzs,dxdzs,ys,xs)
109 gaskelld 1.1 
110              
111 jones    1.2 	radw = hcer_mirglass_thick/hcer_mirglass_radlen
112              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
113              c
114              	drift = hcer_mirback1_thick/2+hcer_mirglass_thick/2
115              	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
116              	radw = hcer_mirback1_thick/hcer_mirback1_radlen
117              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
118              c
119              	drift = hcer_mirback2_thick/2+hcer_mirback1_thick/2
120              	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
121              	radw = hcer_mirback2_thick/hcer_mirback2_radlen
122              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
123              c
124              	drift = hcer_mirback3_thick/2+hcer_mirback2_thick/2
125              	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
126              	radw = hcer_mirback3_thick/hcer_mirback3_radlen
127              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
128              c
129              	drift = hcer_mirback4_thick/2+hcer_mirback3_thick/2
130 gaskelld 1.1 	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
131 jones    1.2 	radw = hcer_mirback4_thick/hcer_mirback4_radlen
132              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
133 gaskelld 1.1 
134 jones    1.2 	drift = hcer_1_zexit - hcer_1_zmirror -hcer_mirglass_thick/2
135                   > -hcer_mirback1_thick-hcer_mirback2_thick-hcer_mirback3_thick-hcer_mirback4_thick/2
136 gaskelld 1.1 	radw = drift/hcer_1_radlen
137 jones    1.2 	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
138              	if(ms_flag) call musc_ext(m2,p,radw,drift,
139                   > dydzs,dxdzs,ys,xs)
140 gaskelld 1.1 	radw = hcer_exit_thick/hcer_exit_radlen
141 jones    1.2 	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
142                      
143                     else
144              c  if vaccum pipe drift to pipe exit which is at same zpos as the cerenkov exit window. 
145                        if (vac_flag) then
146                 	   drift =  hcer_1_zexit 
147               	   call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
148              	   radw = hfoil_exit_thick/hfoil_exit_radlen
149              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
150                        else ! helium bag
151                 	   drift = hcer_1_zentrance 
152               	   call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
153              	   radw = hfoil_exit_thick/hfoil_exit_radlen
154              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
155              	   radw = helbag_al_thick/helbag_al_radlen ! assume no distance to Helium bag Al mylar
156              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
157              	   radw = helbag_mylar_thick/helbag_mylar_radlen ! assume no distance to Helium bag Al mylar
158              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
159              	   drift = hcer_1_zexit - hcer_1_zentrance
160              	   radw = drift/helbag_hel_radlen
161                         call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
162 jones    1.2 	   if(ms_flag) call musc_ext(m2,p,radw,drift,
163                   > dydzs,dxdzs,ys,xs)
164              	   radw = helbag_al_thick/helbag_al_radlen ! assume no distance to Helium bag Al mylar
165              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
166              	   radw = helbag_mylar_thick/helbag_mylar_radlen ! assume no distance to Helium bag Al mylar
167              	   if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
168                        endif
169 gaskelld 1.1         endif
170              
171 jones    1.2         
172 gaskelld 1.1 
173              C Go to first drift chamber set
174              C For simplicity, perform air MS (probably negligeable) at before drift
175              C instead of 1/2 way through.
176              
177              *	write (6,*) 'made it to the first drift chamber'
178 jones    1.2 	drift = (hdc_1_zpos - 0.5*hdc_nr_plan*hdc_del_plane) 
179                   > - hcer_1_zexit
180 gaskelld 1.1 	radw = drift/hair_radlen
181              	call project(xs,ys,drift,.false.,dflag,m2,p,pathlen)
182              	if (ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
183 jones    1.2 c	if (1 .eq. 1) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
184 gaskelld 1.1 
185              	jchamber = 1
186              	radw = hdc_entr_thick/hdc_entr_radlen
187              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
188              	npl_off = (jchamber-1)*hdc_nr_plan
189              	do iplane = 1,hdc_nr_plan
190              	  radw = hdc_cath_thick/hdc_cath_radlen
191              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
192              	  drift = 0.5*hdc_thick
193              	  radw = drift/hdc_radlen
194              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
195              	  drift = drift + hdc_cath_thick
196              	  call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
197              	  radw = hdc_wire_thick/hdc_wire_radlen
198              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
199              	  if(wcs_flag) then
200              	    tmpran1 = gauss1(nsig_max)	!gaussian, truncated at 99 sigma.
201              	    tmpran2 = gauss1(nsig_max)
202              	  else
203              	    tmpran1 = 0.
204              	    tmpran2 = 0.
205 gaskelld 1.1 	  endif
206 jones    1.2 	  xdc(npl_off+iplane) = xs + hdc_sigma(npl_off+iplane)
207                   > *tmpran1*resmult
208              	  ydc(npl_off+iplane) = ys + hdc_sigma(npl_off+iplane)
209                   > *tmpran2*resmult
210 gaskelld 1.1 	  if (iplane.eq.2 .or. iplane.eq.5) then
211              	    xdc(npl_off+iplane) = 0.   !y plane, no x information
212              	  else
213              c	     write(*,*) ' iplane = ',iplane
214              	    ydc(npl_off+iplane) = 0.   !x-like plane, no y info
215              	  endif
216              *	  write (6,*) 'i am still in the first drift chamber'
217              	  drift = 0.5*hdc_thick
218              	  radw = drift/hdc_radlen
219              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
220              	  drift = drift + hdc_wire_thick
221              	  call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
222              	enddo
223              	radw = hdc_exit_thick/hdc_exit_radlen
224              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
225              	if (xs.gt.(hdc_1_bot-hdc_1x_offset) .or.
226                   >      xs.lt.(hdc_1_top-hdc_1x_offset) .or.
227                   >      ys.gt.(hdc_1_left-hdc_1y_offset) .or.
228                   >      ys.lt.(hdc_1_right-hdc_1y_offset) ) then
229              	  shmsSTOP_dc1 = shmsSTOP_dc1 + 1
230              c	  write(6,*) 'Lost in DC! delta,xp,yp',dpps,dxdzs,dydzs
231 jones    1.2 	  if (use_det_cut) then
232              	     stop_id = 18
233              	     goto 500
234              	  endif
235 gaskelld 1.1 	endif
236 jones    1.2         spec(39)=xs
237                      spec(40)=ys
238 gaskelld 1.1 	radw = hdc_cath_thick/hdc_cath_radlen
239              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
240              
241              C at last cathode foil of first drift chamber set, drift to next
242              
243              *	write (6,*) 'made it to the second drift chamber in the hut'
244              	drift = hdc_2_zpos - hdc_1_zpos - hdc_nr_plan*hdc_del_plane
245              C       Break this into 2 parts to properly account for decay.
246              C       We've already done decay up to the half-way point between the chambers.
247              	call project(xs,ys,drift/2.0,.false.,dflag,m2,p,pathlen)
248              	call project(xs,ys,drift/2.0,decay_flag,dflag,m2,p,pathlen)
249              	radw = drift/hair_radlen
250              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
251              
252              	jchamber = 2
253              	radw = hdc_entr_thick/hdc_entr_radlen
254              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
255              	npl_off = (jchamber-1)*hdc_nr_plan
256              	do iplane = 1,hdc_nr_plan
257              	  radw = hdc_cath_thick/hdc_cath_radlen
258              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
259 gaskelld 1.1 	  drift = 0.5*hdc_thick
260              	  radw = drift/hdc_radlen
261              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
262              	  drift = drift + hdc_cath_thick
263              	  call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
264              	  radw = hdc_wire_thick/hdc_wire_radlen
265              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
266              	  if(wcs_flag) then
267              	    tmpran1 = gauss1(nsig_max)	!gaussian, truncated at 99 sigma.
268              	    tmpran2 = gauss1(nsig_max)
269              	  else
270              	    tmpran1 = 0.
271              	    tmpran2 = 0.
272              	  endif
273 jones    1.2 	  xdc(npl_off+iplane) = xs + hdc_sigma(npl_off+iplane)
274                   > *tmpran1*resmult
275              	  ydc(npl_off+iplane) = ys + hdc_sigma(npl_off+iplane)
276                   > *tmpran2*resmult
277 gaskelld 1.1 	  if (iplane.eq.2 .or. iplane.eq.5) then
278              	    xdc(npl_off+iplane) = 0.   !y plane, no x information
279              	  else
280              	    ydc(npl_off+iplane) = 0.   !x-like plane, no y info
281              	  endif
282              	  drift = 0.5*hdc_thick
283              	  radw = drift/hdc_radlen
284              	  if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
285              	  drift = drift + hdc_wire_thick
286              	  call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
287              	enddo
288              	radw = hdc_exit_thick/hdc_exit_radlen
289              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
290              	if (xs.gt.(hdc_2_bot-hdc_2x_offset) .or.
291                   >      xs.lt.(hdc_2_top-hdc_2x_offset) .or.
292                   >      ys.gt.(hdc_2_left-hdc_2y_offset) .or.
293                   >      ys.lt.(hdc_2_right-hdc_2y_offset) ) then
294              	  shmsSTOP_dc2 = shmsSTOP_dc2 + 1
295 jones    1.2 	  if (use_det_cut) then
296              	     stop_id = 19
297              	     goto 500
298              	  endif
299 gaskelld 1.1 	endif
300 jones    1.2         spec(41)=xs
301                      spec(42)=ys
302 gaskelld 1.1 	radw = hdc_cath_thick/hdc_cath_radlen
303              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
304              
305              C at last cathode foil of second drift chamber set, drift to the 1st hodoscope
306              
307 jones    1.2 	drift = hscin_1x_zpos - hdc_2_zpos - 0.5*hdc_nr_plan
308                   > *hdc_del_plane
309 gaskelld 1.1 	radw = drift/hair_radlen
310              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
311              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
312              	if (ys.gt.(hscin_1x_left+hscin_1y_offset) .or.
313                   >      ys.lt.(hscin_1x_right+hscin_1y_offset)) then
314              	  shmsSTOP_s1 = shmsSTOP_s1 + 1
315 jones    1.2 	  if (use_det_cut) then
316              	     stop_id=20
317              	     goto 500
318              	  endif
319 gaskelld 1.1 	endif
320 jones    1.2         spec(44)=ys
321 gaskelld 1.1 	radw = hscin_1x_thick/hscin_radlen
322              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
323              	drift = hscin_1y_zpos - hscin_1x_zpos
324              	radw = drift/hair_radlen
325              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
326              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
327              	if (xs.gt.(hscin_1y_bot+hscin_1x_offset) .or.
328                   >      xs.lt.(hscin_1y_top+hscin_1x_offset)) then
329              	  shmsSTOP_s1 = shmsSTOP_s1 + 1
330 jones    1.2 	  if (use_det_cut) then
331              	     stop_id=21
332              	     goto 500
333              	  endif
334 gaskelld 1.1 	endif
335 jones    1.2         spec(43)=xs
336 gaskelld 1.1  	radw = hscin_1y_thick/hscin_radlen
337              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
338              
339              C finished first hodoscope, drift to the second cherenkov
340              
341              *	write (6,*) 'made it to the second cherenkov in the hut'
342              	drift = hcer_2_zentrance - hscin_1y_zpos
343              	radw = drift/hair_radlen
344              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
345              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
346              
347              	radw = hcer_2_entr_thick/hcer_2_entr_radlen
348              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
349              
350              	drift = hcer_2_zmirror - hcer_2_zentrance
351              	radw = drift/hcer_2_radlen
352              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
353              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
354              
355              	radw = hcer_mir_thick/hcer_mir_radlen
356              
357 gaskelld 1.1 	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
358              
359              	drift = hcer_2_zexit - hcer_2_zmirror
360              	radw = drift/hcer_2_radlen
361              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
362              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
363              
364              	radw = hcer_2_exit_thick/hcer_2_exit_radlen
365              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
366              
367              C drift to 2nd hodoscope
368              
369              	drift = hscin_2x_zpos - hcer_2_zexit
370              	radw = drift/hair_radlen
371              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
372              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
373              	if (ys.gt.(hscin_2x_left+hscin_2y_offset) .or.
374                   >      ys.lt.(hscin_2x_right+hscin_2y_offset)) then
375              	  shmsSTOP_s3 = shmsSTOP_s3 + 1
376 jones    1.2 	  if (use_det_cut) then
377              	     stop_id = 22
378              	     goto 500
379              	  endif
380 gaskelld 1.1 	endif
381 jones    1.2         spec(46)=ys
382 gaskelld 1.1 	radw = hscin_2x_thick/hscin_radlen
383              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
384              	drift = hscin_2y_zpos - hscin_2x_zpos
385              	radw = drift/hair_radlen
386              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
387              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
388              	if (xs.gt.(hscin_2y_bot+hscin_2x_offset) .or.
389                   >      xs.lt.(hscin_2y_top+hscin_2x_offset)) then
390              	  shmsSTOP_s2 = shmsSTOP_s2 + 1
391 jones    1.2 	  if (use_det_cut) then
392              	     stop_id=23
393              	     goto 500
394              	  endif
395 gaskelld 1.1 	endif
396 jones    1.2         spec(45)=xs
397 gaskelld 1.1 	radw = hscin_2y_thick/hscin_radlen
398              	if(ms_flag) call musc(m2,p,radw,dydzs,dxdzs)
399              
400              C Don't need to drift to calorimeter unless it's required in your trigger.
401              C Note that even with the standard PID trigger, the calorimeter is NOT
402              C required, since the trigger needs either the cerenkov OR the calorimeter.
403              C There is a seperate fiducial cut needed if you require the calorimeter
404              C in you analysis.  That cut is applied AFTER fitting the track (see below).
405              
406              	drift = hcal_4ta_zpos - hscin_2y_zpos
407              	radw = drift/hair_radlen
408              	call project(xs,ys,drift,decay_flag,dflag,m2,p,pathlen)
409              	if(ms_flag) call musc_ext(m2,p,radw,drift,dydzs,dxdzs,ys,xs)
410              	if (ys.gt.hcal_left .or. ys.lt.hcal_right .or.
411                   >	   xs.gt.hcal_bottom .or. xs.lt.hcal_top) then
412              	  shmsSTOP_cal = shmsSTOP_cal + 1
413 jones    1.2 	  if (use_det_cut) then
414              	     stop_id=24
415              	     goto 500
416              	  endif
417 gaskelld 1.1 	endif
418 jones    1.2         spec(47)=xs
419                      spec(48)=ys
420              
421              
422 gaskelld 1.1 
423              
424              C and fit track to give new focal plane values, use LFIT from GENLIB
425              
426              	do jchamber=1,hdc_nr_cham
427              	  npl_off = (jchamber-1)*hdc_nr_plan
428              	  do iplane=1,hdc_nr_plan
429              	    if (jchamber.eq.1) zdc(npl_off+iplane) = hdc_1_zpos +
430                   >          (iplane-0.5-0.5*hdc_nr_plan)*hdc_del_plane
431              	    if (jchamber.eq.2) zdc(npl_off+iplane) = hdc_2_zpos +
432                   >          (iplane-0.5-0.5*hdc_nr_plan)*hdc_del_plane
433              	  enddo
434              	enddo
435              	call lfit(zdc,xdc,12,0,dx,x0,badf)
436              	call lfit(zdc,ydc,12,0,dy,y0,badf)
437              
438              
439              	x_fp = x0
440              	y_fp = y0
441              	dx_fp = dx
442              	dy_fp = dy
443 gaskelld 1.1 
444              C If you use a calorimeter cut in your analysis, the engine applied a
445              C a fiducial cut at the calorimeter.  This is based on the position of the
446              C TRACK at the calorimeter, not the real position of the event.  Go to the
447              C back of the calorimeter since engine uses a FID cut at the back.
448              C The standard fiducial cut is 5 cm from the edges of the block.
449              
450              *	write (6,*) 'at the shower counter in the hut'
451              	xcal = x_fp + dx_fp * hcal_4ta_zpos
452              	ycal = y_fp + dy_fp * hcal_4ta_zpos
453              	if (ycal.gt.(hcal_left-5.0) .or. ycal.lt.(hcal_right+5.0) .or.
454                   >	   xcal.gt.(hcal_bottom-5.0) .or. xcal.lt.(hcal_top+5.0)) then
455              	  shmsSTOP_cal = shmsSTOP_cal + 1
456 jones    1.2 	  if (use_det_cut) then
457              	     stop_id=25
458              	     goto 500
459              	  endif
460 gaskelld 1.1 	endif
461 jones    1.2         spec(49)=xs
462                      spec(50)=ys
463 gaskelld 1.1 
464              	ok_hut = .true.
465              
466              C We are done with this event, whether GOOD or BAD.
467              
468              500	continue
469              
470              C ALL done!
471              	close (unit=chan)
472              
473              	return
474              	end

Analyzer/Replay: Mark Jones, Documents: Stephen Wood
Powered by
ViewCVS 0.9.2-cvsgraph-1.4.0