/[PAMELA software]/DarthVader/TrackerLevel2/src/F77/cncomp.f
ViewVC logotype

Diff of /DarthVader/TrackerLevel2/src/F77/cncomp.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1.1 by mocchiut, Fri May 19 13:15:55 2006 UTC revision 1.5 by pam-fi, Fri Sep 29 08:13:04 2006 UTC
# Line 7  Line 7 
7  *            *          
8  *************************************************************************  *************************************************************************
9    
10        subroutine cncomp(i,j)    !(view, VA1)        subroutine cncomp(i,j,errflag)    !(view, VA1)
11    
12        include 'commontracker.f'        include 'commontracker.f'
13          include 'level1.f'
14        include 'common_reduction.f'        include 'common_reduction.f'
15        include 'calib.f'        include 'calib.f'
16    
17        integer errflag           !error flag to mark no signal free VA1        integer errflag           !error flag to mark no signal free VA1
   
18        integer clstr_old(nstrips_va1) !flag storage vector        integer clstr_old(nstrips_va1) !flag storage vector
   
19        real signal(nstrips_va1)  !"signal" (=adc-ped) value storage vector        real signal(nstrips_va1)  !"signal" (=adc-ped) value storage vector
   
20        real smean, ssigma        !"signal" mean and sigma        real smean, ssigma        !"signal" mean and sigma
21        real cut                  !"strange" strip exclusion cut        real cut                  !"strange" strip exclusion cut
   
22        integer newclstr          !flag to warn about new found clusters to be        integer newclstr          !flag to warn about new found clusters to be
23                                  ! excluded from common noise computation  c                               ! excluded from common noise computation
   
   
 c     call HBOOK1(20000+100*i+j,' ',30,0.,30.,0.) !???  
24    
25  c------------------------------------------------------------------------  c------------------------------------------------------------------------
26  c      c
27  c     variables initialization  c     variables initialization
28  c      c
29  c------------------------------------------------------------------------  c------------------------------------------------------------------------
30        do k=1,nstrips_va1        !loops on strips        do k=1,nstrips_va1        !loops on strips
31           clstr(i,j,k)=1         !initializes signal affected strips flag           clstr(i,j,k)=1         !initializes signal affected strips flag
# Line 40  c--------------------------------------- Line 34  c---------------------------------------
34        enddo                     ! affected strips flag        enddo                     ! affected strips flag
35    
36        newclstr=1                !flag to warn about new found signal        newclstr=1                !flag to warn about new found signal
37                                  ! affected strips  c                               ! affected strips
   
   
   
38  c------------------------------------------------------------------------  c------------------------------------------------------------------------
39  c      c
40  c     high or low signal affected strips exclusion: computes "signal" (=adc-ped)  c     high or low signal affected strips exclusion: computes "signal" (=adc-ped)
41  c     mean value and sigma, and cuts from common noise computation strips  c     mean value and sigma, and cuts from common noise computation strips
42  c     whose ABS(signal) exceeds scut*sigma  c     whose ABS(signal) exceeds scut*sigma
43  c      c
44  c------------------------------------------------------------------------  c------------------------------------------------------------------------
45        countme=0                 !???        countme=0                 !???
46   666  continue                  !???   666  continue                  !???
# Line 59  c--------------------------------------- Line 50  c---------------------------------------
50        nstr=0        nstr=0
51                
52        do k=1,nstrips_va1        do k=1,nstrips_va1
53           nstr=nstr+strange(i,j,k) !uses only           nstr = nstr + strange(i,j,k) !uses only
54           if(mod(i,2).eq.1) then !odd strip ---> Y view           if(mod(i,2).eq.1) then !odd strip ---> Y view
55              signal(k)= - (DBLE(adc(i,j,k))-pedestal(i,j,k)) !negative signal              signal(k) = - (DBLE(adc(i,j,k)) - pedestal(i,j,k)) !negative signal
56           else                   !even strip ---> X view           else                   !even strip ---> X view
57              signal(k)= DBLE(adc(i,j,k))-pedestal(i,j,k) !positive signal              signal(k) =    DBLE(adc(i,j,k)) - pedestal(i,j,k) !positive signal
58           endif           endif
59                     smean = smean + signal(k)*strange(i,j,k)
60           smean=smean+signal(k)*strange(i,j,k)           ssigma = ssigma + (signal(k)**2)*strange(i,j,k)
          ssigma=ssigma+(signal(k)**2)*strange(i,j,k)  
           
 c     call HFILL(10000+100*i+j,signal(k),0.,1.) !???  
61        enddo        enddo
62                
63        smean=smean/nstr          !strips value distribution mean        smean=smean/nstr          !strips value distribution mean
# Line 78  c     call HFILL(10000+100*i+j,signal(k) Line 66  c     call HFILL(10000+100*i+j,signal(k)
66                
67        cut=scut*ssigma           !exclusion cut        cut=scut*ssigma           !exclusion cut
68                
69          nco=0
70          nbo=0
71        do k=1,nstrips_va1        do k=1,nstrips_va1
 c     call HFILL(20000+100*i+j,ABS(signal(k)-smean)/ssigma,0.,1.) !???  
72           if(ABS(signal(k)-smean).gt.cut) then           if(ABS(signal(k)-smean).gt.cut) then
 c     print*,i,j,k,signal(k),abs(signal(k)),cut,strange(i,j,k) !???  
73              strange(i,j,k)=0    !marks strips exceeding cut              strange(i,j,k)=0    !marks strips exceeding cut
74    c            print*,i,j,k,signal(k),smean
75           endif           endif
76             nco=nco+strange(i,j,k)
77             nbo=nbo+bad(i,j,k)
78        enddo                     ! in order not to use them in CN computation        enddo                     ! in order not to use them in CN computation
79    
80    c$$$      if(i.eq.12.and.(j.eq.2.or.j.eq.3))then
81    c$$$         print*,'view ',i,' vk ',j
82    c$$$         print*,'ADC (1-51-128) = ',adc(i,j,1),adc(i,j,52),adc(i,j,128)
83    c$$$         print*,'<ADC-PED> = ',smean
84    c$$$         print*,'s         = ',ssigma
85    c$$$         print*,'nstrange  = ',128-nco
86    c$$$         print*,'nbad      = ',128-nbo
87    c$$$      endif
88    
89        countme=countme+1         !???        countme = countme + 1         !???
90        if (countme.le.3) goto 666 !???        if (countme.le.3) goto 666 !???
91    
   
92  c------------------------------------------------------------------------  c------------------------------------------------------------------------
93  c      c    
94  c     common noise computation  c     common noise computation
95  c      c    
96  c------------------------------------------------------------------------  c-----------------------------------------------------------------------
97        do while(newclstr.eq.1)   !loops on this VA1 till no new signal  *     loops on this VA1 till no new signal affected strips are found
98                                  ! affected strips are found        do while(newclstr.eq.1)  
99    
100           newclstr=0             !to exit from loop if no new cluster is           newclstr=0             !to exit from loop if no new cluster is found
                                 ! found  
101                    
102           errflag=0           errflag=0
103             call cnoise(i,j,errflag) !(view, VA1, error flag) computes cn
104           call cnoise(i,j,errflag) !(view, VA1, error flag) computes common           if(errflag.eq.1) goto 10 !goes to next VA1: this one has no signal-free strips...
                                 ! noise  
   
 c     print*,cn(i,j)         !???  
           
          if(errflag.eq.1) goto 10 !goes to next VA1: this one has no signal  
                                 ! free strips...  
105                    
106           call cutcn(i,j)        !(view, VA1) excludes clusters from           call cutcn(i,j)        !(view, VA1) excludes clusters from cn computation
                                 ! common noise calculation  
107                    
108           ncs=0                  !initializes number of strips not excluded by cncut           ncs=0                  !initializes number of strips not excluded by cncut
   
109           do k=1,nstrips_va1     !loops on strips           do k=1,nstrips_va1     !loops on strips
110              if(clstr(i,j,k).ne.clstr_old(k)) then !checks if there are  *           checks if there are new found clusters, and if so sets
111                                  ! new found clusters, and if so sets              if(clstr(i,j,k).ne.clstr_old(k)) then
112                 newclstr=1       ! newclstr flag = 1                 newclstr=1                      
113                                 clstr_old(k)=clstr(i,j,k)  
114                 clstr_old(k)=clstr(i,j,k) !stores cluster flags in              endif              
             endif               ! clstr_old variable  
   
115              iok=strange(i,j,k)*bad(i,j,k)*clstr(i,j,k)              iok=strange(i,j,k)*bad(i,j,k)*clstr(i,j,k)
   
116              ncs=ncs+iok         !counts number of good strips for cn computation              ncs=ncs+iok         !counts number of good strips for cn computation
   
117           enddo           enddo
118    
119        enddo                     !ends do while loop when there are no new        enddo                     !ends do while
                                 ! clusters  
   
 c      call HFILL(666,FLOAT(ncs),0.,1.) !???  
   
   
 c$$$      if(ncs.lt.20) then        !warns if too many strips have been excluded from CN  
 c$$$                                ! computation  
 c$$$         print*,'cncomp: WARNING, LESS THAN 20 STRIPS PASSED CN CUT'  
 c$$$     $        //' ON VA1 ',j,', VIEW ',i !NB questo errore e' "un po'" in conflitto  
 c$$$                                ! con quello che setta errflag (vedi cnoise.f)...  
 c$$$  
 c$$$      endif  
120    
121   10   continue   10   continue
122    
# Line 174  c$$$      endif Line 147  c$$$      endif
147        subroutine cnoise(i,j,gulp) !(view, VA1)        subroutine cnoise(i,j,gulp) !(view, VA1)
148    
149        include 'commontracker.f'        include 'commontracker.f'
150          include 'level0.f'
151          include 'level1.f'
152        include 'common_reduction.f'        include 'common_reduction.f'
153        include 'calib.f'        include 'calib.f'
154                
# Line 182  c$$$      endif Line 157  c$$$      endif
157                
158        ncn=0                     !number of strips in cn computation        ncn=0                     !number of strips in cn computation
159        cn(i,j)=0                 !initializes cn variable        cn(i,j)=0                 !initializes cn variable
160          cnn(i,j)=0                !initialize cn flag
161    
162        do k=1,nstrips_va1        !loops on strips        do k=1,nstrips_va1        !loops on strips
163           iok=strange(i,j,k)*bad(i,j,k)*clstr(i,j,k) !flag to mark strange, bad  *        tags strange, bad or signal-affected strips
164                                  ! or signal affected strips           iok = strange(i,j,k)*bad(i,j,k)*clstr(i,j,k)
165  ccc         print*,i,j,k,strange(i,j,k),bad(i,j,k),clstr(i,j,k),iok !???           cn(i,j) = cn(i,j) + (DBLE(adc(i,j,k)) - pedestal(i,j,k))*iok
   
          cn(i,j)=cn(i,j) + (DBLE(adc(i,j,k)) - pedestal(i,j,k))*iok !sums ADC-PED  
                                 ! values to compute common noise  
166           ncn = ncn + iok            !counts number of strips in cn computation           ncn = ncn + iok            !counts number of strips in cn computation
167        enddo        enddo
168          
169  ccc      print*,'ncn= ',ncn        if(ncn.lt.NSTRIPMIN) then         !no signal free strips on this VA1...
170        if(ncn.eq.0) then         !no signal free strips on this VA1...           if(ncn.eq.0)then
171           print*,'cnoise: WARNING, NO SIGNAL FREE STRIPS ON VA1 ',j,              if(debug)print*,' WARNING - cnoise: ',
172       $        ', VIEW ',i       $        'no strips for CN computation on VA1 ',j,
173         $        ', VIEW ',i,'  >>> FAILED '
174             else
175                if(debug)print*,' WARNING - cnoise: ',
176         $        'less than ',NSTRIPMIN
177         $           ,' strips for CN computation on VA1 ',j,
178         $        ', VIEW ',i,'  >>> FAILED '
179             endif
180           gulp=1           gulp=1
181             cnn(i,j) = 0
182        else        else
183           cn(i,j)=cn(i,j)/DBLE(ncn) !computes common noise           cn(i,j)=cn(i,j)/DBLE(ncn) !<<<< computes common noise
184           gulp=0                 !resets error flag           cnn(i,j) = ncn
185             gulp=0                
186             if(debug.and.ABS(cn(i,j)).gt.1000)
187         $        print*,'Event ',eventn(1)
188         $        ,': cn(',i,',',j,')= ',cn(i,j),' ncn ',ncn
189        endif        endif
190    
191        return        return
# Line 227  ccc      print*,'ncn= ',ncn Line 212  ccc      print*,'ncn= ',ncn
212        subroutine cutcn(i,j)     !(view, VA1)        subroutine cutcn(i,j)     !(view, VA1)
213    
214        include 'commontracker.f'        include 'commontracker.f'
215          include 'level1.f'
216        include 'common_reduction.f'        include 'common_reduction.f'
217        include 'calib.f'        include 'calib.f'
218    

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

  ViewVC Help
Powered by ViewVC 1.1.23