/[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.10 by pam-fi, Thu Oct 26 16:22:38 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           ierror = 220
         print*,'event ',eventn(1),' >>>>>  decode ERROR'  
         goto 200  
103        endif        endif
104    
105  c--------------------------------------------------  c--------------------------------------------------
106  c     computes common noise for each VA1  c     computes common noise for each VA1
107  c     (excluding strips affected by signal,  c     (excluding strips with signal,
108  c     tagged with the flag CLSTR)  c     tagged with the flag CLSTR)
109  c--------------------------------------------------  c--------------------------------------------------
110        do iv=1,nviews        do iv=1,nviews
111          do ik=1,nva1_view           ima=0
112            cn(iv,ik)=0           !initializes cn variable           do ik=1,nva1_view
113            if(mask_vk(iv,ik).eq.1)call cncomp(iv,ik)              cn(iv,ik)  = 0
114          enddo              cnrms(iv,ik)  = 0
115                cnn(iv,ik) = -1
116                mask_vk_ev(iv,ik)=1
117                iflag=0
118                if(mask_vk(iv,ik).eq.1)call cncomp(iv,ik,iflag)
119                if(iflag.ne.0)then
120                   ima=ima+1
121                   mask_vk_ev(iv,ik)=0
122                   ierror = 220
123                endif
124             enddo
125     100     format(' * WARNING * Event ',i7,' view',i3,': VK MASK ',24i1)
126             if(ima.ne.0.and.debug)write(*,100)eventn(1),iv
127         $        ,(mask_vk_ev(iv,ik),ik=1,nva1_view)
128        enddo        enddo
129    
130          call stripmask !compute mask(i,j,k), combining mask_vk_ev and mask_vk
131    
132  c---------------------------------------------  c---------------------------------------------
133  c     loops on views, VA1 and strips,  c     loops on views, VA1 and strips,
# Line 67  c     and computes strips signals using Line 135  c     and computes strips signals using
135  c     badstrip, pedestals, and  c     badstrip, pedestals, and
136  c     sigma informations from histograms  c     sigma informations from histograms
137  c---------------------------------------------  c---------------------------------------------
       flag_shower = .false.  
138        ind=1                     !clsignal array index        ind=1                     !clsignal array index
139    
140        do iv=1,nviews            !loop on views        do iv=1,nviews            !loop on views
141          do is=1,nstrips_view    !loop on strips (1)          do is=1,nstrips_view    !loop on strips (1)
142            if(mod(iv,2).eq.1) then            if(mod(iv,2).eq.1) then
# Line 80  C===  > Y view Line 148  C===  > Y view
148       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
149              clinclcut(is)=incuty*sigma(iv,nvk(is),nst(is))              clinclcut(is)=incuty*sigma(iv,nvk(is),nst(is))
150       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
151  ccc            print*,"value(",is,")(reduction)= ",value(is)              sat(is)=0
152                if( adc(iv,nvk(is),nst(is)).lt.adc_saty )sat(is)=1
153            else                        else            
154  C===  > X view  C===  > X view
155              value(is)= (DBLE(adc(iv,nvk(is),nst(is)))              value(is)= (DBLE(adc(iv,nvk(is),nst(is)))
# Line 90  C===  > X view Line 159  C===  > X view
159       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
160              clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))              clinclcut(is)=incutx*sigma(iv,nvk(is),nst(is))
161       $           *mask(iv,nvk(is),nst(is))       $           *mask(iv,nvk(is),nst(is))
162                sat(is)=0
163                if( adc(iv,nvk(is),nst(is)).gt.adc_satx )sat(is)=1
164            endif            endif
165          enddo                   !end loop on strips (1)          enddo                   !end loop on strips (1)
166          call search_cluster(iv)          call search_cluster(iv)
167          if(flag_shower.eqv..true.)then  
168            call init_level1                        if(.not.flag_shower)then
169            good1=0             call save_cluster(iv)
170            goto 200              !jump to next event          else
171               fshower(iv) = 1
172               GOOD1(DSPnumber(iv)) = 11
173          endif          endif
174        enddo                     ! end loop on views        enddo                     ! end loop on views
175        do iv=1,nviews        do iv=1,nviews
176          do ik=1,nva1_view          do ik=1,nva1_view
177            cnev(iv,ik)=cn(iv,ik) !assigns computed CN to ntuple variables            cnev(iv,ik)    = cn(iv,ik) !assigns computed CN to ntuple variables
178  ccc          print*,"cnev(",iv,",",ik,")(reduction)= ",cnev(iv,ik)            cnrmsev(iv,ik) = cnrms(iv,ik) !assigns computed CN to ntuple variables
179              cnnev(iv,ik)   = cnn(iv,ik) !assigns computed CN to ntuple variables
180          enddo          enddo
181        enddo        enddo
 c$$$      nevent_good = nevent_good + 1  
         
182  C---------------------------------------------  C---------------------------------------------
183  C     come here if GOOD1=0  C     come here if GOOD1=0
184  C     or the event has too many clusters  C     or the event has too many clusters
185  C---------------------------------------------  C---------------------------------------------
   
186   200  continue   200  continue
187  ccc      print*,'nclstr1(reduction)=',nclstr1  
188          ngood = 0
189          do iv = 1,nviews
190             ngood = ngood + good1(iv)
191          enddo
192          if(ngood.ne.0)print*,'* WARNING * Event ',eventn(1)
193         $     ,':LEVEL1 event status: '
194         $     ,(good1(i),i=1,nviews)
195  c------------------------------------------------------------------------  c------------------------------------------------------------------------
196  c      c
197  c     closes files and exits  c     closes files and exits
198  c      c
199  c------------------------------------------------------------------------  c------------------------------------------------------------------------
200                      RETURN
201        RETURN                          END
       END                        
202    
203  ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***
204  *  *
# Line 142  c--------------------------------------- Line 219  c---------------------------------------
219        include 'level1.f'        include 'level1.f'
220        include 'level0.f'        include 'level0.f'
221    
222        good1=0  c      good1 = 0
223        nclstr1=0        do iv=1,12
224        totCLlength=0           good1(iv) = 1 !missing packet
225          enddo
226          nclstr1 = 0
227          totCLlength = 0
228        do ic=1,nclstrmax        do ic=1,nclstrmax
229           view(ic)=0           view(ic) = 0
230           ladder(ic)=0           ladder(ic) = 0
231           indstart(ic)=0           indstart(ic) = 0
232           indmax(ic)=0           indmax(ic) = 0
233           maxs(ic)=0           maxs(ic) = 0
234           mult(ic)=0                     mult(ic) = 0          
235           dedx(ic)=0           dedx(ic) = 0
236             whichtrack(ic) = 0
237    
238        enddo        enddo
239        do id=1,maxlength         !???        do id=1,maxlength         !???
240           clsignal(id)=0.           clsignal(id) = 0.
241             clsigma(id)  = 0.
242             cladc(id)    = 0.
243             clbad(id)    = 0.
244        enddo        enddo
245        do iv=1,nviews        do iv=1,nviews
246  c        crc1(iv)=0  c        crc1(iv)=0
247          do ik=1,nva1_view          do ik=1,nva1_view
248            cnev(iv,ik)=0            cnev(iv,ik) = 0
249              cnnev(iv,ik) = 0
250          enddo          enddo
251            fshower(iv) = 0
252        enddo        enddo
253                
254        return        return
255        end        end
256    
257  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
258  *  *
259  *  *
# Line 177  c        crc1(iv)=0 Line 265  c        crc1(iv)=0
265        subroutine search_cluster(iv)        subroutine search_cluster(iv)
266    
267        include 'commontracker.f'        include 'commontracker.f'
       include 'common_reduction.f'  
268        include 'level0.f'        include 'level0.f'
269        include 'level1.f'        include 'level1.f'
270        include 'calib.f'        include 'calib.f'
271    
272          include 'common_reduction.f'
273            
274    
275  c     local variables  c     local variables
276        integer rmax,lmax         !estremi del cluster        integer rmax,lmax         !estremi del cluster
277        integer rstop,lstop       !per decidere quali strip includere nel cluster        integer rstop,lstop      
278                                  ! oltre il seed        integer first,last
279        integer first,last,diff   !per includere le strip giuste... !???        integer fsat,lsat
280    
281        integer multtemp          !temporary multiplicity variable        external nst
282    
283        integer CLlength          !lunghezza in strip del cluster        iseed=-999                !cluster seed index initialization
284    
285        external nst        inext=-999                !index where to start new cluster search
286    
287  c------------------------------------------------------------------------        flag_shower = .false.
288  c     looks for clusters on each view        nclstr_view=0
 C     : CERCO STRIP SOPRA CLSEEDCUT, POI SCORRO A DX FINCHE'  
 c     NON TROVO  
 C     STRIP PIU' BASSA (in segnale/rumore)  
 C     => L'ULTIMA DELLA SERIE CRESCENTE  
 C     (LA PIU' ALTA) E' IL  
 C     CLUSTER SEED. POI SCORRO A SX E DX INCLUDENDO TUTTE  
 C     LE STRIP (FINO A 17 AL  
 C     MAX) CHE SUPERANO CLINCLCUT.  
 C     QUANDO CERCO IL CLUSTER SEED SUCCESSIVO SALTO LA STRIP  
 C     ADIACENTE A DESTRA  
 C     DELL'ULTIMO CLUSTER SEED (CHE SARA' NECESSARIAMENTE  
 C     PIU' BASSA) E PRENDO  
 C     COME SEED UNA STRIP SOLO SE IL SUO SEGNALE E'  
 C     MAGGIORE DI QUELLO DELLA STRIP  
 C     PRECEDENTE (PRATICAMENTE PER EVITARE CHE L'ULTIMA  
 C     STRIP DI UN GRUPPO DI STRIP  
 C     TUTTE SOPRA IL CLSEEDCUT VENGA AUTOMATICAMENTE PRESA  
 C     COME SEED... DEVE ESSERE  
 C     PRESA SOLO SE IL CLUSTER E' DOUBLE PEAKED...)  
 c------------------------------------------------------------------------  
 c     6 ottobre 2003  
 c     Elena: CLSEEDCUT = 7 (old value 10)  
 c     Elena: CLINCLCUT = 4 (old value 5)  
289    
290        iseed=-999                !cluster seed index initialization        do jl=1,nladders_view              !1..3 !loops on ladders
291    
292             first = 1+nstrips_ladder*(jl-1) !1,1025,2049
293             last  = nstrips_ladder*jl       !1024,2048,3072
294    
295        do jl=1,nladders_view     !1..3 !loops on ladders  *        X views have 1018 strips instead of 1024
          first=1+nstrips_ladder*(jl-1) !1,1025,2049  
          last=nstrips_ladder*jl !1024,2048,3072  
 c     X views have 1018 strips instead of 1024  
296           if(mod(iv,2).eq.0) then           if(mod(iv,2).eq.0) then
297              first=first+3              first=first+3
298              last=last-3              last=last-3
299           endif           endif
300    
301           do is=first,last       !loop on strips in each ladder           do is=first,last       !loop on strips in each ladder
302              if(is.le.iseed+1) goto 220  
303  c-----------------------------------------  c---------------------------------------------
304  c     after a cluster seed as been found,  c     new-cluster search starts at index inext
305  c     look for next one skipping one strip on the right  c---------------------------------------------
306  c     (i.e. look for double peak cluster)              if(is.lt.inext) goto 220 ! next strip
307  c-----------------------------------------  
             if(is.ne.first) then  
                if(value(is).le.value(is-1)) goto 220  
             endif  
 c-----------------------------------------  
 c     skips cluster seed  
 c     finding if strips values are descreasing (a strip  
 c     can be a cluster seed only if previous strip value  
 c     is lower)  
 c-----------------------------------------  
308              if(value(is).gt.clseedcut(is)) then              if(value(is).gt.clseedcut(is)) then
 ccc              print*,"value(",is,")=",value(is),  
 ccc     $             " .gt.clseedcut(",is,")=",clseedcut(is)  
309  c-----------------------------------------  c-----------------------------------------
310  c     possible SEED...  c     possible SEED...
311  c-----------------------------------------  c-----------------------------------------
312                 itemp=is                 itemp = is
313                   fsat = 0         ! first saturated strip
314                   lsat = 0         ! last saturated strip
315                 if(itemp.eq.last) goto 230 !estremo...                 if(itemp.eq.last) goto 230 !estremo...
316                 do while(value(itemp)  c              ------------------------                
317       $              /sigma(iv,nvk(itemp),nst(itemp))  c              search for first maximum
318       $              .le.value(itemp+1)  c              ------------------------
319       $              /sigma(iv,nvk(itemp+1),nst(itemp+1))) !BIAS: aggiustare il caso uguale!???                 do while(
320                    itemp=itemp+1       $                   value(itemp).le.value(itemp+1)
321                    if(itemp.eq.last) goto 230 !stops if reaches last strip       $              .and.value(itemp+1).gt.clseedcut(itemp+1))
322                      itemp = itemp+1
323                      if(itemp.eq.last)   goto 230 !stops if reaches last strip
324                      if(sat(itemp).eq.1) goto 230 !stop if reaches a saturated strip
325                 enddo            ! of the ladder                 enddo            ! of the ladder
326   230           continue   230           continue
327  c-----------------------------------------  c              -----------------------------
328    c              check if strips are saturated
329    c              -----------------------------    
330                   if( sat(itemp).eq.1 )then
331                      fsat = itemp
332                      lsat = itemp
333                      if(itemp.eq.last) goto 231 !estremo...
334                      do while( sat(itemp+1).eq.1 )
335                         itemp = itemp+1
336                         lsat = itemp
337                         if(itemp.eq.last)   goto 231 !stops if reaches last strip
338                      enddo                  
339                   endif
340     231           continue
341    c---------------------------------------------------------------------------
342  c     fownd SEED!!!  c     fownd SEED!!!
343  c-----------------------------------------  c     (if there are saturated strips, the cluster is centered in the middle)
344                 iseed=itemp      c---------------------------------------------------------------------------
345  c----------------------------------------------------------                 if(fsat.eq.0.and.lsat.eq.0)then
346                      iseed = itemp ! <<< SEED
347                   else
348                      iseed = int((lsat+fsat)/2) ! <<< SEED
349    c$$$                  print*,'saturated strips ',fsat,lsat,iseed
350    c$$$                  print*,'--> ',(value(ii),ii=fsat,lsat)
351                   endif    
352    c---------------------------------------------------------------
353  c     after finding a cluster seed, checks also adjacent strips,  c     after finding a cluster seed, checks also adjacent strips,
354  C     and marks the ones exceeding clinclcut  C     and tags the ones exceeding clinclcut
355  c----------------------------------------------------------  c---------------------------------------------------------------
356                 ir=iseed         !indici destro                 ir=iseed         !indici destro
357                 il=iseed         ! e sinistro                 il=iseed         ! e sinistro
358                                
# Line 282  c--------------------------------------- Line 363  c---------------------------------------
363                 lstop=0          ! inclusion loop                 lstop=0          ! inclusion loop
364    
365                 do while(lstop.eq.0.or.rstop.eq.0) !shifts left and right from                 do while(lstop.eq.0.or.rstop.eq.0) !shifts left and right from
366                    ir=ir+1       !position index for strips on right side of  
367                                  ! cluster seed  
368                    il=il-1       !and for left side                    ir=ir+1       !index for right side
369                      il=il-1       !index for left side
370  c------------------------------------------------------------------------  c------------------------------------------------------------------------
371  c     checks for last or first strip of the ladder  c     checks for last or first strip of the ladder
372  c------------------------------------------------------------------------  c------------------------------------------------------------------------
373                    if(ir.gt.last) then !when index goes beyond last strip                    if( ir.gt.last  ) rstop = 1                      
374                       rstop=1    ! of the ladder, change rstop flag in order                    if( il.lt.first ) lstop = 1
                                 ! to "help" exiting from loop  
                   endif  
                     
                   if(il.lt.first) then !idem when index goes beyond  
                      lstop=1    ! first strip of the ladder  
                   endif  
375                                        
376  c------------------------------------------------------------------------  c------------------------------------------------------------------------
377  c     check for clusters including more than nclstrp strips  c     add strips exceeding inclusion cut
378  c------------------------------------------------------------------------  c------------------------------------------------------------------------
379                    if((rmax-lmax+1).ge.nclstrp) then                    if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
380                       goto 210   !exits inclusion loop:  
381                                  ! lmax and rmax maintain last value                    if(rstop.eq.0) then !if right cluster morder has not been reached
382                                  ! NB .ge.!???                       if(value(ir).gt.clinclcut(ir)) then
383                    endif                          rmax=ir !include a strip on the right
 c------------------------------------------------------------------------  
 c     marks strips exceeding inclusion cut  
 c------------------------------------------------------------------------  
                   if(rstop.eq.0) then !if last strip of the ladder or last  
                                 ! over-cut strip has not been reached  
                      if(value(ir).gt.clinclcut(ir)) then !puts in rmax the  
                         rmax=ir ! last right over-cut strip  
384                       else                       else
385                          rstop=1 !otherwise cluster ends on right and rstop                          rstop=1 !cluster right end
386                       endif      ! flag=1 signals it                       endif    
387                    endif                    endif
388                    if(lstop.eq.0) then  
389                      if( (rmax-lmax+1).ge.nclstrp )goto 210   !exits inclusion loop
390    
391                      if(lstop.eq.0) then !if left cluster morder has not been reached
392                       if(value(il).gt.clinclcut(il)) then                       if(value(il).gt.clinclcut(il)) then
393                          lmax=il                          lmax=il !include a strip on the left
394                       else                       else
395                          lstop=1                          lstop=1 !cluster left end
396                       endif                       endif
397                    endif                    endif
398    
399                 enddo            !ends strip inclusion loop                 enddo            !ends strip inclusion loop
400                   goto 211
401   210           continue         !jumps here if more than nclstrp have been included   210           continue         !jumps here if more than nclstrp have been included
402                        c               print*,'>>> nclstrp! '
403                 multtemp=rmax-lmax+1 !stores multiplicity in temp   211           continue
404                                  ! variable. NB rmax and lmax can change later in  c-----------------------------------------
405                                  ! order to include enough strips to calculate eta3  c     end of inclusion loop!
406                                  ! and eta4. so mult is not always equal to cllength  c-----------------------------------------
407  c------------------------------------------------------------------------                
408  c     NB per essere sicuro di poter calcolare eta3 e eta4 devo includere  c------------------------------------------------------------------------
409  c     sempre e comunque le 2 strip adiacenti al cluster seed e quella  c     adjust the cluster in order to have at least a strip around the seed
410  c     adiacente ulteriore dalla parte della piu' alta fra queste due  c------------------------------------------------------------------------
411  c     (vedi oltre...)!???                 if(iseed.eq.lmax.and.lmax.ne.first)then
412  c------------------------------------------------------------------------                    lmax = lmax-1
413                      if( (rmax-lmax+1).gt.nclstrp )rmax=rmax-1
414  c     nel caso di estremi del ladder...!???                 endif
415                   if(iseed.eq.rmax.and.rmax.ne.last )then
416  c     ho meno di 4 strip nel cluster --> se sono sui bordi o quasi del ladder                    rmax = rmax+1
417  c     costruisco il cluster ad hoc e poi esco, se non sono sui bordi o quasi                    if( (rmax-lmax+1).gt.nclstrp )lmax=lmax+1
 c     vado oltre (aggiungero' quindi strip a sx e dx in modo da poter calcolare  
 c     eta3e4)  
                if((rmax-lmax+1).lt.4) then  
   
                   if(iseed.eq.first) then !estremi...  
                      rmax=iseed+2 !NB in questo modo puo' anche capitare di  
                      lmax=iseed ! includere strip sotto taglio di inclusione  
                      goto 250   ! che non serviranno per eta3e4!???  
                   endif  
                     
                   if(iseed.eq.last) then !estremi...  
                      rmax=iseed  
                      lmax=iseed-2 !NB 2 e non 3, perche' altrimenti sarei in  
                      goto 250   ! ((rmax-lmax+1).lt.4).eq.false. !???  
                   endif         !NMB questo e' l'unico caso di cllength=3!???  
                     
                   if(iseed.eq.first+1) then !quasi estremi...  
                      rmax=iseed+2  
                      lmax=iseed-1  
                      goto 250  
                   endif  
                   if(iseed.eq.last-1) then  
                      rmax=iseed+1  
                      lmax=iseed-2  
                      goto 250  
                   endif  
 c     se ho 4 o piu' strip --> se sono sui bordi esco, se sono sui quasi bordi  
 c     includo la strip del bordo  
                else  
                     
                   if(iseed.eq.first) goto 250 !estremi... non includo altro                    
                   if(iseed.eq.last) goto 250  
                   if(iseed.eq.first+1) then !quasi estremi... mi assicuro di  
                      lmax=first ! avere le strip adiacenti al seed  
                      if((rmax-lmax+1).gt.nclstrp) rmax=rmax-1 !NB effetto  
                      goto 250   ! coperta: se la lunghezza del cluster era gia'  
                   endif         ! al limite (nclstrp), per poter aggiungere questa  
                                 ! strip a sinistra devo toglierne una a destra...!???  
                   if(iseed.eq.last-1) then  
                      rmax=last  
                      if((rmax-lmax+1).gt.nclstrp) lmax=lmax+1  
                      goto 250  
                   endif                    
418                 endif                 endif
419    
420  c------------------------------------------------------------------------  c------------------------------------------------------------------------
421  c     be sure to include in the cluster the cluster seed with its 2 adjacent  c     adjust the cluster in order to store a minimum number of strips
422  c     strips, and the one adjacent to the greatest between this two strip, as the  c------------------------------------------------------------------------
423  c     fourth one. if the strips have the same value (!) the fourth one is chosen                 do while( (rmax-lmax+1).lt.nclstrpmin )
424  c     as the one having the greatest value between the second neighbors  
425  c------------------------------------------------------------------------                    vl = -99999
426                 if(value(iseed+1).eq.value(iseed-1)) then                    vr = -99999
427                    if(value(iseed+2).ge.value(iseed-2)) then !??? qui cmq c'e'                    if(lmax-1.ge.first) vl = value(lmax-1)
428                       diff=(iseed+2)-rmax                    if(rmax+1.le.last ) vr = value(rmax+1)
429                       if(diff.gt.0) then                    if(vr.ge.vl) then
430                          rmax=rmax+diff                       rmax = rmax+1
431                          if((rmax-lmax+1).gt.nclstrp) then                    else  
432                             lmax=rmax-nclstrp+1                       lmax = lmax-1
                         endif  
                      endif  
                      diff=(iseed-1)-lmax  
                      if(diff.lt.0) then  
                         lmax=lmax+diff  
                         if((rmax-lmax+1).gt.nclstrp) then  
                            rmax=lmax+nclstrp-1  
                         endif  
                      endif  
                   else  
                      diff=(iseed-2)-lmax  
                      if(diff.lt.0) then  
                         lmax=lmax+diff  
                         if((rmax-lmax+1).gt.nclstrp) then  
                            rmax=lmax+nclstrp-1  
                         endif  
                      endif  
                      diff=(iseed+1)-rmax  
                      if(diff.gt.0) then  
                         rmax=rmax+diff  
                         if((rmax-lmax+1).gt.nclstrp) then  
                            lmax=rmax-nclstrp+1  
                         endif  
                      endif  
                       
                   endif  
                elseif(value(iseed+1).gt.value(iseed-1)) then  
 c     !??? sposto il limite del cluster a destra per includere sempre le strip  
 c     necessarie al calcolo di eta-i  
 c     se il cluster diventa  troppo lungo lo accorcio a sinistra per avere non piu'  
 c     di nclstrp (in questo caso sono sicuro di aver gia' incluso le strip  
 c     necessarie al calcolo di eta-i a sinistra, quindi se voglio posso uscire)  
                   diff=(iseed+2)-rmax  
                   if(diff.gt.0) then  
                      rmax=rmax+diff  
                      if((rmax-lmax+1).gt.nclstrp) then  
                         lmax=rmax-nclstrp+1  
 c     goto 250  
                      endif  
                   endif  
                   diff=(iseed-1)-lmax  
                   if(diff.lt.0) then  
                      lmax=lmax+diff  
                      if((rmax-lmax+1).gt.nclstrp) then  
                         rmax=lmax+nclstrp-1  
 c     goto 250 !inutile!???  
                      endif  
                   endif  
                else  
                   diff=(iseed-2)-lmax  
                   if(diff.lt.0) then  
                      lmax=lmax+diff  
                      if((rmax-lmax+1).gt.nclstrp) then  
                         rmax=lmax+nclstrp-1  
 c     goto 250  
                      endif  
                   endif  
                   diff=(iseed+1)-rmax  
                   if(diff.gt.0) then  
                      rmax=rmax+diff  
                      if((rmax-lmax+1).gt.nclstrp) then  
                         lmax=rmax-nclstrp+1  
 c     goto 250 !inutile!???  
                      endif  
433                    endif                    endif
434                 endif                    
435   250           continue                 enddo
436    
437  c--------------------------------------------------------  c--------------------------------------------------------
438  c     fills ntuple variables  c     store cluster info
439  c--------------------------------------------------------  c--------------------------------------------------------
440                 nclstr1=nclstr1+1 !cluster number                 nclstr_view = nclstr_view + 1 !cluster number
441  ccc               print*,nclstr1,multtemp  
442                 if(nclstr1.gt.nclstrmax) then !too many clusters for the event:                 if(nclstr_view.gt.nclstrmax_view) then !too many clusters for the view:
443                    good1=0       ! event  c$$$                  if(verbose) print*,'Event ',eventn(1),
444                    nclstr1=0  c$$$     $                 ': more than ',nclstrmax_view
445                    totCLlength=0  c$$$     $                 ,' clusters on view ',iv
446                    flag_shower = .true.                    flag_shower = .true.
                   print*,'Event ',eventn(1),  
      $                 ': more than ',nclstrmax,' clusters'  
447                    goto 2000                    goto 2000
448                 endif                 endif
449                 view(nclstr1)=iv !vista del cluster  
450                 ladder(nclstr1)=nld(iseed,iv) !ladder a cui appartiene il cluster seed                 ladder_view(nclstr_view) = nld(iseed,iv)
451                 maxs(nclstr1)=iseed !strip del cluster seed                 maxs_view(nclstr_view)   = iseed
452                 mult(nclstr1)=multtemp !molteplicita'                 mult_view(nclstr_view)   = rmax-lmax+1
453                                 rmax_view(nclstr_view)   = rmax
454                 indstart(nclstr1)=ind !posizione dell'inizio del cluster nell'                 lmax_view(nclstr_view)   = lmax
455                                  ! array clsignal  
456                 indmax(nclstr1)=indstart(nclstr1)+(iseed-lmax) !posizione del  c$$$               if(rmax-lmax+1.gt.25)
457                                  ! cluster seed nell'array clsignal  c$$$     $              print*,'view ',iv
458    c$$$     $              ,' cl ',nclstr_view,' mult ',rmax-lmax+1
459    c------------------------------------------------------------------------
460    c     search for a dowble peak inside the cluster                                                                                                            
461    c------------------------------------------------------------------------
462                   inext = rmax+1   !<< index where to start new-cluster search
463                                
464                 CLlength=rmax-lmax+1 !numero di strip del cluster                 vmax = 0
465                 totCLlength=totCLlength+CLlength                 vmin = value(iseed)
466                 dedx(nclstr1)=0                 imax = iseed
467                 do j=lmax,rmax   !stores sequentially cluter strip values in                 imin = iseed
468                    clsignal(ind)=value(j) ! clsignal array                 do iss = max(iseed+1,lsat+1),rmax
469                    ind=ind+1                    if( value(iss).lt.vmin )then
470  c                  if(value(j).gt.0)                       if( imax.ne.iseed )goto 221 !found dowble peek
471                    if(value(j).gt.clinclcut(j))                       imin = iss
472       $                 dedx(nclstr1)=dedx(nclstr1)+value(j) !cluster charge                       vmin = value(iss)
473                      else
474                         delta = value(iss) - value(imin)
475                         cut = sqrt(clinclcut(iss)**2 + clinclcut(imin)**2)
476                         if(
477         $                    delta.gt.cut .and.
478         $                    value(iss).gt.clseedcut(iss).and.
479         $                    .true.)then
480                            if( value(iss).gt.vmax )then                        
481                               imax = iss
482                               vmax = value(iss)
483                            else
484                               goto 221 !found dowble peek
485                            endif
486                         endif
487                      endif
488                 enddo                 enddo
489     221           continue
490                  
491                   if(imax.gt.iseed)then
492                      inext = imax    !<< index where to start new-cluster search
493    c$$$                  print*,'--- double peek ---'
494    c$$$                  print*,(value(ii),ii=lmax,rmax)
495    c$$$                  print*,'seed ',iseed,' imin ',imin,' imax ',imax
496                   endif
497  c--------------------------------------------------------  c--------------------------------------------------------
498  c      c
499  c--------------------------------------------------------  c--------------------------------------------------------
500              endif               !end possible seed conditio              endif               !end possible seed conditio
501   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 515  c---------------------------------------
515  *  *
516  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
517    
518          subroutine save_cluster(iv)
519    *
520    *     (080/2006 Elena Vannuccini)
521    *     Save the clusters view by view
522    
523          include 'commontracker.f'
524          include 'level1.f'
525          include 'calib.f'
526          include 'common_reduction.f'
527    
528          integer CLlength          !lunghezza in strip del cluster
529    
530          do ic=1,nclstr_view
531    
532             nclstr1 = nclstr1+1
533             view(nclstr1)   = iv
534             ladder(nclstr1) = ladder_view(ic)
535             maxs(nclstr1)   = maxs_view(ic)
536             mult(nclstr1)   = mult_view(ic)
537                  
538    c        posizione dell'inizio del cluster nell' array clsignal
539             indstart(nclstr1) = ind
540    c        posizione del cluster seed nell'array clsignal
541             indmax(nclstr1)   = indstart(nclstr1)
542         $        +( maxs_view(ic) - lmax_view(ic) )
543            
544             CLlength      = rmax_view(ic) - lmax_view(ic) + 1 !numero di strip salvate
545             totCLlength   = totCLlength + CLlength
546             dedx(nclstr1) = 0
547             do j=lmax_view(ic),rmax_view(ic)         !stores sequentially cluter strip values in
548    
549                clsignal(ind) = value(j) ! clsignal array
550    
551                ivk=nvk(j)
552                ist=nst(j)
553    
554                clsigma(ind) = sigma(iv,ivk,ist)
555                cladc(ind)   = adc(iv,ivk,ist)
556                clbad(ind)   = bad(iv,ivk,ist)
557    c            clped(ind)   = pedestal(iv,ivk,ist)
558    
559                ind=ind+1
560    c     if(value(j).gt.0)
561                if(value(j).gt.clinclcut(j))
562         $           dedx(nclstr1) = dedx(nclstr1) + value(j) !cluster charge
563             enddo
564    
565    c         print*,'view ',iv,' -- save_cluster -- nclstr1: '
566    c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),dedx(nclstr1)
567            
568          enddo
569          
570          return
571          end
572    *---***---***---***---***---***---***---***---***
573    *
574    *
575    *
576    *
577    *
578    *---***---***---***---***---***---***---***---***
579    
580    
581        subroutine stripmask        subroutine stripmask
582    
# Line 533  c--------------------------------------- Line 588  c---------------------------------------
588  *  *
589        include 'commontracker.f'        include 'commontracker.f'
590        include 'level1.f'        include 'level1.f'
591          include 'common_reduction.f'
592        include 'calib.f'        include 'calib.f'
593    
 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$$$*     ----------------------  
     
594  *     init mask  *     init mask
595        do iv=1,nviews        do iv=1,nviews
596           do ivk=1,nva1_view           do ivk=1,nva1_view
597              do is=1,nstrips_va1              do is=1,nstrips_va1
598                 mask(iv,ivk,is) = mask_vk(iv,ivk)  c               mask(iv,ivk,is) = mask_vk(iv,ivk)
599                   mask(iv,ivk,is) = mask_vk(iv,ivk) * mask_vk_ev(iv,ivk)              
600              enddo              enddo
601           enddo           enddo
602        enddo        enddo
603    
 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  
604    
605        return        return
606        end        end

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

  ViewVC Help
Powered by ViewVC 1.1.23