/[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.1 by mocchiut, Fri May 19 13:15:56 2006 UTC revision 1.9 by pam-fi, Mon Oct 16 12:36:52 2006 UTC
# Line 10  Line 10 
10  *    *  
11  *************************************************************************  *************************************************************************
12    
13        subroutine reductionflight()        subroutine reductionflight(ierror)
14    
15        include 'commontracker.f'        include 'commontracker.f'
16        include 'level0.f'        include 'level0.f'
# Line 18  Line 18 
18        include 'common_reduction.f'        include 'common_reduction.f'
19        include 'calib.f'        include 'calib.f'
20                
21          data eventn_old/nviews*0/
22    
23          integer ierror
24          ierror = 0
25    
26  *     -------------------------------------------------------  *     -------------------------------------------------------
27  *     STRIP MASK  *     STRIP MASK
28  *     -------------------------------------------------------  *     -------------------------------------------------------
29    
30        call stripmask  c      call stripmask   !called later, after CN computation
31        call init_level1        call init_level1
32    
33  C---------------------------------------------------  c      good1 = good0
34  C     variables in blocks GENERAL and CPU are anyway filled  c--------------------------------------------------
35  C     in order to mantain sincronization among  c     check the LEVEL0 event status for missing
36  C     events at different levels  c     sections or DSP alarms
37  C---------------------------------------------------  c     ==> set the variable GOOD1(12)
38        good1=good0  c--------------------------------------------------
39  c$$$      do iv=1,12        do iv=1,nviews
40  c$$$        crc1(iv)=crc(iv)           if(DSPnumber(iv).gt.0.and.DSPnumber(iv).le.12)then
41  c$$$      enddo  c           ------------------------
42  ccc      print*,'totdatalength(reduction)=',TOTDATAlength  c           GOOD
43  ccc      print*,''  c           ------------------------
44                GOOD1(DSPnumber(iv))=0 !OK
45    c           ------------------------
46    c           CRC error
47    c           ------------------------
48                if(crc(iv).eq.1) then
49                   GOOD1(DSPnumber(iv)) = 2
50                   goto 18 !next view
51                endif
52    c           ------------------------
53    c           online-software alarm
54    c           ------------------------
55                if(
56         $           fl1(iv).ne.0.or.
57         $           fl2(iv).ne.0.or.
58         $           fl3(iv).ne.0.or.
59         $           fl4(iv).ne.0.or.
60         $           fl5(iv).ne.0.or.
61         $           fl6(iv).ne.0.or.
62         $           fc(iv).ne.0.or.
63         $           DATAlength(iv).eq.0.or.
64         $           .false.)then
65                   GOOD1(DSPnumber(iv))=3
66                   goto 18
67                endif
68    c           ------------------------
69    c           DSP-counter jump
70    c           ------------------------
71                if(
72         $           eventn_old(iv).ne.0.and. !first event in this file
73         $           eventn(iv).ne.1.and.     !first event in run
74         $           good_old(DSPnumber(iv)).ne.0.and. !previous event corrupted
75         $           .true.)then
76    
77                   if(eventn(iv).ne.(eventn_old(iv)+1))then
78                      GOOD1(DSPnumber(iv))=4
79                      goto 18
80                   endif
81    
82                endif
83    c           ------------------------
84     18         continue
85             endif
86          enddo
87    
88          ngood = 0
89          do iv = 1,nviews
90             eventn_old(iv) = eventn(iv)
91             good_old(iv)   = good1(iv)
92             ngood = ngood + good1(iv)
93          enddo
94    c      if(ngood.ne.0)print*,'* WARNING * LEVEL0 event status: '
95    c     $     ,(good1(i),i=1,nviews)
96  c--------------------------------------------------  c--------------------------------------------------
97  c     read the variable DATATRACKER from LEVEL0  c     read the variable DATATRACKER from LEVEL0
98  c     and fill the variable ADC (inverting view 11)  c     and fill the variable ADC (invertin view 11)
99  c--------------------------------------------------  c--------------------------------------------------
100        call filladc(iflag)        call filladc(iflag)
101        if(iflag.ne.0)then        if(iflag.ne.0)then
102          good1=0  c        good1=0!<<<<<<<<<<<<<<<
103          print*,'event ',eventn(1),' >>>>>  decode ERROR'  c       if(DEBUG)print*,'event ',eventn(1),' >>>>>  decode ERROR'
104          goto 200           ierror = 220
105    c        goto 200
106    c         print*,'filladc error'
107        endif        endif
108    
109  c--------------------------------------------------  c--------------------------------------------------
# Line 54  c     (excluding strips affected by sign Line 112  c     (excluding strips affected by sign
112  c     tagged with the flag CLSTR)  c     tagged with the flag CLSTR)
113  c--------------------------------------------------  c--------------------------------------------------
114        do iv=1,nviews        do iv=1,nviews
115          do ik=1,nva1_view           ima=0
116            cn(iv,ik)=0           !initializes cn variable           do ik=1,nva1_view
117            if(mask_vk(iv,ik).eq.1)call cncomp(iv,ik)              cn(iv,ik)  = 0
118          enddo              cnn(iv,ik) = -1
119                mask_vk_ev(iv,ik)=1
120                iflag=0
121                if(mask_vk(iv,ik).eq.1)call cncomp(iv,ik,iflag)
122    c     if(iflag.ne.0)good1=0
123                if(iflag.ne.0)then
124                   ima=ima+1
125                   mask_vk_ev(iv,ik)=0
126                   ierror = 220
127    c$$$               if(verbose)
128    c$$$     $              print*,' * WARNING * Event ',eventn(1)
129    c$$$     $              ,': masked vk ',ik,' on view',iv
130                endif
131             enddo
132     100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
133    c         if(ima.ne.0.and.verbose)print*,' * WARNING * Event ',eventn(1)
134    c     $              ,' view',iv,': VK MASK '
135    c     $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
136             if(ima.ne.0.and.verbose)write(*,100)eventn(1),iv
137         $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
138        enddo        enddo
139    c      if(good1.eq.0)then
140    c         ierror = 220
141    c      endif
142    
143          call stripmask !compute mask(i,j,k), combining mask_vk_ev and mask_vk
144  c---------------------------------------------  c---------------------------------------------
145  c     loops on views, VA1 and strips,  c     loops on views, VA1 and strips,
146  c     and computes strips signals using  c     and computes strips signals using
# Line 69  c     sigma informations from histograms Line 149  c     sigma informations from histograms
149  c---------------------------------------------  c---------------------------------------------
150        flag_shower = .false.        flag_shower = .false.
151        ind=1                     !clsignal array index        ind=1                     !clsignal array index
152    
153        do iv=1,nviews            !loop on views        do iv=1,nviews            !loop on views
154          do is=1,nstrips_view    !loop on strips (1)          do is=1,nstrips_view    !loop on strips (1)
155            if(mod(iv,2).eq.1) then            if(mod(iv,2).eq.1) then
# Line 91  C===  > X view Line 172  C===  > X view
172              clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))              clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))
173       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
174            endif            endif
175    c$$$          print*,iv,is,' --- ',adc(iv,nvk(is),nst(is)),cn(iv,nvk(is))
176    c$$$     $         ,pedestal(iv,nvk(is),nst(is)),value(is)
177    c$$$     $         ,sigma(iv,nvk(is),nst(is))
178    c          if(value(is).gt.clseedcut(is))
179    c     $         print*,iv,is,' --- (ADC_PED_CN) ',value(is),clseedcut(is)
180          enddo                   !end loop on strips (1)          enddo                   !end loop on strips (1)
181          call search_cluster(iv)          call search_cluster(iv)
182          if(flag_shower.eqv..true.)then  c$$$        if(flag_shower.eqv..true.)then
183            call init_level1                c$$$          call init_level1              
184            good1=0  c$$$          good1=0
185            goto 200              !jump to next event  c$$$          goto 200              !jump to next event
186    c$$$        endif
187    ccc
188    ccc    modified by Elena (08/2006)
189    ccc
190            if(.not.flag_shower)then
191               call save_cluster(iv)
192            else
193               fshower(iv) = 1
194               GOOD1(DSPn) = 11
195          endif          endif
196        enddo                     ! end loop on views        enddo                     ! end loop on views
197        do iv=1,nviews        do iv=1,nviews
198          do ik=1,nva1_view          do ik=1,nva1_view
199            cnev(iv,ik)=cn(iv,ik) !assigns computed CN to ntuple variables            cnev(iv,ik)  = cn(iv,ik) !assigns computed CN to ntuple variables
200              cnnev(iv,ik) = cnn(iv,ik) !assigns computed CN to ntuple variables
201  ccc          print*,"cnev(",iv,",",ik,")(reduction)= ",cnev(iv,ik)  ccc          print*,"cnev(",iv,",",ik,")(reduction)= ",cnev(iv,ik)
202          enddo          enddo
203        enddo        enddo
 c$$$      nevent_good = nevent_good + 1  
         
204  C---------------------------------------------  C---------------------------------------------
205  C     come here if GOOD1=0  C     come here if GOOD1=0
206  C     or the event has too many clusters  C     or the event has too many clusters
207  C---------------------------------------------  C---------------------------------------------
   
208   200  continue   200  continue
209  ccc      print*,'nclstr1(reduction)=',nclstr1  
210          ngood = 0
211          do iv = 1,nviews
212             ngood = ngood + good1(iv)
213          enddo
214          if(ngood.ne.0)print*,'* WARNING * Event ',eventn(1)
215         $     ,':LEVEL1 event status: '
216         $     ,(good1(i),i=1,nviews)
217  c------------------------------------------------------------------------  c------------------------------------------------------------------------
218  c      c
219  c     closes files and exits  c     closes files and exits
220  c      c
221  c------------------------------------------------------------------------  c------------------------------------------------------------------------
222                      RETURN
223        RETURN                          END
       END                        
224    
225  ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***
226  *  *
# Line 142  c--------------------------------------- Line 241  c---------------------------------------
241        include 'level1.f'        include 'level1.f'
242        include 'level0.f'        include 'level0.f'
243    
244        good1=0  c      good1 = 0
245        nclstr1=0        do iv=1,12
246        totCLlength=0           good1(iv) = 1 !missing packet
247          enddo
248          nclstr1 = 0
249          totCLlength = 0
250        do ic=1,nclstrmax        do ic=1,nclstrmax
251           view(ic)=0           view(ic) = 0
252           ladder(ic)=0           ladder(ic) = 0
253           indstart(ic)=0           indstart(ic) = 0
254           indmax(ic)=0           indmax(ic) = 0
255           maxs(ic)=0           maxs(ic) = 0
256           mult(ic)=0                     mult(ic) = 0          
257           dedx(ic)=0           dedx(ic) = 0
258             whichtrack(ic) = 0
259    
260        enddo        enddo
261        do id=1,maxlength         !???        do id=1,maxlength         !???
262           clsignal(id)=0.           clsignal(id) = 0.
263             clsigma(id)  = 0.
264             cladc(id)    = 0.
265             clbad(id)    = 0.
266        enddo        enddo
267        do iv=1,nviews        do iv=1,nviews
268  c        crc1(iv)=0  c        crc1(iv)=0
269          do ik=1,nva1_view          do ik=1,nva1_view
270            cnev(iv,ik)=0            cnev(iv,ik) = 0
271              cnnev(iv,ik) = 0
272          enddo          enddo
273            fshower(iv) = 0
274        enddo        enddo
275                
276        return        return
# Line 177  c        crc1(iv)=0 Line 286  c        crc1(iv)=0
286        subroutine search_cluster(iv)        subroutine search_cluster(iv)
287    
288        include 'commontracker.f'        include 'commontracker.f'
       include 'common_reduction.f'  
289        include 'level0.f'        include 'level0.f'
290        include 'level1.f'        include 'level1.f'
291        include 'calib.f'        include 'calib.f'
292    
293          include 'common_reduction.f'
294            
295    
296  c     local variables  c     local variables
# Line 192  c     local variables Line 301  c     local variables
301    
302        integer multtemp          !temporary multiplicity variable        integer multtemp          !temporary multiplicity variable
303    
       integer CLlength          !lunghezza in strip del cluster  
   
304        external nst        external nst
305    
306  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 224  c     Elena: CLINCLCUT = 4 (old value 5) Line 331  c     Elena: CLINCLCUT = 4 (old value 5)
331    
332        iseed=-999                !cluster seed index initialization        iseed=-999                !cluster seed index initialization
333    
334          nclstr_view=0
335    
336        do jl=1,nladders_view     !1..3 !loops on ladders        do jl=1,nladders_view     !1..3 !loops on ladders
337           first=1+nstrips_ladder*(jl-1) !1,1025,2049           first=1+nstrips_ladder*(jl-1) !1,1025,2049
338           last=nstrips_ladder*jl !1024,2048,3072           last=nstrips_ladder*jl !1024,2048,3072
# Line 232  c     X views have 1018 strips instead o Line 341  c     X views have 1018 strips instead o
341              first=first+3              first=first+3
342              last=last-3              last=last-3
343           endif           endif
344    
345           do is=first,last       !loop on strips in each ladder           do is=first,last       !loop on strips in each ladder
346    
347              if(is.le.iseed+1) goto 220              if(is.le.iseed+1) goto 220
348  c-----------------------------------------  *******************************************************
349  c     after a cluster seed as been found,  *     Elena 08/2006
350  c     look for next one skipping one strip on the right  * QUESTA PARTE NON E` ADEGUATA per cluster con grossi rilasci di carica
351  c     (i.e. look for double peak cluster)  * perche` salva molte volte lo stesso cluster
352  c-----------------------------------------  * (salvo il cluster rispetto al primo massimo e basta...)
353              if(is.ne.first) then  *******************************************************
354                 if(value(is).le.value(is-1)) goto 220  c$$$c-----------------------------------------
355              endif  c$$$c     after a cluster seed as been found,
356  c-----------------------------------------  c$$$c     look for next one skipping one strip on the right
357  c     skips cluster seed  c$$$c     (i.e. look for double peak cluster)
358  c     finding if strips values are descreasing (a strip  c$$$c-----------------------------------------
359  c     can be a cluster seed only if previous strip value  c$$$            if(is.ne.first) then
360  c     is lower)  c$$$               if(value(is).le.value(is-1)) goto 220
361  c-----------------------------------------  c$$$            endif
362    c$$$c-----------------------------------------
363    c$$$c     skips cluster seed
364    c$$$c     finding if strips values are descreasing (a strip
365    c$$$c     can be a cluster seed only if previous strip value
366    c$$$c     is lower)
367    c$$$c-----------------------------------------
368    *******************************************************
369    * LA RICERCA PARTE DALL'ULTIMA STRIP SALVATA (***TEMPORANEO****)
370    *******************************************************
371                if(is.le.iseed+rmax+1) goto 220
372    *******************************************************
373    
374              if(value(is).gt.clseedcut(is)) then              if(value(is).gt.clseedcut(is)) then
375  ccc              print*,"value(",is,")=",value(is),  ccc              print*,"value(",is,")=",value(is),
376  ccc     $             " .gt.clseedcut(",is,")=",clseedcut(is)  ccc     $             " .gt.clseedcut(",is,")=",clseedcut(is)
# Line 256  c     possible SEED... Line 379  c     possible SEED...
379  c-----------------------------------------  c-----------------------------------------
380                 itemp=is                 itemp=is
381                 if(itemp.eq.last) goto 230 !estremo...                 if(itemp.eq.last) goto 230 !estremo...
382                 do while(value(itemp)  ****************************************************
383       $              /sigma(iv,nvk(itemp),nst(itemp))  *     modificato da Elena (08/2006) per salvare
384       $              .le.value(itemp+1)  *     il cluster intorno al massimo assoluto
385       $              /sigma(iv,nvk(itemp+1),nst(itemp+1))) !BIAS: aggiustare il caso uguale!???  ****************************************************
386    c$$$               do while(value(itemp)
387    c$$$     $              /sigma(iv,nvk(itemp),nst(itemp))
388    c$$$     $              .le.value(itemp+1)
389    c$$$     $              /sigma(iv,nvk(itemp+1),nst(itemp+1))) !BIAS: aggiustare il caso uguale!???
390    c$$$                  itemp=itemp+1
391    c$$$                  if(itemp.eq.last) goto 230 !stops if reaches last strip
392    c$$$               enddo            ! of the ladder
393                   do while(
394         $                   value(itemp).le.value(itemp+1)
395         $              .and.value(itemp+1).gt.clseedcut(itemp+1))
396                    itemp=itemp+1                    itemp=itemp+1
397                    if(itemp.eq.last) goto 230 !stops if reaches last strip                    if(itemp.eq.last) goto 230 !stops if reaches last strip
398                 enddo            ! of the ladder                 enddo            ! of the ladder
# Line 423  c--------------------------------------- Line 556  c---------------------------------------
556                             lmax=rmax-nclstrp+1                             lmax=rmax-nclstrp+1
557                          endif                          endif
558                       endif                       endif
                       
559                    endif                    endif
560                 elseif(value(iseed+1).gt.value(iseed-1)) then                 elseif(value(iseed+1).gt.value(iseed-1)) then
561  c     !??? sposto il limite del cluster a destra per includere sempre le strip  c     !??? sposto il limite del cluster a destra per includere sempre le strip
# Line 468  c     goto 250 !inutile!??? Line 600  c     goto 250 !inutile!???
600   250           continue   250           continue
601    
602  c--------------------------------------------------------  c--------------------------------------------------------
603  c     fills ntuple variables  c     fills cluster variables
604  c--------------------------------------------------------  c--------------------------------------------------------
605                 nclstr1=nclstr1+1 !cluster number  c$$$               nclstr1=nclstr1+1 !cluster number
606  ccc               print*,nclstr1,multtemp  c$$$ccc               print*,nclstr1,multtemp
607                 if(nclstr1.gt.nclstrmax) then !too many clusters for the event:  c$$$               if(nclstr1.gt.nclstrmax) then !too many clusters for the event:
608                    good1=0       ! event  c$$$                  if(verbose)print*,'Event ',eventn(1),
609                    nclstr1=0  c$$$     $                 ': more than ',nclstrmax,' clusters'
610                    totCLlength=0  c$$$                  good1=0       ! event
611    c$$$                  nclstr1=0
612    c$$$                  totCLlength=0
613    c$$$                  flag_shower = .true.
614    c$$$                  goto 2000
615    c$$$               endif
616    c$$$               view(nclstr1)   = iv !vista del cluster
617    c$$$               ladder(nclstr1) = nld(iseed,iv) !ladder a cui appartiene il cluster seed
618    c$$$               maxs(nclstr1)   = iseed !strip del cluster seed
619    c$$$               mult(nclstr1)   = multtemp !molteplicita'
620    c$$$              
621    c$$$               indstart(nclstr1) = ind !posizione dell'inizio del cluster nell'
622    c$$$c                                      ! array clsignal
623    c$$$               indmax(nclstr1)   = indstart(nclstr1)+(iseed-lmax) !posizione del
624    c$$$c                                      ! cluster seed nell'array clsignal
625    c$$$              
626    c$$$               CLlength      = rmax-lmax+1 !numero di strip del cluster
627    c$$$               totCLlength   = totCLlength+CLlength
628    c$$$               dedx(nclstr1) = 0
629    c$$$               do j=lmax,rmax   !stores sequentially cluter strip values in
630    c$$$                  clsignal(ind) = value(j) ! clsignal array
631    c$$$                  ind=ind+1
632    c$$$c                  if(value(j).gt.0)
633    c$$$                  if(value(j).gt.clinclcut(j))
634    c$$$     $                 dedx(nclstr1) = dedx(nclstr1) + value(j) !cluster charge
635    c$$$               enddo
636    ccc
637    ccc            *** Modified by Elena (08/2006) ***
638    ccc
639                   nclstr_view = nclstr_view + 1 !cluster number
640    c               print*,'view ',iv,' -- search_cluster -- nclstr_view: '
641    c     $              ,nclstr_view
642                   if(nclstr_view.gt.nclstrmax_view) then !too many clusters for the view:
643                      if(verbose) print*,'Event ',eventn(1),
644         $                 ': more than ',nclstrmax_view
645         $                 ,' clusters on view ',iv
646    c                  good1=0       ! event
647    c                  nclstr1=0
648    c                  totCLlength=0
649                    flag_shower = .true.                    flag_shower = .true.
                   print*,'Event ',eventn(1),  
      $                 ': more than ',nclstrmax,' clusters'  
650                    goto 2000                    goto 2000
651                 endif                 endif
652                 view(nclstr1)=iv !vista del cluster  
653                 ladder(nclstr1)=nld(iseed,iv) !ladder a cui appartiene il cluster seed  c               view(nclstr1)   = iv !vista del cluster
654                 maxs(nclstr1)=iseed !strip del cluster seed                 ladder_view(nclstr_view) = nld(iseed,iv) !ladder a cui appartiene il cluster seed
655                 mult(nclstr1)=multtemp !molteplicita'                 maxs_view(nclstr_view)   = iseed !strip del cluster seed
656                                 mult_view(nclstr_view)   = multtemp !molteplicita'
657                 indstart(nclstr1)=ind !posizione dell'inizio del cluster nell'                 rmax_view(nclstr_view)   = rmax
658                                  ! array clsignal                 lmax_view(nclstr_view)   = lmax
659                 indmax(nclstr1)=indstart(nclstr1)+(iseed-lmax) !posizione del  
                                 ! cluster seed nell'array clsignal  
                 
                CLlength=rmax-lmax+1 !numero di strip del cluster  
                totCLlength=totCLlength+CLlength  
                dedx(nclstr1)=0  
                do j=lmax,rmax   !stores sequentially cluter strip values in  
                   clsignal(ind)=value(j) ! clsignal array  
                   ind=ind+1  
 c                  if(value(j).gt.0)  
                   if(value(j).gt.clinclcut(j))  
      $                 dedx(nclstr1)=dedx(nclstr1)+value(j) !cluster charge  
                enddo  
660  c--------------------------------------------------------  c--------------------------------------------------------
661  c      c
662  c--------------------------------------------------------  c--------------------------------------------------------
663              endif               !end possible seed conditio              endif               !end possible seed conditio
664   220        continue            !jumps here to skip strips left of last seed   220        continue            !jumps here to skip strips left of last seed
# Line 522  c--------------------------------------- Line 678  c---------------------------------------
678  *  *
679  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
680    
681          subroutine save_cluster(iv)
682    *
683    *     (080/2006 Elena Vannuccini)
684    *     Save the clusters view by view
685    
686          include 'commontracker.f'
687          include 'level1.f'
688          include 'calib.f'
689          include 'common_reduction.f'
690    
691          integer CLlength          !lunghezza in strip del cluster
692    
693          do ic=1,nclstr_view
694    
695             nclstr1 = nclstr1+1
696             view(nclstr1)   = iv
697             ladder(nclstr1) = ladder_view(ic)
698             maxs(nclstr1)   = maxs_view(ic)
699             mult(nclstr1)   = mult_view(ic)
700                  
701    c        posizione dell'inizio del cluster nell' array clsignal
702             indstart(nclstr1) = ind
703    c        posizione del cluster seed nell'array clsignal
704             indmax(nclstr1)   = indstart(nclstr1)
705         $        +( maxs_view(ic) - lmax_view(ic) )
706            
707             CLlength      = rmax_view(ic) - lmax_view(ic) + 1 !numero di strip salvate
708             totCLlength   = totCLlength + CLlength
709             dedx(nclstr1) = 0
710             do j=lmax_view(ic),rmax_view(ic)         !stores sequentially cluter strip values in
711    
712                clsignal(ind) = value(j) ! clsignal array
713    
714                ivk=nvk(j)
715                ist=nst(j)
716    
717                clsigma(ind) = sigma(iv,ivk,ist)
718                cladc(ind)   = adc(iv,ivk,ist)
719                clbad(ind)   = bad(iv,ivk,ist)
720    c            clped(ind)   = pedestal(iv,ivk,ist)
721    
722                ind=ind+1
723    c     if(value(j).gt.0)
724                if(value(j).gt.clinclcut(j))
725         $           dedx(nclstr1) = dedx(nclstr1) + value(j) !cluster charge
726             enddo
727    
728    c         print*,'view ',iv,' -- save_cluster -- nclstr1: '
729    c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),dedx(nclstr1)
730            
731          enddo
732          
733          return
734          end
735    *---***---***---***---***---***---***---***---***
736    *
737    *
738    *
739    *
740    *
741    *---***---***---***---***---***---***---***---***
742    
743    
744        subroutine stripmask        subroutine stripmask
745    
# Line 533  c--------------------------------------- Line 751  c---------------------------------------
751  *  *
752        include 'commontracker.f'        include 'commontracker.f'
753        include 'level1.f'        include 'level1.f'
754          include 'common_reduction.f'
755        include 'calib.f'        include 'calib.f'
756    
 c$$$      character*20 data_file  
 c$$$  
 c$$$      character*3 aid  
 c$$$      character*6 adate  
 c$$$      integer id  
 c$$$      integer date  
 c$$$  
 c$$$*     ----------------------  
 c$$$*     retrieve date and id  
 c$$$      aid=data_file(8:10)  
 c$$$      adate=data_file(2:6)  
 c$$$      READ (aid, '(I3)'), id  
 c$$$      READ (adate, '(I6)'), date  
 c$$$*     ----------------------  
     
757  *     init mask  *     init mask
758        do iv=1,nviews        do iv=1,nviews
759           do ivk=1,nva1_view           do ivk=1,nva1_view
760              do is=1,nstrips_va1              do is=1,nstrips_va1
761                 mask(iv,ivk,is) = mask_vk(iv,ivk)  c               mask(iv,ivk,is) = mask_vk(iv,ivk)
762                   mask(iv,ivk,is) = mask_vk(iv,ivk) * mask_vk_ev(iv,ivk)              
763              enddo              enddo
764           enddo           enddo
765        enddo        enddo
766    
 c$$$*     ---------------------  
 c$$$*     VIEW 2 - VK 23-24  
 c$$$*     couple of vk damaged during integration  
 c$$$      if(date.ge.50208)then  
 c$$$cc         print*,'MASK: view 2 - vk 23/24'  
 c$$$         mask_vk(2,23)=0  
 c$$$         mask_vk(2,24)=0  
 c$$$         do is=1,nstrips_va1  
 c$$$            mask(2,23,is)=0  
 c$$$            mask(2,24,is)=0  
 c$$$         enddo  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 7 - VK 11-12  
 c$$$      if(date.ge.50209)then  
 c$$$        if(.not.(date.eq.50209.and.id.le.6)) then  
 c$$$cc          print*,'MASK: view 7 - vk 11/12'  
 c$$$          mask_vk(7,11)=0  
 c$$$          mask_vk(7,12)=0  
 c$$$          do is=1,nstrips_va1  
 c$$$            mask(7,11,is)=0  
 c$$$            mask(7,12,is)=0  
 c$$$          enddo  
 c$$$        endif  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 7 - VK 21-22  
 c$$$      if(date.ge.50316)then  
 c$$$cc         print*,'MASK: view 7 - vk 21/22'  
 c$$$         mask_vk(7,21)=0  
 c$$$         mask_vk(7,22)=0  
 c$$$         do is=1,nstrips_va1  
 c$$$            mask(7,21,is)=0  
 c$$$            mask(7,22,is)=0  
 c$$$         enddo  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 12 - VK 1-2-3-4  
 c$$$      if((date.eq.50317).and.(id.le.3))then  
 c$$$cc        print*,'MASK: view 12 - vk 1/2/3/4'  
 c$$$        mask_vk(12,1)=0  
 c$$$        mask_vk(12,2)=0  
 c$$$        mask_vk(12,3)=0  
 c$$$        mask_vk(12,4)=0  
 c$$$        do is=1,nstrips_va1  
 c$$$          mask(12,1,is)=0  
 c$$$          mask(12,2,is)=0  
 c$$$          mask(12,3,is)=0  
 c$$$          mask(12,4,is)=0  
 c$$$        enddo  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 7 - VK 5-6  
 c$$$      if(date.ge.50320)then  
 c$$$        if(.not.(date.eq.50320.and.id.le.3)) then  
 c$$$cc          print*,'MASK: view 7 - vk 5/6'  
 c$$$          mask_vk(7,5)=0  
 c$$$          mask_vk(7,6)=0  
 c$$$          do is=1,nstrips_va1  
 c$$$            mask(7,5,is)=0  
 c$$$            mask(7,6,is)=0  
 c$$$          enddo  
 c$$$        endif  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 7 - VK 13-14  
 c$$$      if(date.ge.50320)then  
 c$$$        if(.not.(date.eq.50320.and.id.le.5)) then  
 c$$$cc          print*,'MASK: view 7 - vk 13/14'  
 c$$$          mask_vk(7,13)=0  
 c$$$          mask_vk(7,14)=0  
 c$$$          do is=1,nstrips_va1  
 c$$$            mask(7,13,is)=0  
 c$$$            mask(7,14,is)=0  
 c$$$          enddo  
 c$$$        endif  
 c$$$      endif  
 c$$$  
 c$$$***   SAMARA  
 c$$$***   SAMARA  
 c$$$***   SAMARA  
 c$$$*     it needs further checks...  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 7 - VK 9-10  
 c$$$*     VIEW 12 - VK 1-2-3-4  
 c$$$      if((date.eq.50516).and.(id.le.8))then  
 c$$$cc        print*,'MASK: view 7 - vk 9/10'  
 c$$$cc        print*,'MASK: view 12 - vk 1/2/3/4'  
 c$$$        mask_vk(7,9)=0  
 c$$$        mask_vk(7,10)=0  
 c$$$        mask_vk(12,1)=0  
 c$$$        mask_vk(12,2)=0  
 c$$$        mask_vk(12,3)=0  
 c$$$        mask_vk(12,4)=0  
 c$$$        do is=1,nstrips_va1  
 c$$$          mask(7,9,is)=0  
 c$$$          mask(7,10,is)=0  
 c$$$          mask(12,1,is)=0  
 c$$$          mask(12,2,is)=0  
 c$$$          mask(12,3,is)=0  
 c$$$          mask(12,4,is)=0  
 c$$$        enddo  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 7 - VK 9-10  
 c$$$      if(date.ge.50516)then  
 c$$$        if(.not.(date.eq.50516.and.id.le.8)) then  
 c$$$cc          print*,'MASK: view 7 - vk 9/10'  
 c$$$          mask_vk(7,9)=0  
 c$$$          mask_vk(7,10)=0  
 c$$$          do is=1,nstrips_va1  
 c$$$            mask(7,9,is)=0  
 c$$$            mask(7,10,is)=0  
 c$$$          enddo  
 c$$$        endif  
 c$$$      endif  
 c$$$  
 c$$$*     ---------------------  
 c$$$*     VIEW 12 - VK 7-8  
 c$$$      if(date.ge.50523)then  
 c$$$        if(.not.(date.eq.50523.and.id.le.3)) then  
 c$$$cc          print*,'MASK: view 12 - vk 7/8'  
 c$$$          mask_vk(12,7)=0  
 c$$$          mask_vk(12,8)=0  
 c$$$          do is=1,nstrips_va1  
 c$$$            mask(12,7,is)=0  
 c$$$            mask(12,8,is)=0  
 c$$$          enddo  
 c$$$        endif  
 c$$$      endif  
767    
768        return        return
769        end        end

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.23