/[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.18 by pam-fi, Fri Apr 27 10:39:58 2007 UTC revision 1.28 by mocchiut, Tue Aug 4 14:01:39 2009 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$$$            mask_vk_ev(iv,ik) = 1
181  *           if chip is not masked ---> evaluate CN  c$$$            call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks
182  *           --------------------------------------  c$$$*           --------------------------------------
183              if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!  c$$$*           if chip is not masked ---> evaluate CN
184                 call cncomp(iv,ik,iflag)  c$$$*           --------------------------------------
185                 if(iflag.ne.0)then  c$$$            if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!
186                    ima=ima+1  c$$$               call cncomp(iv,ik,iflag)
187                    mask_vk_ev(iv,ik)=0  c$$$               if(iflag.ne.0)then
188                    ierror = 220  c$$$                  ima=ima+1
189                 endif  c$$$                  mask_vk_ev(iv,ik)=0
190                 call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks  c$$$                  ierror = 220
191              endif  c$$$               endif
192           enddo  c$$$               call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks
193   100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)  c$$$            endif
194           if(ima.ne.0.and.debug)write(*,100)eventn(1),iv  c$$$         enddo
195       $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)  c$$$ 100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
196  c         if(ima.ne.0)write(*,100)eventn(1),iv  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)    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 152  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              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
267  C     or the event has too many clusters  C     or the event has too many clusters
268  C---------------------------------------------  C---------------------------------------------
269   200  continue  c 200  continue
270    
271        ngood = 0        ngood = 0
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 283  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 399  c     add strips exceeding inclusion cut Line 462  c     add strips exceeding inclusion cut
462  c------------------------------------------------------------------------  c------------------------------------------------------------------------
463                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
464    
465                    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
466                       if(value(ir).gt.clinclcut(ir)) then                       if(value(ir).gt.clinclcut(ir)) then
467                          rmax=ir !include a strip on the right                          rmax=ir !include a strip on the right
468                       else                       else
# Line 409  c--------------------------------------- Line 472  c---------------------------------------
472    
473                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
474    
475                    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
476                       if(value(il).gt.clinclcut(il)) then                       if(value(il).gt.clinclcut(il)) then
477                          lmax=il !include a strip on the left                          lmax=il !include a strip on the left
478                       else                       else
# Line 417  c--------------------------------------- Line 480  c---------------------------------------
480                       endif                       endif
481                    endif                    endif
482    
483    c                  if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
484    
485                 enddo            !ends strip inclusion loop                 enddo            !ends strip inclusion loop
486                 goto 211                 goto 211
487   210           continue         !jumps here if more than nclstrp have been included   210           continue         !jumps here if more than nclstrp have been included
# Line 437  c--------------------------------------- Line 502  c---------------------------------------
502                    rmax = rmax+1                    rmax = rmax+1
503                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
504                 endif                 endif
505    c-------------------------------------------------------------------------------
506    c     adjust the cluster in order to have at least ANOTHER strip around the seed
507    c-------------------------------------------------------------------------------
508                   if(iseed-1.eq.lmax.and.lmax.ne.first)then
509                      lmax = lmax-1
510                      if( (rmax-lmax+1).gt.nclstrp )rmax=rmax-1
511                   endif
512                   if(iseed+1.eq.rmax.and.rmax.ne.last )then
513                      rmax = rmax+1
514                      if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
515                   endif
516    c---------------------------------------------------
517    c     now we have 5 stored-strips around the maximum
518    c---------------------------------------------------
519    
520  c------------------------------------------------------------------------  c------------------------------------------------------------------------
521  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 470  c$$$     $                 ,' clusters o Line 549  c$$$     $                 ,' clusters o
549    
550                 ladder_view(nclstr_view) = nld(iseed,iv)                 ladder_view(nclstr_view) = nld(iseed,iv)
551                 maxs_view(nclstr_view)   = iseed                 maxs_view(nclstr_view)   = iseed
                mult_view(nclstr_view)   = rmax-lmax+1  
552                 rmax_view(nclstr_view)   = rmax                 rmax_view(nclstr_view)   = rmax
553                 lmax_view(nclstr_view)   = lmax                 lmax_view(nclstr_view)   = lmax
554    c               mult_view(nclstr_view)   = rmax-lmax+1
555                   mult_view(nclstr_view)   = 0
556                   do ii=lmax,rmax
557                      if(value(ii).gt.clinclcut(ii))  
558         $                 mult_view(nclstr_view) = mult_view(nclstr_view)+1
559                   enddo
560    
561    
562  c$$$               if(rmax-lmax+1.gt.25)  c$$$               if(rmax-lmax+1.gt.25)
563  c$$$     $              print*,'view ',iv  c$$$     $              print*,'view ',iv
# Line 498  c--------------------------------------- Line 583  c---------------------------------------
583       $                    delta.gt.cut .and.       $                    delta.gt.cut .and.
584       $                    value(iss).gt.clseedcut(iss).and.       $                    value(iss).gt.clseedcut(iss).and.
585       $                    .true.)then       $                    .true.)then
586                          if( value(iss).gt.vmax )then                                                  if( value(iss).gt.vmax )then
587                             imax = iss                             imax = iss
588                             vmax = value(iss)                             vmax = value(iss)
589                          else                          else
# Line 536  c--------------------------------------- Line 621  c---------------------------------------
621  *  *
622  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
623    
624        subroutine save_cluster(iv)        subroutine savecluster(iv)
625  *  *
626  *     (080/2006 Elena Vannuccini)  *     (080/2006 Elena Vannuccini)
627  *     Save the clusters view by view  *     Save the clusters view by view
# Line 568  c        posizione del cluster seed nell Line 653  c        posizione del cluster seed nell
653           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
654    
655              clsignal(ind) = value(j) ! clsignal array              clsignal(ind) = value(j) ! clsignal array
656    c$$$            print*,ind,clsignal(ind)
657              ivk=nvk(j)              ivk=nvk(j)
658              ist=nst(j)              ist=nst(j)
659    
# Line 583  c     if(value(j).gt.0) Line 668  c     if(value(j).gt.0)
668       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge
669           enddo           enddo
670    
671  c         print*,'view ',iv,' -- save_cluster -- nclstr1: '  c$$$         print*,'view ',iv,' -- savecluster -- nclstr1: '
672  c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),sgnl(nclstr1)  c$$$     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),sgnl(nclstr1)
673            c$$$         print*,'----------------------'
674    
675        enddo        enddo
676                
677        return        return
# Line 598  c     $        ,nclstr1,maxs(nclstr1),mu Line 684  c     $        ,nclstr1,maxs(nclstr1),mu
684  *  *
685  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
686    
687          subroutine evaluatecn(iv)
688          
689          include 'commontracker.f'
690          include 'level0.f'
691          include 'level1.f'
692          include 'common_reduction.f'
693          include 'calib.f'
694          
695          ima=0
696          do ik=1,nva1_view
697             cn(iv,ik)    = 0
698             cnrms(iv,ik) = 0
699             cnn(iv,ik)   = -1
700             iflag = 0
701             mask_vk_ev(iv,ik) = 1
702             call stripmask(iv,ik)  !compute mask(i,j,k), combining VA1-masks
703    *     --------------------------------------
704    *     if chip is not masked ---> evaluate CN
705    *     --------------------------------------
706             if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!
707                call cncomp(iv,ik,iflag)
708                if(iflag.ne.0)then
709                   ima=ima+1
710                   mask_vk_ev(iv,ik)=0
711                   ierror = 220
712                endif
713                call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks
714             endif
715          enddo
716     100  format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
717          if(ima.ne.0.and.verbose.eq.1)write(*,100)eventn(1),iv
718         $     ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
719          
720          return
721          end
722    
723    *---***---***---***---***---***---***---***---***
724    *
725    *
726    *
727    *
728    *
729    *---***---***---***---***---***---***---***---***
730          subroutine subtractped(iv)
731          
732          include 'commontracker.f'
733          include 'level1.f'
734          include 'calib.f'
735          include 'common_reduction.f'
736    
737          do is=1,nstrips_view      !loop on strips (1)
738             if(mod(iv,2).eq.1) then
739    C===  > Y view
740    c     print*,iv,nvk(is),nst(is),adc(iv,nvk(is),nst(is))
741    c     $            ,cn(iv,nvk(is))
742    c     $            ,pedestal(iv,nvk(is),nst(is))
743                value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))
744         $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
745         $           *mask(iv,nvk(is),nst(is))
746                clseedcut(is)=clcuty*sigma(iv,nvk(is),nst(is))
747         $           *mask(iv,nvk(is),nst(is))
748                clinclcut(is)=incuty*sigma(iv,nvk(is),nst(is))
749         $           *mask(iv,nvk(is),nst(is))
750                sat(is)=0
751                if( adc(iv,nvk(is),nst(is)).lt.adc_saty )sat(is)=1
752             else            
753    C===  > X view
754                value(is)= (DBLE(adc(iv,nvk(is),nst(is)))
755         $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
756         $           *mask(iv,nvk(is),nst(is))
757                clseedcut(is)=clcutx*sigma(iv,nvk(is),nst(is))
758         $           *mask(iv,nvk(is),nst(is))
759                clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))
760         $           *mask(iv,nvk(is),nst(is))
761                sat(is)=0
762                if( adc(iv,nvk(is),nst(is)).gt.adc_satx )sat(is)=1
763             endif
764          enddo                     !end loop on strips (1)
765          
766          
767          return
768          end
769    *---***---***---***---***---***---***---***---***
770    *
771    *
772    *
773    *
774    *
775    *---***---***---***---***---***---***---***---***
776  c$$$      subroutine stripmask  c$$$      subroutine stripmask
777  c$$$  c$$$
778  c$$$*     this routine set va1 and single-strip masks,  c$$$*     this routine set va1 and single-strip masks,
# Line 657  c$$$      end Line 831  c$$$      end
831  *        - run-based (chip declared bad on the basis of <SIG>)  *        - run-based (chip declared bad on the basis of <SIG>)
832  *        - event-based (failure in CN computation)  *        - event-based (failure in CN computation)
833  *        --------------------------------------------------------  *        --------------------------------------------------------
834    c         print*,iv,ivk
835    c     $        ,mask_vk(iv,ivk),mask_vk_ev(iv,ivk),mask_vk_run(iv,ivk)
836           if( mask_vk(iv,ivk) .ne. -1)then                       if( mask_vk(iv,ivk) .ne. -1)then            
837              mask(iv,ivk,is) = 1              mask(iv,ivk,is) = 1
838       $           * mask_vk(iv,ivk)     !from DB       $           * mask_vk(iv,ivk)     !from DB

Legend:
Removed from v.1.18  
changed lines
  Added in v.1.28

  ViewVC Help
Powered by ViewVC 1.1.23