/[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.9 by pam-fi, Fri Aug 31 14:56:52 2007 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 39  c--------------------------------------- Line 33  c---------------------------------------
33           strange(i,j,k)=1       !initializes unusually high or low signal           strange(i,j,k)=1       !initializes unusually high or low signal
34        enddo                     ! affected strips flag        enddo                     ! affected strips flag
35    
36        newclstr=1                !flag to warn about new found signal  c------------------------------------------------------------------------
37                                  ! affected strips  c     (september 2007)
38    c     remove from CN computation the first and the last 3 channels of
39    c     each X view, becouse they ar not connected to any strip
40    c------------------------------------------------------------------------
41          if(mod(i,2).eq.0)then
42             if(j.eq.1)then
43                do k=1,3
44                   strange(i,j,k)=0
45                enddo
46             elseif(j.eq.nva1_ladder)then
47                do k=nstrips_va1,nstrips_va1-2,-1
48                   strange(i,j,k)=0
49                enddo
50             endif
51          endif
52    
53          newclstr=1                !flag to warn about new found signal
54    c                               ! affected strips
55  c------------------------------------------------------------------------  c------------------------------------------------------------------------
56  c      c
57  c     high or low signal affected strips exclusion: computes "signal" (=adc-ped)  c     high or low signal affected strips exclusion: computes "signal" (=adc-ped)
58  c     mean value and sigma, and cuts from common noise computation strips  c     mean value and sigma, and cuts from common noise computation strips
59  c     whose ABS(signal) exceeds scut*sigma  c     whose ABS(signal) exceeds scut*sigma
60  c      c
61  c------------------------------------------------------------------------  c------------------------------------------------------------------------
62        countme=0                 !???        countme=0                 !???
63   666  continue                  !???   666  continue                  !???
# Line 59  c--------------------------------------- Line 67  c---------------------------------------
67        nstr=0        nstr=0
68                
69        do k=1,nstrips_va1        do k=1,nstrips_va1
70           nstr=nstr+strange(i,j,k) !uses only           nstr = nstr + strange(i,j,k) !uses only
71           if(mod(i,2).eq.1) then !odd strip ---> Y view           if(mod(i,2).eq.1) then ! ---> Y view
72              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
73           else                   !even strip ---> X view           else                   ! ---> X view
74              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
75           endif           endif
76                     smean = smean + signal(k)*strange(i,j,k)
77           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.) !???  
78        enddo        enddo
79                
80        smean=smean/nstr          !strips value distribution mean        smean=smean/nstr          !strips value distribution mean      
         
81        ssigma=SQRT((ssigma/nstr)-smean**2) !strips value distribution sigma        ssigma=SQRT((ssigma/nstr)-smean**2) !strips value distribution sigma
82                
83        cut=scut*ssigma           !exclusion cut        cut=scut*ssigma           !exclusion cut
84                
85          nco=0
86          nbo=0
87        do k=1,nstrips_va1        do k=1,nstrips_va1
 c     call HFILL(20000+100*i+j,ABS(signal(k)-smean)/ssigma,0.,1.) !???  
88           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) !???  
89              strange(i,j,k)=0    !marks strips exceeding cut              strange(i,j,k)=0    !marks strips exceeding cut
90    c            print*,i,j,k,signal(k),smean
91           endif           endif
92             nco=nco+strange(i,j,k)
93             nbo=nbo+bad(i,j,k)
94        enddo                     ! in order not to use them in CN computation        enddo                     ! in order not to use them in CN computation
95    
96    c$$$      if(i.eq.12.and.(j.eq.2.or.j.eq.3))then
97    c$$$         print*,'view ',i,' vk ',j
98    c$$$         print*,'ADC (1-51-128) = ',adc(i,j,1),adc(i,j,52),adc(i,j,128)
99    c$$$         print*,'<ADC-PED> = ',smean
100    c$$$         print*,'s         = ',ssigma
101    c$$$         print*,'nstrange  = ',128-nco
102    c$$$         print*,'nbad      = ',128-nbo
103    c$$$      endif
104    
105        countme=countme+1         !???        countme = countme + 1         !???
106        if (countme.le.3) goto 666 !???        if (countme.le.3) goto 666 !???
107    
   
108  c------------------------------------------------------------------------  c------------------------------------------------------------------------
109  c      c    
110  c     common noise computation  c     common noise computation
111  c      c    
112  c------------------------------------------------------------------------  c-----------------------------------------------------------------------
113        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
114                                  ! affected strips are found        do while(newclstr.eq.1)  
115    
116           newclstr=0             !to exit from loop if no new cluster is           newclstr=0             !to exit from loop if no new cluster is found
                                 ! found  
117                    
118           errflag=0           errflag=0
119             call cnoise(i,j,errflag) !(view, VA1, error flag) computes cn
120           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...  
121                    
122           call cutcn(i,j)        !(view, VA1) excludes clusters from           call cutcn(i,j)        !(view, VA1) excludes clusters from cn computation
                                 ! common noise calculation  
123                    
124           ncs=0                  !initializes number of strips not excluded by cncut           ncs=0                  !initializes number of strips not excluded by cncut
   
125           do k=1,nstrips_va1     !loops on strips           do k=1,nstrips_va1     !loops on strips
126              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
127                                  ! new found clusters, and if so sets              if(clstr(i,j,k).ne.clstr_old(k)) then
128                 newclstr=1       ! newclstr flag = 1                 newclstr=1                      
129                                 clstr_old(k)=clstr(i,j,k)  
130                 clstr_old(k)=clstr(i,j,k) !stores cluster flags in              endif              
             endif               ! clstr_old variable  
   
131              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)
   
132              ncs=ncs+iok         !counts number of good strips for cn computation              ncs=ncs+iok         !counts number of good strips for cn computation
   
133           enddo           enddo
134    
135        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  
136    
137   10   continue   10   continue
138    
# Line 174  c$$$      endif Line 163  c$$$      endif
163        subroutine cnoise(i,j,gulp) !(view, VA1)        subroutine cnoise(i,j,gulp) !(view, VA1)
164    
165        include 'commontracker.f'        include 'commontracker.f'
166          include 'level0.f'
167          include 'level1.f'
168        include 'common_reduction.f'        include 'common_reduction.f'
169        include 'calib.f'        include 'calib.f'
170                
# Line 182  c$$$      endif Line 173  c$$$      endif
173                
174        ncn=0                     !number of strips in cn computation        ncn=0                     !number of strips in cn computation
175        cn(i,j)=0                 !initializes cn variable        cn(i,j)=0                 !initializes cn variable
176          cnrms(i,j)=0              !initializes cn rms
177          cnn(i,j)=0                !initialize cn flag
178    
179        do k=1,nstrips_va1        !loops on strips        do k=1,nstrips_va1        !loops on strips
180           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
181                                  ! or signal affected strips           iok = strange(i,j,k)*bad(i,j,k)*clstr(i,j,k)
182  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
183             cnrms(i,j) = cnrms(i,j)
184           cn(i,j)=cn(i,j) + (DBLE(adc(i,j,k)) - pedestal(i,j,k))*iok !sums ADC-PED       $        + (DBLE(adc(i,j,k)) - pedestal(i,j,k))
185                                  ! values to compute common noise       $        *(DBLE(adc(i,j,k)) - pedestal(i,j,k))*iok
186           ncn = ncn + iok            !counts number of strips in cn computation           ncn = ncn + iok            !counts number of strips in cn computation
187        enddo        enddo
188          
189  ccc      print*,'ncn= ',ncn        if(ncn.lt.NSTRIPMIN) then         !no signal free strips on this VA1...
190        if(ncn.eq.0) then         !no signal free strips on this VA1...           if(ncn.eq.0)then
191           print*,'cnoise: WARNING, NO SIGNAL FREE STRIPS ON VA1 ',j,              if(debug.eq.1)print*,' WARNING - cnoise: ',
192       $        ', VIEW ',i       $        'no strips for CN computation on VA1 ',j,
193         $        ', VIEW ',i,'  >>> FAILED '
194             else
195                if(debug.eq.1)print*,' WARNING - cnoise: ',
196         $        'less than ',NSTRIPMIN
197         $           ,' strips for CN computation on VA1 ',j,
198         $        ', VIEW ',i,'  >>> FAILED '
199             endif
200           gulp=1           gulp=1
201             cnn(i,j) = 0
202        else        else
203           cn(i,j)=cn(i,j)/DBLE(ncn) !computes common noise           cn(i,j)=cn(i,j)/DBLE(ncn) !<<<< computes common noise
204           gulp=0                 !resets error flag           cnrms(i,j)= SQRT( cnrms(i,j)/DBLE(ncn) - cn(i,j)**2 )
205             cnn(i,j) = ncn
206             gulp=0                
207    c$$$         print*,'Event ',eventn(1)
208    c$$$     $        ,': cn(',i,',',j,')= ',cn(i,j),' ncn ',ncn
209            
210             if(debug.eq.1.and.ABS(cn(i,j)).gt.1000)
211         $        print*,'Event ',eventn(1)
212         $        ,': cn(',i,',',j,')= ',cn(i,j),' ncn ',ncn
213        endif        endif
214    
215        return        return
# Line 227  ccc      print*,'ncn= ',ncn Line 236  ccc      print*,'ncn= ',ncn
236        subroutine cutcn(i,j)     !(view, VA1)        subroutine cutcn(i,j)     !(view, VA1)
237    
238        include 'commontracker.f'        include 'commontracker.f'
239          include 'level1.f'
240        include 'common_reduction.f'        include 'common_reduction.f'
241        include 'calib.f'        include 'calib.f'
242    

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

  ViewVC Help
Powered by ViewVC 1.1.23