/[PAMELA software]/DarthVader/TrackerLevel2/src/F77/cncomp.f
ViewVC logotype

Annotation of /DarthVader/TrackerLevel2/src/F77/cncomp.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (hide annotations) (download)
Fri May 19 13:15:55 2006 UTC (18 years, 6 months ago) by mocchiut
Branch: MAIN
Branch point for: DarthVader
Initial revision

1 mocchiut 1.1 *************************************************************************
2     *
3     * Subroutine cncomp.f
4     *
5     * iterates common noise computation subroutine (./cnoise.f) and cluster
6     * cutting subroutine (./cutcn.f) till no more clusters are found
7     *
8     *************************************************************************
9    
10     subroutine cncomp(i,j) !(view, VA1)
11    
12     include 'commontracker.f'
13     include 'common_reduction.f'
14     include 'calib.f'
15    
16     integer errflag !error flag to mark no signal free VA1
17    
18     integer clstr_old(nstrips_va1) !flag storage vector
19    
20     real signal(nstrips_va1) !"signal" (=adc-ped) value storage vector
21    
22     real smean, ssigma !"signal" mean and sigma
23     real cut !"strange" strip exclusion cut
24    
25     integer newclstr !flag to warn about new found clusters to be
26     ! excluded from common noise computation
27    
28    
29     c call HBOOK1(20000+100*i+j,' ',30,0.,30.,0.) !???
30    
31     c------------------------------------------------------------------------
32     c
33     c variables initialization
34     c
35     c------------------------------------------------------------------------
36     do k=1,nstrips_va1 !loops on strips
37     clstr(i,j,k)=1 !initializes signal affected strips flag
38     clstr_old(k)=1 !initializes signal affected strips storage
39     strange(i,j,k)=1 !initializes unusually high or low signal
40     enddo ! affected strips flag
41    
42     newclstr=1 !flag to warn about new found signal
43     ! affected strips
44    
45    
46    
47     c------------------------------------------------------------------------
48     c
49     c high or low signal affected strips exclusion: computes "signal" (=adc-ped)
50     c mean value and sigma, and cuts from common noise computation strips
51     c whose ABS(signal) exceeds scut*sigma
52     c
53     c------------------------------------------------------------------------
54     countme=0 !???
55     666 continue !???
56    
57     smean=0. !initialization
58     ssigma=0.
59     nstr=0
60    
61     do k=1,nstrips_va1
62     nstr=nstr+strange(i,j,k) !uses only
63     if(mod(i,2).eq.1) then !odd strip ---> Y view
64     signal(k)= - (DBLE(adc(i,j,k))-pedestal(i,j,k)) !negative signal
65     else !even strip ---> X view
66     signal(k)= DBLE(adc(i,j,k))-pedestal(i,j,k) !positive signal
67     endif
68    
69     smean=smean+signal(k)*strange(i,j,k)
70     ssigma=ssigma+(signal(k)**2)*strange(i,j,k)
71    
72     c call HFILL(10000+100*i+j,signal(k),0.,1.) !???
73     enddo
74    
75     smean=smean/nstr !strips value distribution mean
76    
77     ssigma=SQRT((ssigma/nstr)-smean**2) !strips value distribution sigma
78    
79     cut=scut*ssigma !exclusion cut
80    
81     do k=1,nstrips_va1
82     c call HFILL(20000+100*i+j,ABS(signal(k)-smean)/ssigma,0.,1.) !???
83     if(ABS(signal(k)-smean).gt.cut) then
84     c print*,i,j,k,signal(k),abs(signal(k)),cut,strange(i,j,k) !???
85     strange(i,j,k)=0 !marks strips exceeding cut
86     endif
87     enddo ! in order not to use them in CN computation
88    
89    
90     countme=countme+1 !???
91     if (countme.le.3) goto 666 !???
92    
93    
94     c------------------------------------------------------------------------
95     c
96     c common noise computation
97     c
98     c------------------------------------------------------------------------
99     do while(newclstr.eq.1) !loops on this VA1 till no new signal
100     ! affected strips are found
101    
102     newclstr=0 !to exit from loop if no new cluster is
103     ! found
104    
105     errflag=0
106    
107     call cnoise(i,j,errflag) !(view, VA1, error flag) computes common
108     ! noise
109    
110     c print*,cn(i,j) !???
111    
112     if(errflag.eq.1) goto 10 !goes to next VA1: this one has no signal
113     ! free strips...
114    
115     call cutcn(i,j) !(view, VA1) excludes clusters from
116     ! common noise calculation
117    
118     ncs=0 !initializes number of strips not excluded by cncut
119    
120     do k=1,nstrips_va1 !loops on strips
121     if(clstr(i,j,k).ne.clstr_old(k)) then !checks if there are
122     ! new found clusters, and if so sets
123     newclstr=1 ! newclstr flag = 1
124    
125     clstr_old(k)=clstr(i,j,k) !stores cluster flags in
126     endif ! clstr_old variable
127    
128     iok=strange(i,j,k)*bad(i,j,k)*clstr(i,j,k)
129    
130     ncs=ncs+iok !counts number of good strips for cn computation
131    
132     enddo
133    
134     enddo !ends do while loop when there are no new
135     ! clusters
136    
137     c call HFILL(666,FLOAT(ncs),0.,1.) !???
138    
139    
140     c$$$ if(ncs.lt.20) then !warns if too many strips have been excluded from CN
141     c$$$ ! computation
142     c$$$ print*,'cncomp: WARNING, LESS THAN 20 STRIPS PASSED CN CUT'
143     c$$$ $ //' ON VA1 ',j,', VIEW ',i !NB questo errore e' "un po'" in conflitto
144     c$$$ ! con quello che setta errflag (vedi cnoise.f)...
145     c$$$
146     c$$$ endif
147    
148     10 continue
149    
150     return
151     end
152    
153    
154    
155    
156     *************************************************************************
157     *
158     * Subroutine cnoise.f!DA COMMENTARE!???
159     *
160     * uses adc(nviews,nva1_view,nstrips_va1) and
161     * pedestal(nviews,nva1_view,nstrips_va1) variables to compute common noise,
162     * and fills cn(nviews,nva1_view) variable. in the computation only
163     * not-bad and not-signal-affected strips are used
164     * (bad(nviews,nva1_view,nstrips_va1) and
165     * clstr(nviews,nva1_view,nstrips_va1) flags)
166     *
167     * needs:
168     * - ./common_calib.f
169     *
170     * to be called inside ./cncomp.f
171     *
172     *************************************************************************
173    
174     subroutine cnoise(i,j,gulp) !(view, VA1)
175    
176     include 'commontracker.f'
177     include 'common_reduction.f'
178     include 'calib.f'
179    
180    
181     integer gulp !error flag
182    
183     ncn=0 !number of strips in cn computation
184     cn(i,j)=0 !initializes cn variable
185    
186     do k=1,nstrips_va1 !loops on strips
187     iok=strange(i,j,k)*bad(i,j,k)*clstr(i,j,k) !flag to mark strange, bad
188     ! or signal affected strips
189     ccc print*,i,j,k,strange(i,j,k),bad(i,j,k),clstr(i,j,k),iok !???
190    
191     cn(i,j)=cn(i,j) + (DBLE(adc(i,j,k)) - pedestal(i,j,k))*iok !sums ADC-PED
192     ! values to compute common noise
193     ncn = ncn + iok !counts number of strips in cn computation
194     enddo
195    
196     ccc print*,'ncn= ',ncn
197     if(ncn.eq.0) then !no signal free strips on this VA1...
198     print*,'cnoise: WARNING, NO SIGNAL FREE STRIPS ON VA1 ',j,
199     $ ', VIEW ',i
200     gulp=1
201     else
202     cn(i,j)=cn(i,j)/DBLE(ncn) !computes common noise
203     gulp=0 !resets error flag
204     endif
205    
206     return
207     end
208    
209    
210     *************************************************************************
211     *
212     * Subroutine cutcn.f!DA COMMENTARE!???
213     *
214     * excludes strips with particle signals and/or noisy strips from common
215     * noise calculation, marking their clstr(nviews,nva1_view,nstrips_va1)
216     * flag:
217     * clstr=0 ---> not to be used in CN computation
218     * clstr=1 ---> to be used in CN computation
219     *
220     * needs:
221     * - ./common_calib.f
222     *
223     * to be called inside ./cncomp.f
224     *
225     *************************************************************************
226    
227     subroutine cutcn(i,j) !(view, VA1)
228    
229     include 'commontracker.f'
230     include 'common_reduction.f'
231     include 'calib.f'
232    
233    
234     integer skip !used to skip strips (see later...)
235    
236     integer kr, kl !position indexes to check signal affected
237     ! strips on right and left side of cluster
238     ! seed
239     integer ir, il !flags to exit loop on reaching VA1 extremes
240    
241     real valuec !cluster seed signal
242     real cut,stripcut !cluster seed cut
243    
244     real valuel, valuer !left and right strips signal
245     real stripcnincut !strip include cut
246    
247     skip = 0 !initializes skip
248    
249     do k=1,nstrips_va1 !loops on strips searching for cluster seeds
250    
251     if(k.le.skip) goto 20 !continues only if k strip has not been
252     ! checked yet
253    
254     clstr(i,j,k)=1 !reinitializes strip to be used in CN!???
255     ! computation, in order to be able to exclude
256     ! different strips at every CN computation loop
257    
258     c------------------------------------------------------------------------
259     c
260     c selects cut according to view
261     c
262     c------------------------------------------------------------------------
263     if(mod(i,2).eq.1) then !odd strip ---> Y view
264     valuec= - (DBLE(adc(i,j,k))-cn(i,j)-pedestal(i,j,k)) !negative signal
265     cut=clcuty !sets Y cut to find cluster seeds
266     else !even strip ---> X view
267     valuec= DBLE(adc(i,j,k))-cn(i,j)-pedestal(i,j,k) !positive signal
268     cut=clcutx !sets X cut to find cluster seeds
269     endif
270    
271    
272     c------------------------------------------------------------------------
273     c
274     c seeks clusters
275     c
276     c------------------------------------------------------------------------
277     stripcut=cut*sigma(i,j,k) !cluster seed cut
278    
279     c if(ABS(valuec).gt.stripcut) then !checks if signal exceeds threshold!???
280     if(valuec.gt.stripcut) then !checks if signal exceeds threshold
281    
282     c$$$ print*,'cut',i,j,k,valuec,stripcut,adc(i,j,k),cn(i,j)
283     c$$$ $ ,pedestal(i,j,k) !???
284    
285     clstr(i,j,k)=0 !if so, marks this strip as part of a
286     ! cluster
287    
288     c------------------------------------------------------------------------
289     c after finding a cluster seed, checks also adiacent strips, and marks
290     c the ones exceeding cnincut
291     c------------------------------------------------------------------------
292     kr=k !initializes position indexes to be equal to
293     kl=k ! cluster seed position
294    
295     ir=0 !initialize flags used to exit from
296     il=0 ! inclusion loop
297    
298     do while (il.eq.0.or.ir.eq.0) !shifts left and right from
299     ! cluster seed till it finds a strip below
300     ! the threshold, or till it reaches first or
301     ! last VA1 strip
302     kr=kr+1 !position index for strips on right side of
303     ! cluster seed
304     kl=kl-1 !and for left side
305    
306     c------------------------------------------------------------------------
307     c checks for last or first strip
308     c------------------------------------------------------------------------
309     if(kr.gt.nstrips_va1.and.ir.eq.0) then !when index goes
310     ir=1 ! beyond last VA1 strip, change ir flag in
311     ! order to "help" exiting from loop
312     skip=nstrips_va1+1 !sets skip beyond last strip: all
313     ! strips on the right have been included in
314     ! the cluster, so skips all next strips
315     ! (goto 20 condition is now always true)
316     endif
317    
318     if(kl.lt.1.and.il.eq.0) then !idem when index goes beyond
319     il=1 ! first strip
320     endif
321    
322     c P.S.: the "....and.i#.eq.0" term in above conditions is needed. In
323     c fact, even if I reach a under-cut strip on the right (so I get ir=1),
324     c the "do while loop" continues till such strip will be found on the
325     c left too.
326     c Thus kl and kr (! too) keep increasing, and it can happen kr gets
327     c greater than nstrips_va1 before kl reaches a under-cut strip. In this
328     c case it would pass this "if condition", so setting skip=nstrips_va1+1
329     c and skipping right strips never checked, if the "....and.i#.eq.0" term
330     c weren't the: instead, including this part it won't pass it
331     c because when I found reach the last VA1 strip on the right I set ir=1.
332     c (AAAAAAHHHHHHHHH!!!!!!!!!!!)
333    
334     c------------------------------------------------------------------------
335     c marks strips exceeding inclusion cut
336     c------------------------------------------------------------------------
337     c for right strips (kr index)
338     if(ir.eq.0) then !if last strip or last over-cut strip has
339     ! not been reached
340    
341     if(mod(i,2).eq.1) then !Y view
342     valuer= - (DBLE(adc(i,j,kr))-cn(i,j) !puts in valuer
343     $ -pedestal(i,j,kr)) ! right strip value
344     else !X view
345     valuer=DBLE(adc(i,j,kr))-cn(i,j)-pedestal(i,j,kr)
346     endif
347    
348     stripcnincut=cnincut*sigma(i,j,kr) !defines include cut
349     c if(ABS(valuer).gt.stripcnincut) then !marks right strip if it !???
350     if(valuer.gt.stripcnincut) then !marks right strip if it
351     clstr(i,j,kr)=0 !exceedes include cut
352     c$$$ print*,'inclcut_r',i,j,kr,valuer,stripcnincut
353     c$$$ $ ,adc(i,j,kr),cn(i,j),pedestal(i,j,kr) !???
354     else
355     ir=1 !otherwise cluster ends and ir flag =1
356     ! signals it
357     skip=kr !putting skip=kr, next k to be checked is
358     ! k=kr
359     endif
360    
361     endif
362    
363     c for left strips (kl index)
364     if(il.eq.0) then !if first strip or last over-cut strip has
365     ! not been reached
366    
367     if (mod(i,2).eq.1) then !Y view
368     valuel= - (DBLE(adc(i,j,kl))-cn(i,j) !puts in valuel
369     $ -pedestal(i,j,kl)) ! left strip value
370     else !X view
371     valuel=DBLE(adc(i,j,kl))-cn(i,j)-pedestal(i,j,kl)
372     endif
373    
374     stripcnincut=cnincut*sigma(i,j,kl) !defines include cut
375     c if(ABS(valuel).gt.stripcnincut) then !marks left strip if it!???
376     if(valuel.gt.stripcnincut) then !marks left strip if it
377     clstr(i,j,kl)=0 !exceedes include cut
378     c$$$ print*,'inclcut_l',i,j,kl,valuel,stripcnincut
379     c$$$ $ ,adc(i,j,kl),cn(i,j),pedestal(i,j,kl) !???
380     else
381     il=1 !otherwise cluster ends and il flag =1
382     ! signals it
383     endif
384    
385     endif
386    
387     enddo !ends lateral strips loop
388    
389     endif !ends cluster seed condition
390    
391     20 continue !comes here if next strip on the right has
392     ! already been included in a cluster
393    
394     enddo !ends principal strip loop
395    
396     return
397     end

  ViewVC Help
Powered by ViewVC 1.1.23