/[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.3 by pam-fi, Fri Aug 4 08:18:06 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 'common_reduction.f'        include 'common_reduction.f'
14        include 'calib.f'        include 'calib.f'
15    
16        integer errflag           !error flag to mark no signal free VA1        integer errflag           !error flag to mark no signal free VA1
   
17        integer clstr_old(nstrips_va1) !flag storage vector        integer clstr_old(nstrips_va1) !flag storage vector
   
18        real signal(nstrips_va1)  !"signal" (=adc-ped) value storage vector        real signal(nstrips_va1)  !"signal" (=adc-ped) value storage vector
   
19        real smean, ssigma        !"signal" mean and sigma        real smean, ssigma        !"signal" mean and sigma
20        real cut                  !"strange" strip exclusion cut        real cut                  !"strange" strip exclusion cut
   
21        integer newclstr          !flag to warn about new found clusters to be        integer newclstr          !flag to warn about new found clusters to be
22                                  ! excluded from common noise computation  c                               ! excluded from common noise computation
   
   
 c     call HBOOK1(20000+100*i+j,' ',30,0.,30.,0.) !???  
23    
24  c------------------------------------------------------------------------  c------------------------------------------------------------------------
25  c      c
26  c     variables initialization  c     variables initialization
27  c      c
28  c------------------------------------------------------------------------  c------------------------------------------------------------------------
29        do k=1,nstrips_va1        !loops on strips        do k=1,nstrips_va1        !loops on strips
30           clstr(i,j,k)=1         !initializes signal affected strips flag           clstr(i,j,k)=1         !initializes signal affected strips flag
# Line 40  c--------------------------------------- Line 33  c---------------------------------------
33        enddo                     ! affected strips flag        enddo                     ! affected strips flag
34    
35        newclstr=1                !flag to warn about new found signal        newclstr=1                !flag to warn about new found signal
36                                  ! affected strips  c                               ! affected strips
   
   
   
37  c------------------------------------------------------------------------  c------------------------------------------------------------------------
38  c      c
39  c     high or low signal affected strips exclusion: computes "signal" (=adc-ped)  c     high or low signal affected strips exclusion: computes "signal" (=adc-ped)
40  c     mean value and sigma, and cuts from common noise computation strips  c     mean value and sigma, and cuts from common noise computation strips
41  c     whose ABS(signal) exceeds scut*sigma  c     whose ABS(signal) exceeds scut*sigma
42  c      c
43  c------------------------------------------------------------------------  c------------------------------------------------------------------------
44        countme=0                 !???        countme=0                 !???
45   666  continue                  !???   666  continue                  !???
# Line 59  c--------------------------------------- Line 49  c---------------------------------------
49        nstr=0        nstr=0
50                
51        do k=1,nstrips_va1        do k=1,nstrips_va1
52           nstr=nstr+strange(i,j,k) !uses only           nstr = nstr + strange(i,j,k) !uses only
53           if(mod(i,2).eq.1) then !odd strip ---> Y view           if(mod(i,2).eq.1) then !odd strip ---> Y view
54              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
55           else                   !even strip ---> X view           else                   !even strip ---> X view
56              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
57           endif           endif
58                     smean = smean + signal(k)*strange(i,j,k)
59           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.) !???  
60        enddo        enddo
61                
62        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 65  c     call HFILL(10000+100*i+j,signal(k)
65                
66        cut=scut*ssigma           !exclusion cut        cut=scut*ssigma           !exclusion cut
67                
68          nco=0
69          nbo=0
70        do k=1,nstrips_va1        do k=1,nstrips_va1
 c     call HFILL(20000+100*i+j,ABS(signal(k)-smean)/ssigma,0.,1.) !???  
71           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) !???  
72              strange(i,j,k)=0    !marks strips exceeding cut              strange(i,j,k)=0    !marks strips exceeding cut
73    c            print*,i,j,k,signal(k),smean
74           endif           endif
75             nco=nco+strange(i,j,k)
76             nbo=nbo+bad(i,j,k)
77        enddo                     ! in order not to use them in CN computation        enddo                     ! in order not to use them in CN computation
78    
79    c$$$      if(i.eq.12.and.(j.eq.2.or.j.eq.3))then
80    c$$$         print*,'view ',i,' vk ',j
81    c$$$         print*,'ADC (1-51-128) = ',adc(i,j,1),adc(i,j,52),adc(i,j,128)
82    c$$$         print*,'<ADC-PED> = ',smean
83    c$$$         print*,'s         = ',ssigma
84    c$$$         print*,'nstrange  = ',128-nco
85    c$$$         print*,'nbad      = ',128-nbo
86    c$$$      endif
87    
88        countme=countme+1         !???        countme = countme + 1         !???
89        if (countme.le.3) goto 666 !???        if (countme.le.3) goto 666 !???
90    
   
91  c------------------------------------------------------------------------  c------------------------------------------------------------------------
92  c      c    
93  c     common noise computation  c     common noise computation
94  c      c    
95  c------------------------------------------------------------------------  c-----------------------------------------------------------------------
96        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
97                                  ! affected strips are found        do while(newclstr.eq.1)  
98    
99           newclstr=0             !to exit from loop if no new cluster is           newclstr=0             !to exit from loop if no new cluster is found
                                 ! found  
100                    
101           errflag=0           errflag=0
102             call cnoise(i,j,errflag) !(view, VA1, error flag) computes cn
103           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)         !???  
104                    
105           if(errflag.eq.1) goto 10 !goes to next VA1: this one has no signal           call cutcn(i,j)        !(view, VA1) excludes clusters from cn computation
                                 ! free strips...  
           
          call cutcn(i,j)        !(view, VA1) excludes clusters from  
                                 ! common noise calculation  
106                    
107           ncs=0                  !initializes number of strips not excluded by cncut           ncs=0                  !initializes number of strips not excluded by cncut
   
108           do k=1,nstrips_va1     !loops on strips           do k=1,nstrips_va1     !loops on strips
109              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
110                                  ! new found clusters, and if so sets              if(clstr(i,j,k).ne.clstr_old(k)) then
111                 newclstr=1       ! newclstr flag = 1                 newclstr=1                      
112                                 clstr_old(k)=clstr(i,j,k)  
113                 clstr_old(k)=clstr(i,j,k) !stores cluster flags in              endif              
             endif               ! clstr_old variable  
   
114              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)
   
115              ncs=ncs+iok         !counts number of good strips for cn computation              ncs=ncs+iok         !counts number of good strips for cn computation
   
116           enddo           enddo
117    
118        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  
119    
120   10   continue   10   continue
121    
# Line 182  c$$$      endif Line 154  c$$$      endif
154                
155        ncn=0                     !number of strips in cn computation        ncn=0                     !number of strips in cn computation
156        cn(i,j)=0                 !initializes cn variable        cn(i,j)=0                 !initializes cn variable
157          cnflag(i,j)=0            !initialize cn flag OK
158    
159        do k=1,nstrips_va1        !loops on strips        do k=1,nstrips_va1        !loops on strips
160           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
161                                  ! or signal affected strips           iok = strange(i,j,k)*bad(i,j,k)*clstr(i,j,k)
162  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  
163           ncn = ncn + iok            !counts number of strips in cn computation           ncn = ncn + iok            !counts number of strips in cn computation
164        enddo        enddo
165          
166  ccc      print*,'ncn= ',ncn        if(ncn.lt.NSTRIPMIN) then         !no signal free strips on this VA1...
167        if(ncn.eq.0) then         !no signal free strips on this VA1...           if(ncn.eq.0)then
168           print*,'cnoise: WARNING, NO SIGNAL FREE STRIPS ON VA1 ',j,              if(debug)print*,' WARNING - cnoise: ',
169       $        ', VIEW ',i       $        'no strips for CN computation on VA1 ',j,
170         $        ', VIEW ',i,'  >>> FAILED '
171             else
172                if(debug)print*,' WARNING - cnoise: ',
173         $        'less than ',NSTRIPMIN
174         $           ,' strips for CN computation on VA1 ',j,
175         $        ', VIEW ',i,'  >>> FAILED '
176             endif
177           gulp=1           gulp=1
178             cnflag(i,j) = -1
179        else        else
180           cn(i,j)=cn(i,j)/DBLE(ncn) !computes common noise           cn(i,j)=cn(i,j)/DBLE(ncn) !<<<< computes common noise
181           gulp=0                 !resets error flag           if(ncn.lt.NSTRIPWARNING) then
182                if(debug)print*,' WARNING - cnoise: ',
183         $        'less than ',NSTRIPWARNING
184         $           ,' strips for CN computation on VA1 ',j,
185         $        ', VIEW ',i            
186                cnflag(i,j) = 1
187             endif
188             gulp=0                
189        endif        endif
190    
191        return        return

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

  ViewVC Help
Powered by ViewVC 1.1.23