/[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.4 by pam-fi, Fri Aug 4 08:18:06 2006 UTC revision 1.5 by pam-fi, Tue Sep 5 12:52:21 2006 UTC
# Line 48  c     tagged with the flag CLSTR) Line 48  c     tagged with the flag CLSTR)
48  c--------------------------------------------------  c--------------------------------------------------
49        do iv=1,nviews        do iv=1,nviews
50          do ik=1,nva1_view          do ik=1,nva1_view
51            cn(iv,ik)=0                      cn(iv,ik)  = 0
52              cnn(iv,ik) = -1
53            mask_vk_ev(iv,ik)=1            mask_vk_ev(iv,ik)=1
54            iflag=0            iflag=0
55            if(mask_vk(iv,ik).eq.1)call cncomp(iv,ik,iflag)            if(mask_vk(iv,ik).eq.1)call cncomp(iv,ik,iflag)
# Line 63  c      if(good1.eq.0)then Line 64  c      if(good1.eq.0)then
64  c         ierror = 220  c         ierror = 220
65  c      endif  c      endif
66    
67        call stripmask !compute mask(i,j,k)        call stripmask !compute mask(i,j,k), combining mask_vk_ev and mask_vk
68  c---------------------------------------------  c---------------------------------------------
69  c     loops on views, VA1 and strips,  c     loops on views, VA1 and strips,
70  c     and computes strips signals using  c     and computes strips signals using
# Line 72  c     sigma informations from histograms Line 73  c     sigma informations from histograms
73  c---------------------------------------------  c---------------------------------------------
74        flag_shower = .false.        flag_shower = .false.
75        ind=1                     !clsignal array index        ind=1                     !clsignal array index
76    
77        do iv=1,nviews            !loop on views        do iv=1,nviews            !loop on views
78          do is=1,nstrips_view    !loop on strips (1)          do is=1,nstrips_view    !loop on strips (1)
79            if(mod(iv,2).eq.1) then            if(mod(iv,2).eq.1) then
# Line 101  c          if(value(is).gt.clseedcut(is) Line 103  c          if(value(is).gt.clseedcut(is)
103  c     $         print*,iv,is,' --- (ADC_PED_CN) ',value(is),clseedcut(is)  c     $         print*,iv,is,' --- (ADC_PED_CN) ',value(is),clseedcut(is)
104          enddo                   !end loop on strips (1)          enddo                   !end loop on strips (1)
105          call search_cluster(iv)          call search_cluster(iv)
106          if(flag_shower.eqv..true.)then  c$$$        if(flag_shower.eqv..true.)then
107            call init_level1                c$$$          call init_level1              
108            good1=0  c$$$          good1=0
109            goto 200              !jump to next event  c$$$          goto 200              !jump to next event
110    c$$$        endif
111    ccc
112    ccc    modified by Elena (08/2006)
113    ccc
114            if(.not.flag_shower)then
115               call save_cluster(iv)
116            else
117               fshower(iv) = 1
118          endif          endif
119        enddo                     ! end loop on views        enddo                     ! end loop on views
120        do iv=1,nviews        do iv=1,nviews
121          do ik=1,nva1_view          do ik=1,nva1_view
122            cnev(iv,ik)=cn(iv,ik) !assigns computed CN to ntuple variables            cnev(iv,ik)  = cn(iv,ik) !assigns computed CN to ntuple variables
123            cnevflag(iv,ik)=cnflag(iv,ik) !assigns computed CN to ntuple variables            cnnev(iv,ik) = cnn(iv,ik) !assigns computed CN to ntuple variables
124  ccc          print*,"cnev(",iv,",",ik,")(reduction)= ",cnev(iv,ik)  ccc          print*,"cnev(",iv,",",ik,")(reduction)= ",cnev(iv,ik)
125          enddo          enddo
126        enddo        enddo
# Line 146  c--------------------------------------- Line 156  c---------------------------------------
156        include 'level1.f'        include 'level1.f'
157        include 'level0.f'        include 'level0.f'
158    
159        good1=0        good1 = 0
160        nclstr1=0        nclstr1 = 0
161        totCLlength=0        totCLlength = 0
162        do ic=1,nclstrmax        do ic=1,nclstrmax
163           view(ic)=0           view(ic) = 0
164           ladder(ic)=0           ladder(ic) = 0
165           indstart(ic)=0           indstart(ic) = 0
166           indmax(ic)=0           indmax(ic) = 0
167           maxs(ic)=0           maxs(ic) = 0
168           mult(ic)=0                     mult(ic) = 0          
169           dedx(ic)=0           dedx(ic) = 0
170             whichtrack(ic) = 0
171    
172        enddo        enddo
173        do id=1,maxlength         !???        do id=1,maxlength         !???
174           clsignal(id)=0.           clsignal(id) = 0.
175             clsigma(id)  = 0.
176             cladc(id)    = 0.
177             clbad(id)    = 0.
178        enddo        enddo
179        do iv=1,nviews        do iv=1,nviews
180  c        crc1(iv)=0  c        crc1(iv)=0
181          do ik=1,nva1_view          do ik=1,nva1_view
182            cnev(iv,ik)=0            cnev(iv,ik) = 0
183              cnnev(iv,ik) = 0
184          enddo          enddo
185            fshower(iv) = 0
186        enddo        enddo
187                
188        return        return
# Line 181  c        crc1(iv)=0 Line 198  c        crc1(iv)=0
198        subroutine search_cluster(iv)        subroutine search_cluster(iv)
199    
200        include 'commontracker.f'        include 'commontracker.f'
       include 'common_reduction.f'  
201        include 'level0.f'        include 'level0.f'
202        include 'level1.f'        include 'level1.f'
203        include 'calib.f'        include 'calib.f'
204    
205          include 'common_reduction.f'
206            
207    
208  c     local variables  c     local variables
# Line 196  c     local variables Line 213  c     local variables
213    
214        integer multtemp          !temporary multiplicity variable        integer multtemp          !temporary multiplicity variable
215    
       integer CLlength          !lunghezza in strip del cluster  
   
216        external nst        external nst
217    
218  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 228  c     Elena: CLINCLCUT = 4 (old value 5) Line 243  c     Elena: CLINCLCUT = 4 (old value 5)
243    
244        iseed=-999                !cluster seed index initialization        iseed=-999                !cluster seed index initialization
245    
246          nclstr_view=0
247    
248        do jl=1,nladders_view     !1..3 !loops on ladders        do jl=1,nladders_view     !1..3 !loops on ladders
249           first=1+nstrips_ladder*(jl-1) !1,1025,2049           first=1+nstrips_ladder*(jl-1) !1,1025,2049
250           last=nstrips_ladder*jl !1024,2048,3072           last=nstrips_ladder*jl !1024,2048,3072
# Line 238  c     X views have 1018 strips instead o Line 255  c     X views have 1018 strips instead o
255           endif           endif
256           do is=first,last       !loop on strips in each ladder           do is=first,last       !loop on strips in each ladder
257              if(is.le.iseed+1) goto 220              if(is.le.iseed+1) goto 220
258  c-----------------------------------------  *******************************************************
259  c     after a cluster seed as been found,  *     Elena 08/2006
260  c     look for next one skipping one strip on the right  * QUESTA PARTE NON E` ADEGUATA per cluster con grossi rilasci di carica
261  c     (i.e. look for double peak cluster)  * perche` salva molte volte lo stesso cluster
262  c-----------------------------------------  * (salvo il cluster rispetto al massimo e basta...)
263              if(is.ne.first) then  *******************************************************
264                 if(value(is).le.value(is-1)) goto 220  c$$$c-----------------------------------------
265              endif  c$$$c     after a cluster seed as been found,
266  c-----------------------------------------  c$$$c     look for next one skipping one strip on the right
267  c     skips cluster seed  c$$$c     (i.e. look for double peak cluster)
268  c     finding if strips values are descreasing (a strip  c$$$c-----------------------------------------
269  c     can be a cluster seed only if previous strip value  c$$$            if(is.ne.first) then
270  c     is lower)  c$$$               if(value(is).le.value(is-1)) goto 220
271  c-----------------------------------------  c$$$            endif
272    c$$$c-----------------------------------------
273    c$$$c     skips cluster seed
274    c$$$c     finding if strips values are descreasing (a strip
275    c$$$c     can be a cluster seed only if previous strip value
276    c$$$c     is lower)
277    c$$$c-----------------------------------------
278    *******************************************************
279    * LA RICERCA PARTE DALL'ULTIMA STRIP SALVATA (***TEMPORANEO****)
280    *******************************************************
281                if(is.le.iseed+rmax+1) goto 220
282    *******************************************************
283    
284              if(value(is).gt.clseedcut(is)) then              if(value(is).gt.clseedcut(is)) then
285  ccc              print*,"value(",is,")=",value(is),  ccc              print*,"value(",is,")=",value(is),
286  ccc     $             " .gt.clseedcut(",is,")=",clseedcut(is)  ccc     $             " .gt.clseedcut(",is,")=",clseedcut(is)
# Line 260  c     possible SEED... Line 289  c     possible SEED...
289  c-----------------------------------------  c-----------------------------------------
290                 itemp=is                 itemp=is
291                 if(itemp.eq.last) goto 230 !estremo...                 if(itemp.eq.last) goto 230 !estremo...
292                 do while(value(itemp)  ****************************************************
293       $              /sigma(iv,nvk(itemp),nst(itemp))  *     modificato da Elena (08/2006) per salvare
294       $              .le.value(itemp+1)  *     il cluster intorno al massimo assoluto
295       $              /sigma(iv,nvk(itemp+1),nst(itemp+1))) !BIAS: aggiustare il caso uguale!???  ****************************************************
296    c$$$               do while(value(itemp)
297    c$$$     $              /sigma(iv,nvk(itemp),nst(itemp))
298    c$$$     $              .le.value(itemp+1)
299    c$$$     $              /sigma(iv,nvk(itemp+1),nst(itemp+1))) !BIAS: aggiustare il caso uguale!???
300    c$$$                  itemp=itemp+1
301    c$$$                  if(itemp.eq.last) goto 230 !stops if reaches last strip
302    c$$$               enddo            ! of the ladder
303                   do while(value(itemp).le.value(itemp+1))
304                    itemp=itemp+1                    itemp=itemp+1
305                    if(itemp.eq.last) goto 230 !stops if reaches last strip                    if(itemp.eq.last) goto 230 !stops if reaches last strip
306                 enddo            ! of the ladder                 enddo            ! of the ladder
# Line 473  c     goto 250 !inutile!??? Line 510  c     goto 250 !inutile!???
510  c--------------------------------------------------------  c--------------------------------------------------------
511  c     fills cluster variables  c     fills cluster variables
512  c--------------------------------------------------------  c--------------------------------------------------------
513                 nclstr1=nclstr1+1 !cluster number  c$$$               nclstr1=nclstr1+1 !cluster number
514  ccc               print*,nclstr1,multtemp  c$$$ccc               print*,nclstr1,multtemp
515                 if(nclstr1.gt.nclstrmax) then !too many clusters for the event:  c$$$               if(nclstr1.gt.nclstrmax) then !too many clusters for the event:
516                    if(verbose)print*,'Event ',eventn(1),  c$$$                  if(verbose)print*,'Event ',eventn(1),
517       $                 ': more than ',nclstrmax,' clusters'  c$$$     $                 ': more than ',nclstrmax,' clusters'
518                    good1=0       ! event  c$$$                  good1=0       ! event
519                    nclstr1=0  c$$$                  nclstr1=0
520                    totCLlength=0  c$$$                  totCLlength=0
521    c$$$                  flag_shower = .true.
522    c$$$                  goto 2000
523    c$$$               endif
524    c$$$               view(nclstr1)   = iv !vista del cluster
525    c$$$               ladder(nclstr1) = nld(iseed,iv) !ladder a cui appartiene il cluster seed
526    c$$$               maxs(nclstr1)   = iseed !strip del cluster seed
527    c$$$               mult(nclstr1)   = multtemp !molteplicita'
528    c$$$              
529    c$$$               indstart(nclstr1) = ind !posizione dell'inizio del cluster nell'
530    c$$$c                                      ! array clsignal
531    c$$$               indmax(nclstr1)   = indstart(nclstr1)+(iseed-lmax) !posizione del
532    c$$$c                                      ! cluster seed nell'array clsignal
533    c$$$              
534    c$$$               CLlength      = rmax-lmax+1 !numero di strip del cluster
535    c$$$               totCLlength   = totCLlength+CLlength
536    c$$$               dedx(nclstr1) = 0
537    c$$$               do j=lmax,rmax   !stores sequentially cluter strip values in
538    c$$$                  clsignal(ind) = value(j) ! clsignal array
539    c$$$                  ind=ind+1
540    c$$$c                  if(value(j).gt.0)
541    c$$$                  if(value(j).gt.clinclcut(j))
542    c$$$     $                 dedx(nclstr1) = dedx(nclstr1) + value(j) !cluster charge
543    c$$$               enddo
544    ccc
545    ccc            *** Modified by Elena (08/2006) ***
546    ccc
547                   nclstr_view = nclstr_view + 1 !cluster number
548    c               print*,'view ',iv,' -- search_cluster -- nclstr_view: '
549    c     $              ,nclstr_view
550                   if(nclstr_view.gt.nclstrmax_view) then !too many clusters for the view:
551                      if(verbose) print*,'Event ',eventn(1),
552         $                 ': more than ',nclstrmax_view
553         $                 ,' clusters on view ',iv
554    c                  good1=0       ! event
555    c                  nclstr1=0
556    c                  totCLlength=0
557                    flag_shower = .true.                    flag_shower = .true.
558                    goto 2000                    goto 2000
559                 endif                 endif
560                 view(nclstr1)=iv !vista del cluster  
561                 ladder(nclstr1)=nld(iseed,iv) !ladder a cui appartiene il cluster seed  c               view(nclstr1)   = iv !vista del cluster
562                 maxs(nclstr1)=iseed !strip del cluster seed                 ladder_view(nclstr_view) = nld(iseed,iv) !ladder a cui appartiene il cluster seed
563                 mult(nclstr1)=multtemp !molteplicita'                 maxs_view(nclstr_view)   = iseed !strip del cluster seed
564                                 mult_view(nclstr_view)   = multtemp !molteplicita'
565                 indstart(nclstr1)=ind !posizione dell'inizio del cluster nell'                 rmax_view(nclstr_view)   = rmax
566                                  ! array clsignal                 lmax_view(nclstr_view)   = lmax
567                 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  
568  c--------------------------------------------------------  c--------------------------------------------------------
569  c  c
570  c--------------------------------------------------------  c--------------------------------------------------------
# Line 525  c--------------------------------------- Line 586  c---------------------------------------
586  *  *
587  *---***---***---***---***---***---***---***---***  *---***---***---***---***---***---***---***---***
588    
589          subroutine save_cluster(iv)
590    *
591    *     (080/2006 Elena Vannuccini)
592    *     Save the clusters view by view
593    
594          include 'commontracker.f'
595          include 'level1.f'
596          include 'calib.f'
597          include 'common_reduction.f'
598    
599          integer CLlength          !lunghezza in strip del cluster
600    
601          do ic=1,nclstr_view
602    
603             nclstr1 = nclstr1+1
604             view(nclstr1)   = iv
605             ladder(nclstr1) = ladder_view(ic)
606             maxs(nclstr1)   = maxs_view(ic)
607             mult(nclstr1)   = mult_view(ic)
608                  
609    c        posizione dell'inizio del cluster nell' array clsignal
610             indstart(nclstr1) = ind
611    c        posizione del cluster seed nell'array clsignal
612             indmax(nclstr1)   = indstart(nclstr1)
613         $        +( maxs_view(ic) - lmax_view(ic) )
614            
615             CLlength      = rmax_view(ic) - lmax_view(ic) + 1 !numero di strip salvate
616             totCLlength   = totCLlength + CLlength
617             dedx(nclstr1) = 0
618             do j=lmax_view(ic),rmax_view(ic)         !stores sequentially cluter strip values in
619    
620                clsignal(ind) = value(j) ! clsignal array
621    
622                ivk=nvk(j)
623                ist=nst(j)
624    
625                clsigma(ind) = sigma(iv,ivk,ist)
626                cladc(ind)   = adc(iv,ivk,ist)
627                clbad(ind)   = bad(iv,ivk,ist)
628    c            clped(ind)   = pedestal(iv,ivk,ist)
629    
630                ind=ind+1
631    c     if(value(j).gt.0)
632                if(value(j).gt.clinclcut(j))
633         $           dedx(nclstr1) = dedx(nclstr1) + value(j) !cluster charge
634             enddo
635    
636    c         print*,'view ',iv,' -- save_cluster -- nclstr1: '
637    c     $        ,nclstr1,maxs(nclstr1),mult(nclstr1),dedx(nclstr1)
638            
639          enddo
640          
641          return
642          end
643    *---***---***---***---***---***---***---***---***
644    *
645    *
646    *
647    *
648    *
649    *---***---***---***---***---***---***---***---***
650    
651    
652        subroutine stripmask        subroutine stripmask
653    
# Line 535  c--------------------------------------- Line 658  c---------------------------------------
658  *     mask_vk(nviews,nva1_view)          !VA1 mask  *     mask_vk(nviews,nva1_view)          !VA1 mask
659  *  *
660        include 'commontracker.f'        include 'commontracker.f'
661  c      include 'level1.f'        include 'level1.f'
662        include 'common_reduction.f'        include 'common_reduction.f'
663        include 'calib.f'        include 'calib.f'
664    

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.23