/[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.14 by pam-fi, Wed Nov 29 10:09:38 2006 UTC revision 1.20 by pam-fi, Thu May 24 16:45:48 2007 UTC
# Line 23  Line 23 
23        integer ierror        integer ierror
24        ierror = 0        ierror = 0
25    
26    c$$$      debug = .true.
27    c$$$      verbose = .true.
28    c$$$      warning = .true.
29    
30    *     //////////////////////////
31    *     initialize some parameters
32    *     //////////////////////////
33    
34        call init_level1        call init_level1
35    
36    c      debug=.true.
37    
38          if(debug)print*,'-- check LEVEL0 status'
39    
40          ievco=-1
41          mismatch=0
42  c      good1 = good0  c      good1 = good0
43  c--------------------------------------------------  c--------------------------------------------------
44  c     check the LEVEL0 event status for missing  c     check the LEVEL0 event status for missing
# Line 41  c           ------------------------ Line 55  c           ------------------------
55  c           CRC error  c           CRC error
56  c           ------------------------  c           ------------------------
57              if(crc(iv).eq.1) then              if(crc(iv).eq.1) then
58                 GOOD1(DSPnumber(iv)) = 2  c               GOOD1(DSPnumber(iv)) = 2
59                 goto 18 !next view  c               GOOD1(DSPnumber(iv)) = GOOD1(DSPnumber(iv)) + 2**1
60                   GOOD1(DSPnumber(iv)) = ior(GOOD1(DSPnumber(iv)),2**1)
61     102           format(' * WARNING * Event ',i7,' view',i3
62         $          ,' CRC error')
63                   if(debug)write(*,102)eventn(1),DSPnumber(iv)
64    c               goto 18 !next view
65              endif              endif
66  c           ------------------------  c           ------------------------
67  c           online-software alarm  c           online-software alarm
# Line 57  c           ------------------------ Line 76  c           ------------------------
76       $           fc(iv).ne.0.or.       $           fc(iv).ne.0.or.
77       $           DATAlength(iv).eq.0.or.       $           DATAlength(iv).eq.0.or.
78       $           .false.)then       $           .false.)then
79                 GOOD1(DSPnumber(iv))=3  c               GOOD1(DSPnumber(iv))=3
80                 goto 18  c               GOOD1(DSPnumber(iv)) = GOOD1(DSPnumber(iv)) + 2**2
81                   GOOD1(DSPnumber(iv)) = ior(GOOD1(DSPnumber(iv)),2**2)
82     103           format(' * WARNING * Event ',i7,' view',i3
83         $          ,' software alarm')
84                   if(debug)write(*,103)eventn(1),DSPnumber(iv)
85    c               goto 18
86              endif              endif
87  c           ------------------------  c           ------------------------
88  c           DSP-counter jump  c           DSP-counter jump
89  c           ------------------------  c           ------------------------
90              if(  c     commentato perche` non e` un controllo significativo nel caso in cui
91       $           eventn_old(iv).ne.0.and. !first event in this file  c     la subroutine venga chiamata per riprocessare l'evento
92       $           eventn(iv).ne.1.and.     !first event in run  c     sostituito con un check dei contatori dei vari dsp
93       $           good_old(DSPnumber(iv)).ne.0.and. !previous event corrupted  c$$$            if(
94       $           .true.)then  c$$$     $           eventn_old(iv).ne.0.and. !first event in this file
95    c$$$     $           eventn(iv).ne.1.and.     !first event in run
96                 if(eventn(iv).ne.(eventn_old(iv)+1))then  c$$$     $           good_old(DSPnumber(iv)).ne.0.and. !previous event corrupted
97                    GOOD1(DSPnumber(iv))=4  c$$$     $           .true.)then
98                    goto 18  c$$$
99    c$$$               if(eventn(iv).ne.(eventn_old(iv)+1))then
100    c$$$c                  GOOD1(DSPnumber(iv))=4
101    c$$$c                  GOOD1(DSPnumber(iv)) = GOOD1(DSPnumber(iv)) + 2**3
102    c$$$                  GOOD1(DSPnumber(iv)) = ior(GOOD1(DSPnumber(iv)),2**3)
103    c$$$ 104              format(' * WARNING * Event ',i7,' view',i3
104    c$$$     $          ,' counter jump ',i10,i10)
105    c$$$                  if(debug)write(*,104)eventn(1),DSPnumber(iv)
106    c$$$     $                 ,eventn_old(iv),eventn(iv))
107    c$$$                  goto 18
108    c$$$               endif
109    c$$$
110    c$$$            endif
111    c           ------------------------
112    c 18         continue
113    c           ------------------------
114    c           DSP-counter
115    c           ------------------------
116                if( DSPnumber(iv).ne.0.and.GOOD1(DSPnumber(iv)).ne.1)then
117                   if(iv.ne.1.and.ievco.ne.-1)then
118                      if( eventn(iv).ne.ievco )then
119                         mismatch=1
120                      endif
121                 endif                 endif
122                   ievco = eventn(iv)
123              endif              endif
 c           ------------------------  
  18         continue  
124           endif           endif
125        enddo        enddo
126    
127    c      print*,'*** ',(eventn(iv),iv=1,12)
128          
129          if(mismatch.eq.1.and.debug)
130         $     print*,' * WARNING * DSP counter mismatch: '
131         $     ,(eventn(iv),iv=1,12)
132    
133        ngood = 0        ngood = 0
134        do iv = 1,nviews        do iv = 1,nviews
135            
136             if(mismatch.eq.1.and.GOOD1(iv).ne.1)
137         $        GOOD1(iv)=ior(GOOD1(iv),2**3)
138    
139           eventn_old(iv) = eventn(iv)           eventn_old(iv) = eventn(iv)
140           good_old(iv)   = good1(iv)           good_old(iv)   = good1(iv)
141           ngood = ngood + good1(iv)           ngood = ngood + good1(iv)
142    
143        enddo        enddo
144  c      if(ngood.ne.0)print*,'* WARNING * LEVEL0 event status: '  c$$$      if(verbose.and.ngood.ne.0)print*,'* WARNING * Event ',eventn(1)
145  c     $     ,(good1(i),i=1,nviews)  c$$$     $     ,':LEVEL0 event status: '
146    c$$$     $     ,(good1(i),i=1,nviews)
147  c--------------------------------------------------  c--------------------------------------------------
148  c     read the variable DATATRACKER from LEVEL0  c     read the variable DATATRACKER from LEVEL0
149  c     and fill the variable ADC (invertin view 11)  c     and fill the variable ADC (invertin view 11)
150  c--------------------------------------------------  c--------------------------------------------------
151          
152          if(debug)print*,'-- fill ADC vectors'
153    
154        call filladc(iflag)        call filladc(iflag)
155        if(iflag.ne.0)then        if(iflag.ne.0)then
156           ierror = 220           ierror = 220
# Line 102  c     computes common noise for each VA1 Line 161  c     computes common noise for each VA1
161  c     (excluding strips with signal,  c     (excluding strips with signal,
162  c     tagged with the flag CLSTR)  c     tagged with the flag CLSTR)
163  c--------------------------------------------------  c--------------------------------------------------
164          if(debug)print*,'-- compute CN'
165    
166        do iv=1,nviews        do iv=1,nviews
167           ima=0           ima=0
168           do ik=1,nva1_view           do ik=1,nva1_view
169              cn(iv,ik)  = 0              cn(iv,ik)    = 0
170              cnrms(iv,ik)  = 0              cnrms(iv,ik) = 0
171              cnn(iv,ik) = -1              cnn(iv,ik)   = -1
172              iflag=0              iflag = 0
173              mask_vk_ev(iv,ik)=1              mask_vk_ev(iv,ik) = 1
174              call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks              call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks
175  c     NBNBNBNBNB mask per la striscia 1 !!!!!!!!  *           --------------------------------------
176              if(mask(iv,ik,1).eq.1)call cncomp(iv,ik,iflag)  *           if chip is not masked ---> evaluate CN
177              if(iflag.ne.0)then  *           --------------------------------------
178                 ima=ima+1              if( mask(iv,ik,1).eq.1 ) then !!!NBNB mask per la striscia 1 !!!!!!!!
179                 mask_vk_ev(iv,ik)=0                 call cncomp(iv,ik,iflag)
180                 ierror = 220                 if(iflag.ne.0)then
181                      ima=ima+1
182                      mask_vk_ev(iv,ik)=0
183                      ierror = 220
184                   endif
185                   call stripmask(iv,ik) !compute mask(i,j,k), combining VA1-masks
186              endif              endif
             call stripmask(iv,ik)      !compute mask(i,j,k), combining VA1-masks  
               
187           enddo           enddo
188   100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)   100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
189           if(ima.ne.0.and.debug)write(*,100)eventn(1),iv           if(ima.ne.0.and.verbose)write(*,100)eventn(1),iv
190       $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)       $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
191    c         if(ima.ne.0)write(*,100)eventn(1),iv
192    c     $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)  
193        enddo        enddo
194    
195  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 136  c     sigma informations from histograms Line 202  c     sigma informations from histograms
202  c---------------------------------------------  c---------------------------------------------
203        ind=1                     !clsignal array index        ind=1                     !clsignal array index
204    
205          if(debug)print*,'-- search clusters'
206        do iv=1,nviews            !loop on views        do iv=1,nviews            !loop on views
207          do is=1,nstrips_view    !loop on strips (1)          do is=1,nstrips_view    !loop on strips (1)
208            if(mod(iv,2).eq.1) then            if(mod(iv,2).eq.1) then
209  C===  > Y view  C===  > Y view
210    c             print*,iv,nvk(is),nst(is),adc(iv,nvk(is),nst(is))
211    c     $            ,cn(iv,nvk(is))
212    c     $            ,pedestal(iv,nvk(is),nst(is))
213              value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))              value(is)= -(DBLE(adc(iv,nvk(is),nst(is)))
214       $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))       $           -cn(iv,nvk(is))-pedestal(iv,nvk(is),nst(is)))
215       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
# Line 166  C===  > X view Line 236  C===  > X view
236    
237          if(.not.flag_shower)then          if(.not.flag_shower)then
238             call save_cluster(iv)             call save_cluster(iv)
239               if(debug)print*,'view ',iv,' #clusters ', nclstr_view
240          else          else
241             fshower(iv) = 1             fshower(iv) = 1
242  c           GOOD1(DSPnumber(iv)) = 11 !AHAHAHAHA ORRORE!!  c           GOOD1(DSPnumber(iv)) = 11 !AHAHAHAHA ORRORE!!
243             GOOD1(iv) = 11  c           GOOD1(iv) = 11
244    c           GOOD1(iv) = GOOD1(iv) + 2**5
245               GOOD1(iv) = ior(GOOD1(iv),2**5)
246     101       format(' * WARNING * Event ',i7,' view',i3
247         $          ,' #clusters > ',i5,' --> MASKED')
248               if(verbose)write(*,101)eventn(1),iv,nclstrmax_view
249          endif          endif
250        enddo                     ! end loop on views        enddo                     ! end loop on views
251        do iv=1,nviews        do iv=1,nviews
# Line 189  C--------------------------------------- Line 265  C---------------------------------------
265        do iv = 1,nviews        do iv = 1,nviews
266           ngood = ngood + good1(iv)           ngood = ngood + good1(iv)
267        enddo        enddo
268  c$$$      if(ngood.ne.0)print*,'* WARNING * Event ',eventn(1)        if(verbose.and.ngood.ne.0)print*,'* WARNING * Event ',eventn(1)
269  c$$$     $     ,':LEVEL1 event status: '       $     ,':LEVEL1 event status: '
270  c$$$     $     ,(good1(i),i=1,nviews)       $     ,(good1(i),i=1,nviews)
271  c------------------------------------------------------------------------  c------------------------------------------------------------------------
272  c  c
273  c     closes files and exits  c     closes files and exits
# Line 232  c      good1 = 0 Line 308  c      good1 = 0
308           indmax(ic) = 0           indmax(ic) = 0
309           maxs(ic) = 0           maxs(ic) = 0
310           mult(ic) = 0                     mult(ic) = 0          
311           dedx(ic) = 0           sgnl(ic) = 0
312           whichtrack(ic) = 0           whichtrack(ic) = 0     !assigned @ level2
313    
314        enddo        enddo
315        do id=1,maxlength         !???        do id=1,maxlength         !???
# Line 543  c        posizione del cluster seed nell Line 619  c        posizione del cluster seed nell
619                    
620           CLlength      = rmax_view(ic) - lmax_view(ic) + 1 !numero di strip salvate           CLlength      = rmax_view(ic) - lmax_view(ic) + 1 !numero di strip salvate
621           totCLlength   = totCLlength + CLlength           totCLlength   = totCLlength + CLlength
622           dedx(nclstr1) = 0           sgnl(nclstr1) = 0
623           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
624    
625              clsignal(ind) = value(j) ! clsignal array              clsignal(ind) = value(j) ! clsignal array
626    c$$$            print*,ind,clsignal(ind)
627              ivk=nvk(j)              ivk=nvk(j)
628              ist=nst(j)              ist=nst(j)
629    
# Line 559  c            clped(ind)   = pedestal(iv, Line 635  c            clped(ind)   = pedestal(iv,
635              ind=ind+1              ind=ind+1
636  c     if(value(j).gt.0)  c     if(value(j).gt.0)
637              if(value(j).gt.clinclcut(j))              if(value(j).gt.clinclcut(j))
638       $           dedx(nclstr1) = dedx(nclstr1) + value(j) !cluster charge       $           sgnl(nclstr1) = sgnl(nclstr1) + value(j) !cluster charge
639           enddo           enddo
640    
641  c         print*,'view ',iv,' -- save_cluster -- nclstr1: '  c$$$         print*,'view ',iv,' -- save_cluster -- nclstr1: '
642  c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),dedx(nclstr1)  c$$$     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),sgnl(nclstr1)
643            c$$$         print*,'----------------------'
644    
645        enddo        enddo
646                
647        return        return
# Line 616  c$$$      end Line 693  c$$$      end
693    
694        subroutine stripmask(iv,ivk)        subroutine stripmask(iv,ivk)
695    
696    *     -----------------------------------------------
697  *     this routine set va1 and single-strip masks,  *     this routine set va1 and single-strip masks,
698  *     on the basis of the VA1 mask saved in the DB  *     on the basis of the VA1 mask saved in the DB
699  *  *
700  *     mask(nviews,nva1_view,nstrips_va1) !strip mask  *     mask(nviews,nva1_view,nstrips_va1) !strip mask
701  *     mask_vk(nviews,nva1_view)          !VA1 mask  *     mask_vk(nviews,nva1_view)          !VA1 mask
702  *  *     -----------------------------------------------
703        include 'commontracker.f'        include 'commontracker.f'
704        include 'level1.f'        include 'level1.f'
705        include 'common_reduction.f'        include 'common_reduction.f'
# Line 629  c$$$      end Line 707  c$$$      end
707    
708  *     init mask  *     init mask
709        do is=1,nstrips_va1        do is=1,nstrips_va1
710    *        --------------------------------------------------------
711    *        if VA1-mask from DB is 0 or 1, three masks are combined:
712    *        - from DB (a-priori mask)
713    *        - run-based (chip declared bad on the basis of <SIG>)
714    *        - event-based (failure in CN computation)
715    *        --------------------------------------------------------
716    c         print*,iv,ivk
717    c     $        ,mask_vk(iv,ivk),mask_vk_ev(iv,ivk),mask_vk_run(iv,ivk)
718           if( mask_vk(iv,ivk) .ne. -1)then                       if( mask_vk(iv,ivk) .ne. -1)then            
719              mask(iv,ivk,is) = 1              mask(iv,ivk,is) = 1
720       $           * mask_vk(iv,ivk) !from DB       $           * mask_vk(iv,ivk)     !from DB
721       $           * mask_vk_ev(iv,ivk) !from <SIG>       $           * mask_vk_ev(iv,ivk)  !from <SIG>
722       $           * mask_vk_run(iv,ivk) !from CN       $           * mask_vk_run(iv,ivk) !from CN
723    *        -----------------------------------------------------------
724    *        if VA1-mask from DB is -1 only event-based mask is applied
725    *        -----------------------------------------------------------
726           else           else
727              mask(iv,ivk,is) = -1              mask(iv,ivk,is) = -1
728       $           * mask_vk(iv,ivk) !from DB       $           * mask_vk(iv,ivk)     !from DB
729       $           * mask_vk_ev(iv,ivk) !from CN       $           * mask_vk_ev(iv,ivk)  !from CN
730           endif           endif
731        enddo        enddo
732                

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.20

  ViewVC Help
Powered by ViewVC 1.1.23