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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.4 - (show annotations) (download)
Tue Sep 5 12:52:20 2006 UTC (18 years, 3 months ago) by pam-fi
Branch: MAIN
CVS Tags: v2r00BETA
Changes since 1.3: +10 -9 lines
implemented class TrkLevel1

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

  ViewVC Help
Powered by ViewVC 1.1.23