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

Diff of /DarthVader/TrackerLevel2/src/F77/reductionflight.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1.17 by pam-fi, Thu Mar 15 12:17:10 2007 UTC revision 1.26 by pam-fi, Tue Nov 25 14:41:38 2008 UTC
# Line 27  c$$$      debug = .true. Line 27  c$$$      debug = .true.
27  c$$$      verbose = .true.  c$$$      verbose = .true.
28  c$$$      warning = .true.  c$$$      warning = .true.
29    
30    c$$$      print*,debug,verbose,warning
31    c$$$      debug=1
32    c$$$      verbose=1
33    c$$$      warning=1
34    
35    *     //////////////////////////
36    *     initialize some parameters
37    *     //////////////////////////
38    
39        call init_level1        call init_level1
40    
41        if(debug)print*,'-- check LEVEL0 status'  c      debug=.true.
42    
43          if(debug.eq.1)print*,'-- check LEVEL0 status'
44    
45          ievco=-1
46          mismatch=0
47  c      good1 = good0  c      good1 = good0
48  c--------------------------------------------------  c--------------------------------------------------
49  c     check the LEVEL0 event status for missing  c     check the LEVEL0 event status for missing
# Line 47  c           ------------------------ Line 60  c           ------------------------
60  c           CRC error  c           CRC error
61  c           ------------------------  c           ------------------------
62              if(crc(iv).eq.1) then              if(crc(iv).eq.1) then
63                 GOOD1(DSPnumber(iv)) = 2  c               GOOD1(DSPnumber(iv)) = 2
64                 goto 18 !next view  c               GOOD1(DSPnumber(iv)) = GOOD1(DSPnumber(iv)) + 2**1
65                   GOOD1(DSPnumber(iv)) = ior(GOOD1(DSPnumber(iv)),2**1)
66     102           format(' * WARNING * Event ',i7,' view',i3
67         $          ,' CRC error')
68                   if(debug.eq.1)write(*,102)eventn(1),DSPnumber(iv)
69    c               goto 18 !next view
70              endif              endif
71  c           ------------------------  c           ------------------------
72  c           online-software alarm  c           online-software alarm
# Line 63  c           ------------------------ Line 81  c           ------------------------
81       $           fc(iv).ne.0.or.       $           fc(iv).ne.0.or.
82       $           DATAlength(iv).eq.0.or.       $           DATAlength(iv).eq.0.or.
83       $           .false.)then       $           .false.)then
84                 GOOD1(DSPnumber(iv))=3  c               GOOD1(DSPnumber(iv))=3
85                 goto 18  c               GOOD1(DSPnumber(iv)) = GOOD1(DSPnumber(iv)) + 2**2
86                   GOOD1(DSPnumber(iv)) = ior(GOOD1(DSPnumber(iv)),2**2)
87     103           format(' * WARNING * Event ',i7,' view',i3
88         $          ,' software alarm')
89                   if(debug.eq.1)write(*,103)eventn(1),DSPnumber(iv)
90    c               goto 18
91              endif              endif
92  c           ------------------------  c           ------------------------
93  c           DSP-counter jump  c           DSP-counter jump
94  c           ------------------------  c           ------------------------
95              if(  c     commentato perche` non e` un controllo significativo nel caso in cui
96       $           eventn_old(iv).ne.0.and. !first event in this file  c     la subroutine venga chiamata per riprocessare l'evento
97       $           eventn(iv).ne.1.and.     !first event in run  c     sostituito con un check dei contatori dei vari dsp
98       $           good_old(DSPnumber(iv)).ne.0.and. !previous event corrupted  c$$$            if(
99       $           .true.)then  c$$$     $           eventn_old(iv).ne.0.and. !first event in this file
100    c$$$     $           eventn(iv).ne.1.and.     !first event in run
101                 if(eventn(iv).ne.(eventn_old(iv)+1))then  c$$$     $           good_old(DSPnumber(iv)).ne.0.and. !previous event corrupted
102                    GOOD1(DSPnumber(iv))=4  c$$$     $           .true.)then
103                    goto 18  c$$$
104    c$$$               if(eventn(iv).ne.(eventn_old(iv)+1))then
105    c$$$c                  GOOD1(DSPnumber(iv))=4
106    c$$$c                  GOOD1(DSPnumber(iv)) = GOOD1(DSPnumber(iv)) + 2**3
107    c$$$                  GOOD1(DSPnumber(iv)) = ior(GOOD1(DSPnumber(iv)),2**3)
108    c$$$ 104              format(' * WARNING * Event ',i7,' view',i3
109    c$$$     $          ,' counter jump ',i10,i10)
110    c$$$                  if(debug.eq.1)write(*,104)eventn(1),DSPnumber(iv)
111    c$$$     $                 ,eventn_old(iv),eventn(iv))
112    c$$$                  goto 18
113    c$$$               endif
114    c$$$
115    c$$$            endif
116    c           ------------------------
117    c 18         continue
118    c           ------------------------
119    c           DSP-counter
120    c           ------------------------
121                if( DSPnumber(iv).ne.0.and.GOOD1(DSPnumber(iv)).ne.1)then
122                   if(iv.ne.1.and.ievco.ne.-1)then
123                      if( eventn(iv).ne.ievco )then
124                         mismatch=1
125                      endif
126                 endif                 endif
127                   ievco = eventn(iv)
128              endif              endif
 c           ------------------------  
  18         continue  
129           endif           endif
130        enddo        enddo
131    
132    c      print*,'*** ',(eventn(iv),iv=1,12)
133          
134          if(mismatch.eq.1.and.debug.eq.1)
135         $     print*,' * WARNING * DSP counter mismatch: '
136         $     ,(eventn(iv),iv=1,12)
137    
138        ngood = 0        ngood = 0
139        do iv = 1,nviews        do iv = 1,nviews
140            
141             if(mismatch.eq.1.and.GOOD1(iv).ne.1)
142         $        GOOD1(iv)=ior(GOOD1(iv),2**3)
143    
144           eventn_old(iv) = eventn(iv)           eventn_old(iv) = eventn(iv)
145           good_old(iv)   = good1(iv)           good_old(iv)   = good1(iv)
146           ngood = ngood + good1(iv)           ngood = ngood + good1(iv)
147    
148        enddo        enddo
149        if(debug.and.ngood.ne.0)print*,'* WARNING * LEVEL0 event status: '  c$$$      if(verbose.and.ngood.ne.0)print*,'* WARNING * Event ',eventn(1)
150       $     ,(good1(i),i=1,nviews)  c$$$     $     ,':LEVEL0 event status: '
151    c$$$     $     ,(good1(i),i=1,nviews)
152  c--------------------------------------------------  c--------------------------------------------------
153  c     read the variable DATATRACKER from LEVEL0  c     read the variable DATATRACKER from LEVEL0
154  c     and fill the variable ADC (invertin view 11)  c     and fill the variable ADC (invertin view 11)
155  c--------------------------------------------------  c--------------------------------------------------
156                
157        if(debug)print*,'-- fill ADC vectors'        if(debug.eq.1)print*,'-- fill ADC vectors'
158    
159        call filladc(iflag)        call filladc(iflag)
160        if(iflag.ne.0)then        if(iflag.ne.0)then
# Line 111  c     computes common noise for each VA1 Line 166  c     computes common noise for each VA1
166  c     (excluding strips with signal,  c     (excluding strips with signal,
167  c     tagged with the flag CLSTR)  c     tagged with the flag CLSTR)
168  c--------------------------------------------------  c--------------------------------------------------
169        if(debug)print*,'-- compute CN'        if(debug.eq.1)print*,'-- compute CN'
170    
171        do iv=1,nviews        do iv=1,nviews
172           ima=0  
173           do ik=1,nva1_view           call evaluatecn(iv)
174              cn(iv,ik)  = 0  c$$$         ima=0
175              cnrms(iv,ik)  = 0  c$$$         do ik=1,nva1_view
176              cnn(iv,ik) = -1  c$$$            cn(iv,ik)    = 0
177              iflag=0  c$$$            cnrms(iv,ik) = 0
178              mask_vk_ev(iv,ik)=1  c$$$            cnn(iv,ik)   = -1
179              call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks  c$$$            iflag = 0
180  c     NBNBNBNBNB mask per la striscia 1 !!!!!!!!  c$$$            mask_vk_ev(iv,ik) = 1
181              if(mask(iv,ik,1).eq.1)call cncomp(iv,ik,iflag)  c$$$            call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks
182              if(iflag.ne.0)then  c$$$*           --------------------------------------
183                 ima=ima+1  c$$$*           if chip is not masked ---> evaluate CN
184                 mask_vk_ev(iv,ik)=0  c$$$*           --------------------------------------
185                 ierror = 220  c$$$            if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!
186              endif  c$$$               call cncomp(iv,ik,iflag)
187              call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks  c$$$               if(iflag.ne.0)then
188                c$$$                  ima=ima+1
189           enddo  c$$$                  mask_vk_ev(iv,ik)=0
190   100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)  c$$$                  ierror = 220
191           if(ima.ne.0.and.debug)write(*,100)eventn(1),iv  c$$$               endif
192       $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)  c$$$               call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks
193    c$$$            endif
194    c$$$         enddo
195    c$$$ 100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
196    c$$$         if(ima.ne.0.and.verbose.eq.1)write(*,100)eventn(1),iv
197    c$$$     $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
198    
199        enddo        enddo
200    
201  cc      call stripmask !compute mask(i,j,k), combining mask_vk_ev and mask_vk  cc      call stripmask !compute mask(i,j,k), combining mask_vk_ev and mask_vk
# Line 147  c     sigma informations from histograms Line 208  c     sigma informations from histograms
208  c---------------------------------------------  c---------------------------------------------
209        ind=1                     !clsignal array index        ind=1                     !clsignal array index
210    
211        if(debug)print*,'-- search clusters'        if(debug.eq.1)print*,'-- search clusters'
212        do iv=1,nviews            !loop on views        do iv=1,nviews            !loop on views
213          do is=1,nstrips_view    !loop on strips (1)  c$$$        do is=1,nstrips_view    !loop on strips (1)
214            if(mod(iv,2).eq.1) then  c$$$          if(mod(iv,2).eq.1) then
215  C===  > Y view  c$$$C===  > Y view
216              value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))  c$$$c             print*,iv,nvk(is),nst(is),adc(iv,nvk(is),nst(is))
217       $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))  c$$$c     $            ,cn(iv,nvk(is))
218       $           *mask(iv,nvk(is),nst(is))  c$$$c     $            ,pedestal(iv,nvk(is),nst(is))
219              clseedcut(is)=clcuty*sigma(iv,nvk(is),nst(is))  c$$$            value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))
220       $           *mask(iv,nvk(is),nst(is))  c$$$     $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
221              clinclcut(is)=incuty*sigma(iv,nvk(is),nst(is))  c$$$     $           *mask(iv,nvk(is),nst(is))
222       $           *mask(iv,nvk(is),nst(is))  c$$$            clseedcut(is)=clcuty*sigma(iv,nvk(is),nst(is))
223              sat(is)=0  c$$$     $           *mask(iv,nvk(is),nst(is))
224              if( adc(iv,nvk(is),nst(is)).lt.adc_saty )sat(is)=1  c$$$            clinclcut(is)=incuty*sigma(iv,nvk(is),nst(is))
225            else              c$$$     $           *mask(iv,nvk(is),nst(is))
226  C===  > X view  c$$$            sat(is)=0
227              value(is)= (DBLE(adc(iv,nvk(is),nst(is)))  c$$$            if( adc(iv,nvk(is),nst(is)).lt.adc_saty )sat(is)=1
228       $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))  c$$$          else            
229       $           *mask(iv,nvk(is),nst(is))  c$$$C===  > X view
230              clseedcut(is)=clcutx*sigma(iv,nvk(is),nst(is))  c$$$            value(is)= (DBLE(adc(iv,nvk(is),nst(is)))
231       $           *mask(iv,nvk(is),nst(is))  c$$$     $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
232              clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))  c$$$     $           *mask(iv,nvk(is),nst(is))
233       $           *mask(iv,nvk(is),nst(is))  c$$$            clseedcut(is)=clcutx*sigma(iv,nvk(is),nst(is))
234              sat(is)=0  c$$$     $           *mask(iv,nvk(is),nst(is))
235              if( adc(iv,nvk(is),nst(is)).gt.adc_satx )sat(is)=1  c$$$            clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))
236            endif  c$$$     $           *mask(iv,nvk(is),nst(is))
237          enddo                   !end loop on strips (1)  c$$$            sat(is)=0
238          call search_cluster(iv)  c$$$            if( adc(iv,nvk(is),nst(is)).gt.adc_satx )sat(is)=1
239    c$$$          endif
240          if(.not.flag_shower)then  c$$$        enddo                   !end loop on strips (1)
241             call save_cluster(iv)           call subtractped(iv)
242             if(debug)print*,'view ',iv,' #clusters ', nclstr_view           call searchcluster(iv)
243          else  
244             fshower(iv) = 1           if(.not.flag_shower)then
245  c           GOOD1(DSPnumber(iv)) = 11 !AHAHAHAHA ORRORE!!              call savecluster(iv)
246             GOOD1(iv) = 11  c$$$            if(debug.eq.1)print*,' view ',iv,' #clusters ', nclstr_view
247   101       format(' * WARNING * Event ',i7,' view',i3           else
248       $          ,' #clusters > ',i5,' --> MASKED')              fshower(iv) = 1
249             if(debug)write(*,101)eventn(1),iv,nclstrmax_view  c     GOOD1(DSPnumber(iv)) = 11 !AHAHAHAHA ORRORE!!
250          endif  c     GOOD1(iv) = 11
251    c     GOOD1(iv) = GOOD1(iv) + 2**5
252                GOOD1(iv) = ior(GOOD1(iv),2**5)
253     101        format(' * WARNING * Event ',i7,' view',i3
254         $           ,' #clusters > ',i5,' --> MASKED')
255                if(verbose.eq.1)write(*,101)eventn(1),iv,nclstrmax_view
256             endif
257        enddo                     ! end loop on views        enddo                     ! end loop on views
258        do iv=1,nviews        do iv=1,nviews
259          do ik=1,nva1_view           do ik=1,nva1_view
260            cnev(iv,ik)    = cn(iv,ik) !assigns computed CN to ntuple variables              cnev(iv,ik)    = cn(iv,ik) !assigns computed CN to ntuple variables
261            cnrmsev(iv,ik) = cnrms(iv,ik) !assigns computed CN to ntuple variables              cnrmsev(iv,ik) = cnrms(iv,ik) !assigns computed CN to ntuple variables
262            cnnev(iv,ik)   = cnn(iv,ik) !assigns computed CN to ntuple variables              cnnev(iv,ik)   = cnn(iv,ik) !assigns computed CN to ntuple variables
263          enddo           enddo
264        enddo        enddo
265  C---------------------------------------------  C---------------------------------------------
266  C     come here if GOOD1=0  C     come here if GOOD1=0
# Line 205  C--------------------------------------- Line 272  C---------------------------------------
272        do iv = 1,nviews        do iv = 1,nviews
273           ngood = ngood + good1(iv)           ngood = ngood + good1(iv)
274        enddo        enddo
275        if(debug.and.ngood.ne.0)print*,'* WARNING * Event ',eventn(1)        if(verbose.eq.1.and.ngood.ne.0)
276         $     print*,'* WARNING * Event ',eventn(1)
277       $     ,':LEVEL1 event status: '       $     ,':LEVEL1 event status: '
278       $     ,(good1(i),i=1,nviews)       $     ,(good1(i),i=1,nviews)
279  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 278  c        crc1(iv)=0 Line 346  c        crc1(iv)=0
346  *  *
347  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
348    
349        subroutine search_cluster(iv)        subroutine searchcluster(iv)
350    
351        include 'commontracker.f'        include 'commontracker.f'
352        include 'level0.f'        include 'level0.f'
# Line 325  c--------------------------------------- Line 393  c---------------------------------------
393  c-----------------------------------------  c-----------------------------------------
394  c     possible SEED...  c     possible SEED...
395  c-----------------------------------------  c-----------------------------------------
396    c$$$               if(debug.eq.1)print*,'|||| ',value(is),' @',is
397    c$$$     $              ,' cut ',clseedcut(is)
398    
399                 itemp = is                 itemp = is
400                 fsat = 0         ! first saturated strip                 fsat = 0         ! first saturated strip
401                 lsat = 0         ! last saturated strip                 lsat = 0         ! last saturated strip
# Line 336  c              ------------------------ Line 407  c              ------------------------
407       $                   value(itemp).le.value(itemp+1)       $                   value(itemp).le.value(itemp+1)
408       $              .and.value(itemp+1).gt.clseedcut(itemp+1))       $              .and.value(itemp+1).gt.clseedcut(itemp+1))
409                    itemp = itemp+1                    itemp = itemp+1
410    c$$$                  if(debug.eq.1)print*,'|||| ',value(itemp),' @',is
411    c$$$     $                 ,' cut ',clseedcut(itemp)
412                    if(itemp.eq.last)   goto 230 !stops if reaches last strip                    if(itemp.eq.last)   goto 230 !stops if reaches last strip
413                    if(sat(itemp).eq.1) goto 230 !stop if reaches a saturated strip                    if(sat(itemp).eq.1) goto 230 !stop if reaches a saturated strip
414                 enddo            ! of the ladder                 enddo            ! of the ladder
# Line 347  c              ------------------------- Line 420  c              -------------------------
420                    fsat = itemp                    fsat = itemp
421                    lsat = itemp                    lsat = itemp
422                    if(itemp.eq.last) goto 231 !estremo...                    if(itemp.eq.last) goto 231 !estremo...
423                    do while( sat(itemp+1).eq.1 )                    do while(
424         $                 sat(itemp+1).eq.1 .and.
425         $                 value(itemp+1).gt.clseedcut(itemp+1) .and.
426         $                 .true.)
427                       itemp = itemp+1                       itemp = itemp+1
428                       lsat = itemp                       lsat = itemp
429                       if(itemp.eq.last)   goto 231 !stops if reaches last strip                       if(itemp.eq.last)   goto 231 !stops if reaches last strip
# Line 362  c--------------------------------------- Line 438  c---------------------------------------
438                    iseed = itemp ! <<< SEED                    iseed = itemp ! <<< SEED
439                 else                 else
440                    iseed = int((lsat+fsat)/2) ! <<< SEED                    iseed = int((lsat+fsat)/2) ! <<< SEED
441  c$$$                  print*,'saturated strips ',fsat,lsat,iseed                    if(debug.eq.1)
442         $                 print*,'saturated strips (first,last) ',fsat,lsat
443  c$$$                  print*,'--> ',(value(ii),ii=fsat,lsat)  c$$$                  print*,'--> ',(value(ii),ii=fsat,lsat)
444                 endif                     endif    
445  c---------------------------------------------------------------  c---------------------------------------------------------------
446  c     after finding a cluster seed, checks also adjacent strips,  c     after finding a cluster seed, checks also adjacent strips,
447  C     and tags the ones exceeding clinclcut  C     and tags the ones exceeding clinclcut
448  c---------------------------------------------------------------  c---------------------------------------------------------------
449                  
450                   if(debug.eq.1)print*,'SEED ',value(iseed),' @',iseed
451         $              ,' cut ',clseedcut(iseed)
452    
453                 ir=iseed         !indici destro                 ir=iseed         !indici destro
454                 il=iseed         ! e sinistro                 il=iseed         ! e sinistro
455                                
# Line 394  c     add strips exceeding inclusion cut Line 475  c     add strips exceeding inclusion cut
475  c------------------------------------------------------------------------  c------------------------------------------------------------------------
476                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
477    
478                    if(rstop.eq.0) then !if right cluster morder has not been reached                    if(rstop.eq.0) then !if right cluster border has not been reached
479                       if(value(ir).gt.clinclcut(ir)) then                       if(value(ir).gt.clinclcut(ir)) then
480                          rmax=ir !include a strip on the right                          rmax=ir !include a strip on the right
481                       else                       else
# Line 404  c--------------------------------------- Line 485  c---------------------------------------
485    
486                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
487    
488                    if(lstop.eq.0) then !if left cluster morder has not been reached                    if(lstop.eq.0) then !if left cluster border has not been reached
489                       if(value(il).gt.clinclcut(il)) then                       if(value(il).gt.clinclcut(il)) then
490                          lmax=il !include a strip on the left                          lmax=il !include a strip on the left
491                       else                       else
# Line 412  c--------------------------------------- Line 493  c---------------------------------------
493                       endif                       endif
494                    endif                    endif
495    
496    c                  if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
497    
498                 enddo            !ends strip inclusion loop                 enddo            !ends strip inclusion loop
499                 goto 211                 goto 211
500   210           continue         !jumps here if more than nclstrp have been included   210           continue         !jumps here if more than nclstrp have been included
# Line 432  c--------------------------------------- Line 515  c---------------------------------------
515                    rmax = rmax+1                    rmax = rmax+1
516                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
517                 endif                 endif
518    c-------------------------------------------------------------------------------
519    c     adjust the cluster in order to have at least ANOTHER strip around the seed
520    c-------------------------------------------------------------------------------
521                   if(iseed-1.eq.lmax.and.lmax.ne.first)then
522                      lmax = lmax-1
523                      if( (rmax-lmax+1).gt.nclstrp )rmax=rmax-1
524                   endif
525                   if(iseed+1.eq.rmax.and.rmax.ne.last )then
526                      rmax = rmax+1
527                      if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
528                   endif
529    c---------------------------------------------------
530    c     now we have 5 stored-strips around the maximum
531    c---------------------------------------------------
532    
533  c------------------------------------------------------------------------  c------------------------------------------------------------------------
534  c     adjust the cluster in order to store a minimum number of strips  c     adjust the cluster in order to store a minimum number of strips
# Line 465  c$$$     $                 ,' clusters o Line 562  c$$$     $                 ,' clusters o
562    
563                 ladder_view(nclstr_view) = nld(iseed,iv)                 ladder_view(nclstr_view) = nld(iseed,iv)
564                 maxs_view(nclstr_view)   = iseed                 maxs_view(nclstr_view)   = iseed
                mult_view(nclstr_view)   = rmax-lmax+1  
565                 rmax_view(nclstr_view)   = rmax                 rmax_view(nclstr_view)   = rmax
566                 lmax_view(nclstr_view)   = lmax                 lmax_view(nclstr_view)   = lmax
567    c               mult_view(nclstr_view)   = rmax-lmax+1
568                   mult_view(nclstr_view)   = 0
569                   do ii=lmax,rmax
570                      if(value(ii).gt.clinclcut(ii))  
571         $                 mult_view(nclstr_view) = mult_view(nclstr_view)+1
572                   enddo
573    
574    c$$$               print*,(value(ii),ii=lmax,rmax)
575    c$$$               print*,(clinclcut(ii),ii=lmax,rmax)
576    c$$$               print*,(clseedcut(ii),ii=lmax,rmax)
577    
578  c$$$               if(rmax-lmax+1.gt.25)  c$$$               if(rmax-lmax+1.gt.25)
579  c$$$     $              print*,'view ',iv  c$$$     $              print*,'view ',iv
# Line 531  c--------------------------------------- Line 637  c---------------------------------------
637  *  *
638  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
639    
640        subroutine save_cluster(iv)        subroutine savecluster(iv)
641  *  *
642  *     (080/2006 Elena Vannuccini)  *     (080/2006 Elena Vannuccini)
643  *     Save the clusters view by view  *     Save the clusters view by view
# Line 563  c        posizione del cluster seed nell Line 669  c        posizione del cluster seed nell
669           do j=lmax_view(ic),rmax_view(ic)         !stores sequentially cluter strip values in           do j=lmax_view(ic),rmax_view(ic)         !stores sequentially cluter strip values in
670    
671              clsignal(ind) = value(j) ! clsignal array              clsignal(ind) = value(j) ! clsignal array
672    c$$$            print*,ind,clsignal(ind)
673              ivk=nvk(j)              ivk=nvk(j)
674              ist=nst(j)              ist=nst(j)
675    
# Line 578  c     if(value(j).gt.0) Line 684  c     if(value(j).gt.0)
684       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge
685           enddo           enddo
686    
687  c         print*,'view ',iv,' -- save_cluster -- nclstr1: '           if(debug.eq.1)then
688  c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),sgnl(nclstr1)              print*,'view ',iv,' -- '
689                 $           ,' n.cl: ',nclstr1
690         $           ,' maxs: ',maxs(nclstr1)
691         $           ,' mult: ',mult(nclstr1)
692         $           ,' sign: ',sgnl(nclstr1)
693                print*,'----------------------'
694             endif
695        enddo        enddo
696                
697        return        return
# Line 593  c     $        ,nclstr1,maxs(nclstr1),mu Line 704  c     $        ,nclstr1,maxs(nclstr1),mu
704  *  *
705  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
706    
707          subroutine evaluatecn(iv)
708          
709          include 'commontracker.f'
710          include 'level0.f'
711          include 'level1.f'
712          include 'common_reduction.f'
713          include 'calib.f'
714          
715          ima=0
716          do ik=1,nva1_view
717             cn(iv,ik)    = 0
718             cnrms(iv,ik) = 0
719             cnn(iv,ik)   = -1
720             iflag = 0
721             mask_vk_ev(iv,ik) = 1
722             call stripmask(iv,ik)  !compute mask(i,j,k), combining VA1-masks
723    *     --------------------------------------
724    *     if chip is not masked ---> evaluate CN
725    *     --------------------------------------
726             if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!
727                call cncomp(iv,ik,iflag)
728                if(iflag.ne.0)then
729                   ima=ima+1
730                   mask_vk_ev(iv,ik)=0
731                   ierror = 220
732                endif
733                call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks
734             endif
735          enddo
736     100  format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
737          if(ima.ne.0.and.verbose.eq.1)write(*,100)eventn(1),iv
738         $     ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
739          
740          return
741          end
742    
743    *---***---***---***---***---***---***---***---***
744    *
745    *
746    *
747    *
748    *
749    *---***---***---***---***---***---***---***---***
750          subroutine subtractped(iv)
751          
752          include 'commontracker.f'
753          include 'level1.f'
754          include 'calib.f'
755          include 'common_reduction.f'
756    
757          do is=1,nstrips_view      !loop on strips (1)
758             if(mod(iv,2).eq.1) then
759    C===  > Y view
760    c     print*,iv,nvk(is),nst(is),adc(iv,nvk(is),nst(is))
761    c     $            ,cn(iv,nvk(is))
762    c     $            ,pedestal(iv,nvk(is),nst(is))
763                value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))
764         $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
765         $           *mask(iv,nvk(is),nst(is))
766                clseedcut(is)=clcuty*sigma(iv,nvk(is),nst(is))
767         $           *mask(iv,nvk(is),nst(is))
768                clinclcut(is)=incuty*sigma(iv,nvk(is),nst(is))
769         $           *mask(iv,nvk(is),nst(is))
770                sat(is)=0
771                if( adc(iv,nvk(is),nst(is)).lt.adc_saty )
772         $           sat(is)=mask(iv,nvk(is),nst(is))
773             else            
774    C===  > X view
775                value(is)= (DBLE(adc(iv,nvk(is),nst(is)))
776         $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
777         $           *mask(iv,nvk(is),nst(is))
778                clseedcut(is)=clcutx*sigma(iv,nvk(is),nst(is))
779         $           *mask(iv,nvk(is),nst(is))
780                clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))
781         $           *mask(iv,nvk(is),nst(is))
782                sat(is)=0
783                if( adc(iv,nvk(is),nst(is)).gt.adc_satx )
784         $           sat(is)=mask(iv,nvk(is),nst(is))
785             endif
786          enddo                     !end loop on strips (1)
787          
788          
789          return
790          end
791    *---***---***---***---***---***---***---***---***
792    *
793    *
794    *
795    *
796    *
797    *---***---***---***---***---***---***---***---***
798  c$$$      subroutine stripmask  c$$$      subroutine stripmask
799  c$$$  c$$$
800  c$$$*     this routine set va1 and single-strip masks,  c$$$*     this routine set va1 and single-strip masks,
# Line 632  c$$$      end Line 833  c$$$      end
833    
834        subroutine stripmask(iv,ivk)        subroutine stripmask(iv,ivk)
835    
836    *     -----------------------------------------------
837  *     this routine set va1 and single-strip masks,  *     this routine set va1 and single-strip masks,
838  *     on the basis of the VA1 mask saved in the DB  *     on the basis of the VA1 mask saved in the DB
839  *  *
840  *     mask(nviews,nva1_view,nstrips_va1) !strip mask  *     mask(nviews,nva1_view,nstrips_va1) !strip mask
841  *     mask_vk(nviews,nva1_view)          !VA1 mask  *     mask_vk(nviews,nva1_view)          !VA1 mask
842  *  *     -----------------------------------------------
843        include 'commontracker.f'        include 'commontracker.f'
844        include 'level1.f'        include 'level1.f'
845        include 'common_reduction.f'        include 'common_reduction.f'
# Line 645  c$$$      end Line 847  c$$$      end
847    
848  *     init mask  *     init mask
849        do is=1,nstrips_va1        do is=1,nstrips_va1
850    *        --------------------------------------------------------
851    *        if VA1-mask from DB is 0 or 1, three masks are combined:
852    *        - from DB (a-priori mask)
853    *        - run-based (chip declared bad on the basis of <SIG>)
854    *        - event-based (failure in CN computation)
855    *        --------------------------------------------------------
856    c         print*,iv,ivk
857    c     $        ,mask_vk(iv,ivk),mask_vk_ev(iv,ivk),mask_vk_run(iv,ivk)
858           if( mask_vk(iv,ivk) .ne. -1)then                       if( mask_vk(iv,ivk) .ne. -1)then            
859              mask(iv,ivk,is) = 1              mask(iv,ivk,is) = 1
860       $           * mask_vk(iv,ivk) !from DB       $           * mask_vk(iv,ivk)     !from DB
861       $           * mask_vk_ev(iv,ivk) !from <SIG>       $           * mask_vk_ev(iv,ivk)  !from <SIG>
862       $           * mask_vk_run(iv,ivk) !from CN       $           * mask_vk_run(iv,ivk) !from CN
863    *        -----------------------------------------------------------
864    *        if VA1-mask from DB is -1 only event-based mask is applied
865    *        -----------------------------------------------------------
866           else           else
867              mask(iv,ivk,is) = -1              mask(iv,ivk,is) = -1
868       $           * mask_vk(iv,ivk) !from DB       $           * mask_vk(iv,ivk)     !from DB
869       $           * mask_vk_ev(iv,ivk) !from CN       $           * mask_vk_ev(iv,ivk)  !from CN
870           endif           endif
871        enddo        enddo
872                

Legend:
Removed from v.1.17  
changed lines
  Added in v.1.26

  ViewVC Help
Powered by ViewVC 1.1.23