/[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.23 by pam-fi, Fri Aug 31 14:56:52 2007 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           ima=0
173           do ik=1,nva1_view           do ik=1,nva1_view
174              cn(iv,ik)  = 0              cn(iv,ik)    = 0
175              cnrms(iv,ik)  = 0              cnrms(iv,ik) = 0
176              cnn(iv,ik) = -1              cnn(iv,ik)   = -1
177              iflag=0              iflag = 0
178              mask_vk_ev(iv,ik)=1              mask_vk_ev(iv,ik) = 1
179              call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks              call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks
180  c     NBNBNBNBNB mask per la striscia 1 !!!!!!!!  *           --------------------------------------
181              if(mask(iv,ik,1).eq.1)call cncomp(iv,ik,iflag)  *           if chip is not masked ---> evaluate CN
182              if(iflag.ne.0)then  *           --------------------------------------
183                 ima=ima+1              if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!
184                 mask_vk_ev(iv,ik)=0                 call cncomp(iv,ik,iflag)
185                 ierror = 220                 if(iflag.ne.0)then
186                      ima=ima+1
187                      mask_vk_ev(iv,ik)=0
188                      ierror = 220
189                   endif
190                   call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks
191              endif              endif
             call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks  
               
192           enddo           enddo
193   100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)   100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
194           if(ima.ne.0.and.debug)write(*,100)eventn(1),iv           if(ima.ne.0.and.verbose.eq.1)write(*,100)eventn(1),iv
195       $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)       $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
196    c         if(ima.ne.0)write(*,100)eventn(1),iv
197    c     $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)  
198        enddo        enddo
199    
200  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 207  c     sigma informations from histograms
207  c---------------------------------------------  c---------------------------------------------
208        ind=1                     !clsignal array index        ind=1                     !clsignal array index
209    
210        if(debug)print*,'-- search clusters'        if(debug.eq.1)print*,'-- search clusters'
211        do iv=1,nviews            !loop on views        do iv=1,nviews            !loop on views
212          do is=1,nstrips_view    !loop on strips (1)          do is=1,nstrips_view    !loop on strips (1)
213            if(mod(iv,2).eq.1) then            if(mod(iv,2).eq.1) then
214  C===  > Y view  C===  > Y view
215    c             print*,iv,nvk(is),nst(is),adc(iv,nvk(is),nst(is))
216    c     $            ,cn(iv,nvk(is))
217    c     $            ,pedestal(iv,nvk(is),nst(is))
218              value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))              value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))
219       $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))       $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
220       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
# Line 178  C===  > X view Line 241  C===  > X view
241    
242          if(.not.flag_shower)then          if(.not.flag_shower)then
243             call save_cluster(iv)             call save_cluster(iv)
244             if(debug)print*,'view ',iv,' #clusters ', nclstr_view             if(debug.eq.1)print*,'view ',iv,' #clusters ', nclstr_view
245          else          else
246             fshower(iv) = 1             fshower(iv) = 1
247  c           GOOD1(DSPnumber(iv)) = 11 !AHAHAHAHA ORRORE!!  c           GOOD1(DSPnumber(iv)) = 11 !AHAHAHAHA ORRORE!!
248             GOOD1(iv) = 11  c           GOOD1(iv) = 11
249    c           GOOD1(iv) = GOOD1(iv) + 2**5
250               GOOD1(iv) = ior(GOOD1(iv),2**5)
251   101       format(' * WARNING * Event ',i7,' view',i3   101       format(' * WARNING * Event ',i7,' view',i3
252       $          ,' #clusters > ',i5,' --> MASKED')       $          ,' #clusters > ',i5,' --> MASKED')
253             if(debug)write(*,101)eventn(1),iv,nclstrmax_view             if(verbose.eq.1)write(*,101)eventn(1),iv,nclstrmax_view
254          endif          endif
255        enddo                     ! end loop on views        enddo                     ! end loop on views
256        do iv=1,nviews        do iv=1,nviews
# Line 205  C--------------------------------------- Line 270  C---------------------------------------
270        do iv = 1,nviews        do iv = 1,nviews
271           ngood = ngood + good1(iv)           ngood = ngood + good1(iv)
272        enddo        enddo
273        if(debug.and.ngood.ne.0)print*,'* WARNING * Event ',eventn(1)        if(verbose.eq.1.and.ngood.ne.0)
274         $     print*,'* WARNING * Event ',eventn(1)
275       $     ,':LEVEL1 event status: '       $     ,':LEVEL1 event status: '
276       $     ,(good1(i),i=1,nviews)       $     ,(good1(i),i=1,nviews)
277  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 394  c     add strips exceeding inclusion cut Line 460  c     add strips exceeding inclusion cut
460  c------------------------------------------------------------------------  c------------------------------------------------------------------------
461                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
462    
463                    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
464                       if(value(ir).gt.clinclcut(ir)) then                       if(value(ir).gt.clinclcut(ir)) then
465                          rmax=ir !include a strip on the right                          rmax=ir !include a strip on the right
466                       else                       else
# Line 404  c--------------------------------------- Line 470  c---------------------------------------
470    
471                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
472    
473                    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
474                       if(value(il).gt.clinclcut(il)) then                       if(value(il).gt.clinclcut(il)) then
475                          lmax=il !include a strip on the left                          lmax=il !include a strip on the left
476                       else                       else
# Line 412  c--------------------------------------- Line 478  c---------------------------------------
478                       endif                       endif
479                    endif                    endif
480    
481    c                  if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
482    
483                 enddo            !ends strip inclusion loop                 enddo            !ends strip inclusion loop
484                 goto 211                 goto 211
485   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 500  c---------------------------------------
500                    rmax = rmax+1                    rmax = rmax+1
501                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
502                 endif                 endif
503    c-------------------------------------------------------------------------------
504    c     adjust the cluster in order to have at least ANOTHER strip around the seed
505    c-------------------------------------------------------------------------------
506    c$$$               if(iseed-1.eq.lmax.and.lmax.ne.first)then
507    c$$$                  lmax = lmax-1
508    c$$$                  if( (rmax-lmax+1).gt.nclstrp )rmax=rmax-1
509    c$$$               endif
510    c$$$               if(iseed+1.eq.rmax.and.rmax.ne.last )then
511    c$$$                  rmax = rmax+1
512    c$$$                  if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
513    c$$$               endif
514    c---------------------------------------------------
515    c     now we have 5 stored-strips around the maximum
516    c---------------------------------------------------
517    
518  c------------------------------------------------------------------------  c------------------------------------------------------------------------
519  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 547  c$$$     $                 ,' clusters o
547    
548                 ladder_view(nclstr_view) = nld(iseed,iv)                 ladder_view(nclstr_view) = nld(iseed,iv)
549                 maxs_view(nclstr_view)   = iseed                 maxs_view(nclstr_view)   = iseed
                mult_view(nclstr_view)   = rmax-lmax+1  
550                 rmax_view(nclstr_view)   = rmax                 rmax_view(nclstr_view)   = rmax
551                 lmax_view(nclstr_view)   = lmax                 lmax_view(nclstr_view)   = lmax
552    c               mult_view(nclstr_view)   = rmax-lmax+1
553                   mult_view(nclstr_view)   = 0
554                   do ii=lmax,rmax
555                      if(value(ii).gt.clinclcut(ii))  
556         $                 mult_view(nclstr_view) = mult_view(nclstr_view)+1
557                   enddo
558    
559    
560  c$$$               if(rmax-lmax+1.gt.25)  c$$$               if(rmax-lmax+1.gt.25)
561  c$$$     $              print*,'view ',iv  c$$$     $              print*,'view ',iv
# Line 563  c        posizione del cluster seed nell Line 651  c        posizione del cluster seed nell
651           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
652    
653              clsignal(ind) = value(j) ! clsignal array              clsignal(ind) = value(j) ! clsignal array
654    c$$$            print*,ind,clsignal(ind)
655              ivk=nvk(j)              ivk=nvk(j)
656              ist=nst(j)              ist=nst(j)
657    
# Line 578  c     if(value(j).gt.0) Line 666  c     if(value(j).gt.0)
666       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge
667           enddo           enddo
668    
669  c         print*,'view ',iv,' -- save_cluster -- nclstr1: '  c$$$         print*,'view ',iv,' -- save_cluster -- nclstr1: '
670  c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),sgnl(nclstr1)  c$$$     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),sgnl(nclstr1)
671            c$$$         print*,'----------------------'
672    
673        enddo        enddo
674                
675        return        return
# Line 632  c$$$      end Line 721  c$$$      end
721    
722        subroutine stripmask(iv,ivk)        subroutine stripmask(iv,ivk)
723    
724    *     -----------------------------------------------
725  *     this routine set va1 and single-strip masks,  *     this routine set va1 and single-strip masks,
726  *     on the basis of the VA1 mask saved in the DB  *     on the basis of the VA1 mask saved in the DB
727  *  *
728  *     mask(nviews,nva1_view,nstrips_va1) !strip mask  *     mask(nviews,nva1_view,nstrips_va1) !strip mask
729  *     mask_vk(nviews,nva1_view)          !VA1 mask  *     mask_vk(nviews,nva1_view)          !VA1 mask
730  *  *     -----------------------------------------------
731        include 'commontracker.f'        include 'commontracker.f'
732        include 'level1.f'        include 'level1.f'
733        include 'common_reduction.f'        include 'common_reduction.f'
# Line 645  c$$$      end Line 735  c$$$      end
735    
736  *     init mask  *     init mask
737        do is=1,nstrips_va1        do is=1,nstrips_va1
738    *        --------------------------------------------------------
739    *        if VA1-mask from DB is 0 or 1, three masks are combined:
740    *        - from DB (a-priori mask)
741    *        - run-based (chip declared bad on the basis of <SIG>)
742    *        - event-based (failure in CN computation)
743    *        --------------------------------------------------------
744    c         print*,iv,ivk
745    c     $        ,mask_vk(iv,ivk),mask_vk_ev(iv,ivk),mask_vk_run(iv,ivk)
746           if( mask_vk(iv,ivk) .ne. -1)then                       if( mask_vk(iv,ivk) .ne. -1)then            
747              mask(iv,ivk,is) = 1              mask(iv,ivk,is) = 1
748       $           * mask_vk(iv,ivk) !from DB       $           * mask_vk(iv,ivk)     !from DB
749       $           * mask_vk_ev(iv,ivk) !from <SIG>       $           * mask_vk_ev(iv,ivk)  !from <SIG>
750       $           * mask_vk_run(iv,ivk) !from CN       $           * mask_vk_run(iv,ivk) !from CN
751    *        -----------------------------------------------------------
752    *        if VA1-mask from DB is -1 only event-based mask is applied
753    *        -----------------------------------------------------------
754           else           else
755              mask(iv,ivk,is) = -1              mask(iv,ivk,is) = -1
756       $           * mask_vk(iv,ivk) !from DB       $           * mask_vk(iv,ivk)     !from DB
757       $           * mask_vk_ev(iv,ivk) !from CN       $           * mask_vk_ev(iv,ivk)  !from CN
758           endif           endif
759        enddo        enddo
760                

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

  ViewVC Help
Powered by ViewVC 1.1.23