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

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

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

revision 1.7 by pam-fi, Wed Oct 11 06:53:02 2006 UTC revision 1.30 by pam-fi, Tue Aug 28 13:25:50 2007 UTC
# Line 12  Line 12 
12        subroutine track_finding(iflag)        subroutine track_finding(iflag)
13    
14        include 'commontracker.f'        include 'commontracker.f'
15          include 'level1.f'
16        include 'common_momanhough.f'        include 'common_momanhough.f'
17        include 'common_mech.f'        include 'common_mech.f'
18        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
19        include 'common_mini_2.f'        include 'common_mini_2.f'
20        include 'calib.f'        include 'calib.f'
       include 'level1.f'  
21        include 'level2.f'        include 'level2.f'
22    
       include 'momanhough_init.f'  
         
 c      logical DEBUG  
 c      common/dbg/DEBUG  
23    
24    
25    c      print*,'======================================================'
26    c$$$      do ic=1,NCLSTR1
27    c$$$         if(.false.
28    c$$$     $        .or.nsatstrips(ic).gt.0
29    c$$$c     $        .or.nbadstrips(0,ic).gt.0
30    c$$$c     $        .or.nbadstrips(4,ic).gt.0
31    c$$$c     $        .or.nbadstrips(3,ic).gt.0
32    c$$$     $        .or..false.)then
33    c$$$            print*,'--- cl-',ic,' ------------------------'
34    c$$$            istart = INDSTART(IC)
35    c$$$            istop  = TOTCLLENGTH
36    c$$$            if(ic.lt.NCLSTR1)istop=INDSTART(IC+1)-1
37    c$$$            print*,'ADC   ',(CLADC(i),i=istart,istop)
38    c$$$            print*,'s/n   ',(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)
39    c$$$            print*,'sgnl  ',(CLSIGNAL(i),i=istart,istop)
40    c$$$            print*,'strip ',(i-INDMAX(ic),i=istart,istop)
41    c$$$            print*,'view ',VIEW(ic)
42    c$$$            print*,'maxs ',MAXS(ic)
43    c$$$            print*,'COG4 ',cog(4,ic)
44    c$$$            ff = fbad_cog(4,ic)
45    c$$$            print*,'fbad ',ff
46    c$$$            print*,(CLBAD(i),i=istart,istop)
47    c$$$            bb=nbadstrips(0,ic)
48    c$$$            print*,'#BAD (tot)',bb
49    c$$$            bb=nbadstrips(4,ic)
50    c$$$            print*,'#BAD (4)',bb
51    c$$$            bb=nbadstrips(3,ic)
52    c$$$            print*,'#BAD (3)',bb
53    c$$$            ss=nsatstrips(ic)
54    c$$$            print*,'#saturated ',ss
55    c$$$         endif
56    c$$$      enddo
57          
58  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
59  *     STEP 1  *     STEP 1
60  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
# Line 44  c      common/dbg/DEBUG Line 74  c      common/dbg/DEBUG
74  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
75  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
76    
77  c      iflag=0  
78        call cl_to_couples(iflag)        call cl_to_couples(iflag)
79        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
80           goto 880               !fill ntp and go to next event                       goto 880               !go to next event
81        endif        endif
82                
 *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~  
 *     selezione di tracce pulite per diagnostica  
 *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~  
 c$$$         if(DEBUG)then  
 c$$$            do ip=1,nplanes  
 c$$$               if(ncp_plane(ip).ne.1)good2=.false.  
 c$$$            enddo  
 c$$$c            if(good2.eq.0)goto 100!next event  
 c$$$c            if(good2.eq.0)goto 880!fill ntp and go to next event  
 c$$$         endif  
           
   
   
83  *-----------------------------------------------------  *-----------------------------------------------------
84  *-----------------------------------------------------  *-----------------------------------------------------
85  *     HOUGH TRASFORM  *     HOUGH TRASFORM
# Line 91  c$$$         endif Line 108  c$$$         endif
108  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
109  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
110    
111  c      iflag=0  
112        call cp_to_doubtrip(iflag)        call cp_to_doubtrip(iflag)
113        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
114           goto 880               !fill ntp and go to next event                       goto 880               !go to next event            
115        endif        endif
116                
117                
# Line 123  c      iflag=0 Line 140  c      iflag=0
140  *     $     ,ptcloud_xz,tr_cloud,cpcloud_xz            *     $     ,ptcloud_xz,tr_cloud,cpcloud_xz          
141  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
142  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
143    *     count number of hit planes
144          planehit=0                
145          do np=1,nplanes          
146            if(ncp_plane(np).ne.0)then  
147              planehit=planehit+1  
148            endif                  
149          enddo                    
150          if(planehit.lt.3) goto 880 ! exit              
151          
152          nptxz_min=x_min_start              
153          nplxz_min=x_min_start              
154                
155          nptyz_min=y_min_start              
156          nplyz_min=y_min_start              
157    
158  c      iflag=0        cutdistyz=cutystart      
159          cutdistxz=cutxstart      
160    
161     878  continue
162        call doub_to_YZcloud(iflag)        call doub_to_YZcloud(iflag)
163        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
164           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
165        endif        endif
166  c      iflag=0        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then
167            if(cutdistyz.lt.maxcuty/2)then
168              cutdistyz=cutdistyz+cutystep
169            else
170              cutdistyz=cutdistyz+(3*cutystep)
171            endif
172            goto 878                
173          endif                    
174    
175          if(planehit.eq.3) goto 881          
176          
177     879  continue  
178        call trip_to_XZcloud(iflag)        call trip_to_XZcloud(iflag)
179        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
180           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
181        endif        endif
182                                    
183          if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then
184            cutdistxz=cutdistxz+cutxstep
185            goto 879                
186          endif                    
187    
188        
189     881  continue  
190    *     if there is at least three planes on the Y view decreases cuts on X view
191          if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.
192         $     nplxz_min.ne.y_min_start)then
193            nptxz_min=x_min_step    
194            nplxz_min=x_min_start-x_min_step              
195            goto 879                
196          endif                    
197            
198   880  return   880  return
199        end        end
200    
# Line 144  c      iflag=0 Line 204  c      iflag=0
204        subroutine track_fitting(iflag)        subroutine track_fitting(iflag)
205    
206        include 'commontracker.f'        include 'commontracker.f'
207          include 'level1.f'
208        include 'common_momanhough.f'        include 'common_momanhough.f'
209        include 'common_mech.f'        include 'common_mech.f'
210        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
211        include 'common_mini_2.f'        include 'common_mini_2.f'
212        include 'calib.f'        include 'calib.f'
       include 'level1.f'  
213        include 'level2.f'        include 'level2.f'
214    
215        include 'momanhough_init.f'  c      include 'momanhough_init.f'
216                
 c      logical DEBUG  
 c      common/dbg/DEBUG  
   
217        logical FIMAGE            !        logical FIMAGE            !
218          real trackimage(NTRACKSMAX)
219          real*8 AL_GUESS(5)
220    
221  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
222  *     STEP 4   (ITERATED until any other physical track isn't found)  *     STEP 4   (ITERATED until any other physical track isn't found)
# Line 198  c         iflag=0 Line 257  c         iflag=0
257           ibest=0                !best track among candidates           ibest=0                !best track among candidates
258           iimage=0               !track image           iimage=0               !track image
259  *     ------------- select the best track -------------  *     ------------- select the best track -------------
260           rchi2best=1000000000.  c$$$         rchi2best=1000000000.
261    c$$$         do i=1,ntracks
262    c$$$            if(RCHI2_STORE(i).lt.rchi2best.and.
263    c$$$     $         RCHI2_STORE(i).gt.0)then
264    c$$$               ibest=i
265    c$$$               rchi2best=RCHI2_STORE(i)
266    c$$$            endif
267    c$$$         enddo
268    c$$$         if(ibest.eq.0)goto 880 !>> no good candidates
269    
270    *     -------------------------------------------------------
271    *     order track-candidates according to:
272    *     1st) decreasing n.points
273    *     2nd) increasing chi**2
274    *     -------------------------------------------------------
275             rchi2best=1000000000.
276             ndofbest=0            
277           do i=1,ntracks           do i=1,ntracks
278              if(RCHI2_STORE(i).lt.rchi2best.and.             ndof=0              
279       $         RCHI2_STORE(i).gt.0)then             do ii=1,nplanes    
280                 ndof=ndof        
281         $            +int(xgood_store(ii,i))
282         $            +int(ygood_store(ii,i))
283               enddo              
284               if(ndof.gt.ndofbest)then
285                 ibest=i
286                 rchi2best=RCHI2_STORE(i)
287                 ndofbest=ndof    
288               elseif(ndof.eq.ndofbest)then
289                 if(RCHI2_STORE(i).lt.rchi2best.and.
290         $            RCHI2_STORE(i).gt.0)then
291                 ibest=i                 ibest=i
292                 rchi2best=RCHI2_STORE(i)                 rchi2best=RCHI2_STORE(i)
293              endif                 ndofbest=ndof  
294                 endif            
295               endif
296           enddo           enddo
297    
298    c$$$         rchi2best=1000000000.
299    c$$$         ndofbest=0             !(1)
300    c$$$         do i=1,ntracks
301    c$$$           if(RCHI2_STORE(i).lt.rchi2best.and.
302    c$$$     $          RCHI2_STORE(i).gt.0)then
303    c$$$             ndof=0             !(1)
304    c$$$             do ii=1,nplanes    !(1)
305    c$$$               ndof=ndof        !(1)
306    c$$$     $              +int(xgood_store(ii,i)) !(1)
307    c$$$     $              +int(ygood_store(ii,i)) !(1)
308    c$$$             enddo              !(1)
309    c$$$             if(ndof.ge.ndofbest)then !(1)
310    c$$$               ibest=i
311    c$$$               rchi2best=RCHI2_STORE(i)
312    c$$$               ndofbest=ndof    !(1)
313    c$$$             endif              !(1)
314    c$$$           endif
315    c$$$         enddo
316    
317           if(ibest.eq.0)goto 880 !>> no good candidates           if(ibest.eq.0)goto 880 !>> no good candidates
318  *-------------------------------------------------------------------------------      *-------------------------------------------------------------------------------    
319  *     The best track candidate (ibest) is selected and a new fitting is performed.  *     The best track candidate (ibest) is selected and a new fitting is performed.
# Line 224  c         iflag=0 Line 332  c         iflag=0
332              iimage=0              iimage=0
333           endif           endif
334           if(icand.eq.0)then           if(icand.eq.0)then
335              print*,'HAI FATTO UN CASINO!!!!!! icand = ',icand              if(VERBOSE.EQ.1)then
336       $           ,ibest,iimage                 print*,'HAI FATTO UN CASINO!!!!!! icand = ',icand
337         $              ,ibest,iimage
338                endif
339              return              return
340           endif           endif
341    
# Line 236  c         iflag=0 Line 346  c         iflag=0
346  *     **********************************************************  *     **********************************************************
347  *     ************************** FIT *** FIT *** FIT *** FIT ***  *     ************************** FIT *** FIT *** FIT *** FIT ***
348  *     **********************************************************  *     **********************************************************
349             call guess()
350             do i=1,5
351                AL_GUESS(i)=AL(i)
352             enddo
353    c         print*,'## guess: ',al
354    
355           do i=1,5           do i=1,5
356              AL(i)=dble(AL_STORE(i,icand))                          AL(i)=dble(AL_STORE(i,icand))            
357           enddo           enddo
358            
359           IDCAND = icand         !fitted track-candidate           IDCAND = icand         !fitted track-candidate
360           ifail=0                !error flag in chi2 computation           ifail=0                !error flag in chi2 computation
361           jstep=0                !# minimization steps           jstep=0                !# minimization steps
362    
363           call mini_2(jstep,ifail)           iprint=0
364    c         if(DEBUG.EQ.1)iprint=1
365             if(VERBOSE.EQ.1)iprint=1
366             if(DEBUG.EQ.1)iprint=2
367             call mini2(jstep,ifail,iprint)
368           if(ifail.ne.0) then           if(ifail.ne.0) then
369              if(DEBUG)then              if(VERBOSE.EQ.1)then
370                 print *,                 print *,
371       $              '*** MINIMIZATION FAILURE *** (mini_2) '       $              '*** MINIMIZATION FAILURE *** (after refinement) '
372       $              ,iev       $              ,iev
373    
374    c$$$               print*,'guess:   ',(al_guess(i),i=1,5)
375    c$$$               print*,'previous: ',(al_store(i,icand),i=1,5)
376    c$$$               print*,'result:   ',(al(i),i=1,5)
377    c$$$               print*,'xgood ',xgood
378    c$$$               print*,'ygood ',ygood
379    c$$$               print*,'----------------------------------------------'
380              endif              endif
381              chi2=-chi2  c            chi2=-chi2
382           endif           endif
383                    
384           if(DEBUG)then           if(DEBUG.EQ.1)then
385              print*,'----------------------------- improved track coord'              print*,'----------------------------- improved track coord'
386  22222       format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222       format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
387              do ip=1,6              do ip=1,6
# Line 264  c         iflag=0 Line 392  c         iflag=0
392           endif           endif
393    
394  c         rchi2=chi2/dble(ndof)  c         rchi2=chi2/dble(ndof)
395           if(DEBUG)then           if(DEBUG.EQ.1)then
396              print*,' '              print*,' '
397              print*,'****** SELECTED TRACK *************'              print*,'****** SELECTED TRACK *************'
398              print*,'#         R. chi2        RIG'              print*,'#         R. chi2        RIG'
# Line 280  c         rchi2=chi2/dble(ndof) Line 408  c         rchi2=chi2/dble(ndof)
408  *     ------------- search if the track has an IMAGE -------------  *     ------------- search if the track has an IMAGE -------------
409  *     ------------- (also this is stored )           -------------  *     ------------- (also this is stored )           -------------
410           if(FIMAGE)goto 122     !>>> jump! (this is already an image)           if(FIMAGE)goto 122     !>>> jump! (this is already an image)
411  *     now search for track-image, by comparing couples IDs  
412    *     -----------------------------------------------------
413    *     first check if the track is ambiguous
414    *     -----------------------------------------------------
415    *     (modified on august 2007 by ElenaV)
416             is1=0
417             do ip=1,NPLANES
418                if(SENSOR_STORE(ip,icand).ne.0)then
419                   is1=SENSOR_STORE(ip,icand)
420                   if(ip.eq.6)is1=3-is1 !last plane inverted
421                endif
422             enddo
423             if(is1.eq.0)then
424                if(WARNING.EQ.1)print*,'** WARNING ** sensor=0'
425                goto 122            !jump
426             endif
427    c         print*,'is1 ',is1
428             do ip=1,NPLANES
429                is2 = SENSOR_STORE(ip,icand) !sensor
430    c            print*,'is2 ',is2,' ip ',ip
431                if(ip.eq.6.and.is2.ne.0)is2=3-is2 !last plane inverted
432                if(
433         $           (is1.ne.is2.and.is2.ne.0)
434         $           )goto 122      !jump (this track cannot have an image)
435             enddo
436             if(DEBUG.eq.1)print*,' >>> ambiguous track! '
437    *     now search for track-image among track candidates
438    c$$$         do i=1,ntracks
439    c$$$            iimage=i
440    c$$$            do ip=1,nplanes
441    c$$$               if(     CP_STORE(nplanes-ip+1,icand).ne.
442    c$$$     $              -1*CP_STORE(nplanes-ip+1,i).and.
443    c$$$     $              CP_STORE(nplanes-ip+1,i).ne.0.and.
444    c$$$     $              CP_STORE(nplanes-ip+1,icand).ne.0 )iimage=0
445    c$$$               print*,' track ',i,' CP ',CP_STORE(nplanes-ip+1,i)
446    c$$$     $              ,CP_STORE(nplanes-ip+1,icand),iimage
447    c$$$            enddo
448    c$$$            if(  iimage.ne.0.and.
449    c$$$c     $           RCHI2_STORE(i).le.CHI2MAX.and.
450    c$$$c     $           RCHI2_STORE(i).gt.0.and.
451    c$$$     $           .true.)then
452    c$$$               if(DEBUG.EQ.1)print*,'Track candidate ',iimage
453    c$$$     $              ,' >>> TRACK IMAGE >>> of'
454    c$$$     $              ,ibest
455    c$$$               goto 122         !image track found
456    c$$$            endif
457    c$$$         enddo
458    *     ---------------------------------------------------------------
459    *     take the candidate with the greatest number of matching couples
460    *     if more than one satisfies the requirement,
461    *     choose the one with more points and lower chi2
462    *     ---------------------------------------------------------------
463    *     count the number of matching couples
464             ncpmax = 0
465             iimage   = 0           !id of candidate with better matching
466           do i=1,ntracks           do i=1,ntracks
467              iimage=i              ncp=0
468              do ip=1,nplanes              do ip=1,nplanes
469                 if(     CP_STORE(nplanes-ip+1,icand).ne.                 if(CP_STORE(nplanes-ip+1,icand).ne.0)then
470       $              -1*CP_STORE(nplanes-ip+1,i) )iimage=0                    if(
471         $                 CP_STORE(nplanes-ip+1,i).ne.0
472         $                 .and.
473         $                 CP_STORE(nplanes-ip+1,icand).eq.
474         $                 -1*CP_STORE(nplanes-ip+1,i)
475         $                 )then
476                         ncp=ncp+1  !ok
477                      elseif(
478         $                    CP_STORE(nplanes-ip+1,i).ne.0
479         $                    .and.
480         $                    CP_STORE(nplanes-ip+1,icand).ne.
481         $                    -1*CP_STORE(nplanes-ip+1,i)
482         $                    )then
483                         ncp = 0
484                         goto 117   !it is not an image candidate
485                      else
486                        
487                      endif
488                   endif
489    c$$$               print*,' track ',i,' CP ',CP_STORE(nplanes-ip+1,i)
490    c$$$     $              ,CP_STORE(nplanes-ip+1,icand),ncp
491              enddo              enddo
492              if(  iimage.ne.0.and.   117        continue
493  c     $           RCHI2_STORE(i).le.CHI2MAX.and.              trackimage(i)=ncp   !number of matching couples
494  c     $           RCHI2_STORE(i).gt.0.and.              if(ncp>ncpmax)then
495       $           .true.)then                 ncpmax=ncp
496                 if(DEBUG)print*,'Track candidate ',iimage                 iimage=i
      $              ,' >>> TRACK IMAGE >>> of'  
      $              ,ibest  
                goto 122         !image track found  
497              endif              endif
498           enddo           enddo
499    *     check if there are more than one image candidates
500             ngood=0
501             do i=1,ntracks
502                if( ncpmax.ne.0.and.trackimage(i).eq.ncpmax )ngood=ngood+1
503             enddo
504    *     if there are, choose the best one
505             if(ngood.gt.1)then
506    *     -------------------------------------------------------
507    *     order track-candidates according to:
508    *     1st) decreasing n.points
509    *     2nd) increasing chi**2
510    *     -------------------------------------------------------
511                rchi2best=1000000000.
512                ndofbest=0            
513                do i=1,ntracks
514                   if( trackimage(i).eq.ncpmax )then
515                      ndof=0              
516                      do ii=1,nplanes    
517                         ndof=ndof        
518         $                    +int(xgood_store(ii,i))
519         $                    +int(ygood_store(ii,i))
520                      enddo              
521                      if(ndof.gt.ndofbest)then
522                         iimage=i
523                         rchi2best=RCHI2_STORE(i)
524                         ndofbest=ndof    
525                      elseif(ndof.eq.ndofbest)then
526                         if(RCHI2_STORE(i).lt.rchi2best.and.
527         $                    RCHI2_STORE(i).gt.0)then
528                            iimage=i
529                            rchi2best=RCHI2_STORE(i)
530                            ndofbest=ndof  
531                         endif            
532                      endif
533                   endif
534                enddo
535                
536             endif
537    
538             if(DEBUG.EQ.1)print*,'Track candidate ',iimage
539         $        ,' >>> TRACK IMAGE >>> of'
540         $        ,ibest
541    
542   122     continue   122     continue
543    
544    
545  *     --- and store the results --------------------------------  *     --- and store the results --------------------------------
546           ntrk = ntrk + 1                   !counter of found tracks           ntrk = ntrk + 1                   !counter of found tracks
547           if(.not.FIMAGE           if(.not.FIMAGE
# Line 311  c         print*,'++++++++++ iimage,fima Line 554  c         print*,'++++++++++ iimage,fima
554  c     $        ,iimage,fimage,ntrk,image(ntrk)  c     $        ,iimage,fimage,ntrk,image(ntrk)
555    
556           if(ntrk.eq.NTRKMAX)then           if(ntrk.eq.NTRKMAX)then
557              if(verbose)              if(verbose.eq.1)
558       $           print*,       $           print*,
559       $           '** warning ** number of identified '//       $           '** warning ** number of identified '//
560       $           'tracks exceeds vector dimension '       $           'tracks exceeds vector dimension '
# Line 347  cc            good2=.false. Line 590  cc            good2=.false.
590       $        rchi2best.le.CHI2MAX.and.       $        rchi2best.le.CHI2MAX.and.
591  c     $        rchi2best.lt.15..and.  c     $        rchi2best.lt.15..and.
592       $        .true.)then       $        .true.)then
593              if(DEBUG)then              if(DEBUG.EQ.1)then
594                 print*,'***** NEW SEARCH ****'                 print*,'***** NEW SEARCH ****'
595              endif              endif
596              goto 11111          !try new search              goto 11111          !try new search
# Line 361  c     $        rchi2best.lt.15..and. Line 604  c     $        rchi2best.lt.15..and.
604        end        end
605    
606    
   
   
 c$$$************************************************************  
 c$$$  
 c$$$      subroutine readmipparam  
 c$$$              
 c$$$      include 'commontracker.f'  
 c$$$      include 'calib.f'  
 c$$$  
 c$$$      character*60 fname_param  
 c$$$ 201  format('trk-LADDER',i1,'-mip.dat')  
 c$$$      do ilad=1,nladders_view          
 c$$$         write(fname_param,201)ilad  
 c$$$         print *,'Opening file: ',fname_param  
 c$$$         open(10,  
 c$$$     $        FILE='./bin-aux/'//fname_param(1:LNBLNK(fname_param))  
 c$$$     $        ,STATUS='UNKNOWN'  
 c$$$     $        ,IOSTAT=iostat  
 c$$$     $        )  
 c$$$         if(iostat.ne.0)then  
 c$$$            print*,'READMIPPARAM: *** Error in opening file ***'  
 c$$$            return  
 c$$$         endif  
 c$$$         do iv=1,nviews  
 c$$$            read(10,*  
 c$$$     $           ,IOSTAT=iostat  
 c$$$     $           )pip,  
 c$$$     $            mip(int(pip),ilad)  
 c$$$c            print*,ilad,iv,pip,mip(int(pip),ilad)  
 c$$$         enddo  
 c$$$         close(10)  
 c$$$      enddo  
 c$$$  
 c$$$      return  
 c$$$      end  
 c$$$*** * * * *** * * * *** * * * *** * * * *** * * * *** * * * ***  
 c$$$      subroutine readchargeparam  
 c$$$        
 c$$$        
 c$$$      include 'commontracker.f'  
 c$$$      include 'calib.f'  
 c$$$  
 c$$$      character*60 fname_param  
 c$$$ 201  format('charge-l',i1,'.dat')  
 c$$$      do ilad=1,nladders_view          
 c$$$         write(fname_param,201)ilad  
 c$$$         print *,'Opening file: ',fname_param  
 c$$$         open(10,  
 c$$$     $        FILE='./bin-aux/'//fname_param(1:LNBLNK(fname_param))  
 c$$$     $        ,STATUS='UNKNOWN'  
 c$$$     $        ,IOSTAT=iostat  
 c$$$     $        )  
 c$$$         if(iostat.ne.0)then  
 c$$$            print*,'READCHARGEPARAM: *** Error in opening file ***'  
 c$$$            return  
 c$$$         endif  
 c$$$         do ip=1,nplanes  
 c$$$            read(10,*  
 c$$$     $           ,IOSTAT=iostat  
 c$$$     $           )pip,  
 c$$$     $            kch(ip,ilad),cch(ip,ilad),sch(ip,ilad)          
 c$$$c            print*,ilad,ip,pip,kch(ip,ilad),  
 c$$$c     $           cch(ip,ilad),sch(ip,ilad)  
 c$$$         enddo  
 c$$$         close(10)  
 c$$$      enddo  
 c$$$  
 c$$$      return  
 c$$$      end  
 c$$$*** * * * *** * * * *** * * * *** * * * *** * * * *** * * * ***  
 c$$$      subroutine readetaparam  
 c$$$*     -----------------------------------------  
 c$$$*     read eta2,3,4 calibration parameters  
 c$$$*     and fill variables:  
 c$$$*  
 c$$$*     eta2(netabin,nladders_view,nviews)  
 c$$$*     eta3(2*netabin,nladders_view,nviews)  
 c$$$*     eta4(2*netabin,nladders_view,nviews)  
 c$$$*  
 c$$$      include 'commontracker.f'  
 c$$$      include 'calib.f'  
 c$$$  
 c$$$      character*40 fname_binning  
 c$$$      character*40 fname_param  
 c$$$c      character*120 cmd1  
 c$$$c      character*120 cmd2  
 c$$$  
 c$$$  
 c$$$******retrieve ANGULAR BINNING info  
 c$$$      fname_binning='binning.dat'  
 c$$$      print *,'Opening file: ',fname_binning  
 c$$$      open(10,  
 c$$$     $     FILE='./bin-aux/'//fname_binning(1:LNBLNK(fname_binning))  
 c$$$     $     ,STATUS='UNKNOWN'  
 c$$$     $     ,IOSTAT=iostat  
 c$$$     $     )  
 c$$$      if(iostat.ne.0)then  
 c$$$         print*,'READETAPARAM: *** Error in opening file ***'  
 c$$$         return  
 c$$$      endif  
 c$$$      print*,'---- ANGULAR BINNING ----'  
 c$$$      print*,'Bin   -   angL   -   angR'  
 c$$$ 101  format(i2,'       ',f6.2,'     ',f6.2)  
 c$$$      do ibin=1,nangmax  
 c$$$         read(10,*  
 c$$$     $        ,IOSTAT=iostat  
 c$$$     $        )xnn,angL(ibin),angR(ibin)  
 c$$$         if(iostat.ne.0)goto 1000  
 c$$$         write(*,101)int(xnn),angL(ibin),angR(ibin)  
 c$$$      enddo          
 c$$$ 1000 nangbin=int(xnn)  
 c$$$      close(10)  
 c$$$      print*,'-------------------------'  
 c$$$        
 c$$$  
 c$$$  
 c$$$      do ieta=2,4               !loop on eta 2,3,4          
 c$$$******retrieve correction parameters  
 c$$$ 200     format(' Opening eta',i1,' files...')  
 c$$$         write(*,200)ieta  
 c$$$  
 c$$$ 201     format('eta',i1,'-bin',i1,'-l',i1,'.dat')  
 c$$$ 202     format('eta',i1,'-bin',i2,'-l',i1,'.dat')  
 c$$$         do iang=1,nangbin  
 c$$$            do ilad=1,nladders_view  
 c$$$               if(iang.lt.10)write(fname_param,201)ieta,iang,ilad  
 c$$$               if(iang.ge.10)write(fname_param,202)ieta,iang,ilad  
 c$$$c               print *,'Opening file: ',fname_param  
 c$$$               open(10,  
 c$$$     $             FILE='./bin-aux/'//fname_param(1:LNBLNK(fname_param))  
 c$$$     $              ,STATUS='UNKNOWN'  
 c$$$     $              ,IOSTAT=iostat  
 c$$$     $              )  
 c$$$               if(iostat.ne.0)then  
 c$$$                  print*,'READETAPARAM: *** Error in opening file ***'  
 c$$$                  return  
 c$$$               endif  
 c$$$               do ival=1,netavalmax  
 c$$$                  if(ieta.eq.2)read(10,*  
 c$$$     $                 ,IOSTAT=iostat  
 c$$$     $                 )  
 c$$$     $                 eta2(ival,iang),  
 c$$$     $                 (feta2(ival,iv,ilad,iang),iv=1,nviews)  
 c$$$                  if(ieta.eq.3)read(10,*  
 c$$$     $                 ,IOSTAT=iostat  
 c$$$     $                 )  
 c$$$     $                 eta3(ival,iang),  
 c$$$     $                 (feta3(ival,iv,ilad,iang),iv=1,nviews)  
 c$$$                  if(ieta.eq.4)read(10,*  
 c$$$     $                 ,IOSTAT=iostat  
 c$$$     $                 )  
 c$$$     $                 eta4(ival,iang),  
 c$$$     $                 (feta4(ival,iv,ilad,iang),iv=1,nviews)  
 c$$$                  if(iostat.ne.0)then  
 c$$$                     netaval=ival-1  
 c$$$c$$$                     if(eta2(1,iang).ne.-eta2(netaval,iang))  
 c$$$c$$$     $                    print*,'**** ERROR on parameters !!! ****'  
 c$$$                     goto 2000  
 c$$$                  endif  
 c$$$               enddo  
 c$$$ 2000          close(10)  
 c$$$*               print*,'... done'  
 c$$$            enddo  
 c$$$         enddo  
 c$$$  
 c$$$      enddo                     !end loop on eta 2,3,4  
 c$$$  
 c$$$  
 c$$$      return  
 c$$$      end  
 c$$$  
   
607                
608  ************************************************************  ************************************************************
609  ************************************************************  ************************************************************
# Line 557  c$$$ Line 628  c$$$
628  *     PFAy   - Position Finding Algorithm in y (COG2,ETA2,...)  *     PFAy   - Position Finding Algorithm in y (COG2,ETA2,...)
629  *     angx   - Projected angle in x  *     angx   - Projected angle in x
630  *     angy   - Projected angle in y  *     angy   - Projected angle in y
631    *     bfx    - x-component of magnetci field
632    *     bfy    - y-component of magnetic field
633  *  *
634  *     --------- COUPLES -------------------------------------------------------  *     --------- COUPLES -------------------------------------------------------
635  *     The couple defines a point in the space.  *     The couple defines a point in the space.
# Line 595  c$$$ Line 668  c$$$
668  *  *
669  *  *
670    
671        subroutine xyz_PAM(icx,icy,sensor,PFAx,PFAy,angx,angy)        subroutine xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
672    
 c*****************************************************  
 c     07/10/2005 modified by elena vannuccini --> (1)  
 c     01/02/2006 modified by elena vannuccini --> (2)  
 c     02/02/2006 modified by Elena Vannuccini --> (3)  
 c                (implemented new p.f.a.)  
 c     03/02/2006 modified by Elena Vannuccini --> (4)  
 c                (implemented variable resolution)  
 c*****************************************************  
673                
674        include 'commontracker.f'        include 'commontracker.f'
       include 'calib.f'  
675        include 'level1.f'        include 'level1.f'
676          include 'calib.f'
677        include 'common_align.f'        include 'common_align.f'
678        include 'common_mech.f'        include 'common_mech.f'
679        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
       include 'common_resxy.f'  
   
 c      logical DEBUG  
 c      common/dbg/DEBUG  
680    
681        integer icx,icy           !X-Y cluster ID        integer icx,icy           !X-Y cluster ID
682        integer sensor        integer sensor
683        integer viewx,viewy        integer viewx,viewy
684        character*4 PFAx,PFAy     !PFA to be used        character*4 PFAx,PFAy     !PFA to be used
685        real angx,angy            !X-Y angle        real ax,ay                !X-Y geometric angle
686          real angx,angy            !X-Y effective angle
687          real bfx,bfy              !X-Y b-field components
688    
689        real stripx,stripy        real stripx,stripy
690    
691        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
692        double precision xrt_A,yrt_A,zrt_A        double precision xrt_A,yrt_A,zrt_A
693        double precision xrt_B,yrt_B,zrt_B        double precision xrt_B,yrt_B,zrt_B
 c      double precision xi,yi,zi  
 c      double precision xi_A,yi_A,zi_A  
 c      double precision xi_B,yi_B,zi_B  
694                
695    
696        parameter (ndivx=30)        parameter (ndivx=30)
697    
698    
699    c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy
700                
701        resxPAM = 0        resxPAM = 0
702        resyPAM = 0        resyPAM = 0
# Line 647  c      double precision xi_B,yi_B,zi_B Line 710  c      double precision xi_B,yi_B,zi_B
710        xPAM_B = 0.        xPAM_B = 0.
711        yPAM_B = 0.        yPAM_B = 0.
712        zPAM_B = 0.        zPAM_B = 0.
713    c      print*,'## xyz_PAM: ',icx,icy,sensor,PFAx,PFAy,angx,angy
714    
715          if(sensor.lt.1.or.sensor.gt.2)then
716             print*,'xyz_PAM   ***ERROR*** wrong input '
717             print*,'sensor ',sensor
718             icx=0
719             icy=0
720          endif
721    
722  *     -----------------  *     -----------------
723  *     CLUSTER X  *     CLUSTER X
724  *     -----------------  *     -----------------      
   
725        if(icx.ne.0)then        if(icx.ne.0)then
726           viewx = VIEW(icx)  
727           nldx = nld(MAXS(icx),VIEW(icx))           viewx   = VIEW(icx)
728           nplx = npl(VIEW(icx))           nldx    = nld(MAXS(icx),VIEW(icx))
729           resxPAM = RESXAV !!!!!!!TEMPORANEO!!!!!!!!!!!!!!!!           nplx    = npl(VIEW(icx))
730                     resxPAM = RESXAV
731           stripx = float(MAXS(icx))           stripx  = float(MAXS(icx))
732           if(PFAx.eq.'COG1')then  !(1)  
733              stripx = stripx      !(1)           if(
734              resxPAM = resxPAM    !(1)       $        viewx.lt.1.or.        
735         $        viewx.gt.12.or.
736         $        nldx.lt.1.or.
737         $        nldx.gt.3.or.
738         $        stripx.lt.1.or.
739         $        stripx.gt.3072.or.
740         $        .false.)then
741                print*,'xyz_PAM   ***ERROR*** wrong input '
742                print*,'icx ',icx,'view ',viewx,'nld ',nldx,'strip ',stripx
743                icx = 0
744                goto 10
745             endif
746    
747    *        --------------------------
748    *        magnetic-field corrections
749    *        --------------------------
750             angtemp  = ax
751             bfytemp  = bfy
752    *        /////////////////////////////////
753    *        AAAAHHHHHHHH!!!!!!!!!!!!!!!!!!!!!
754    *        *grvzkkjsdgjhhhgngbn###>:(
755    *        /////////////////////////////////
756    c         if(nplx.eq.6) angtemp = -1. * ax
757    c         if(nplx.eq.6) bfytemp = -1. * bfy
758             if(viewx.eq.12) angtemp = -1. * ax
759             if(viewx.eq.12) bfytemp = -1. * bfy
760             tgtemp   = tan(angtemp*acos(-1.)/180.) + pmuH_h*bfytemp*0.00001
761             angx     = 180.*atan(tgtemp)/acos(-1.)
762             stripx   = stripx - 0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX
763    c$$$         print*,nplx,ax,bfy/10.
764    c$$$         print*,angx,0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX
765    c$$$         print*,'========================'
766    c$$$         if(bfy.ne.0.)print*,viewx,'-x- '
767    c$$$     $        ,bfy,-1*0.5*pmuH_h*bfytemp*0.00001*SiDimZ
768    *        --------------------------
769    
770    c$$$         print*,'--- x-cl ---'
771    c$$$         istart = INDSTART(ICX)
772    c$$$         istop  = TOTCLLENGTH
773    c$$$         if(icx.lt.NCLSTR1)istop=INDSTART(ICX+1)-1
774    c$$$         print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)
775    c$$$         print*,(CLSIGNAL(i),i=istart,istop)
776    c$$$         print*,INDMAX(icx)
777    c$$$         print*,cog(4,icx)
778    c$$$         print*,fbad_cog(4,icx)
779            
780    
781             if(PFAx.eq.'COG1')then
782    
783                stripx  = stripx
784                resxPAM = 1e-4*pitchX/sqrt(12.)!!resxPAM
785    
786           elseif(PFAx.eq.'COG2')then           elseif(PFAx.eq.'COG2')then
787              stripx = stripx + cog(2,icx)              
788                stripx  = stripx + cog(2,icx)            
789                resxPAM = risx_cog(abs(angx))!TEMPORANEO              
790              resxPAM = resxPAM*fbad_cog(2,icx)              resxPAM = resxPAM*fbad_cog(2,icx)
791    
792             elseif(PFAx.eq.'COG3')then
793    
794                stripx  = stripx + cog(3,icx)            
795                resxPAM = risx_cog(abs(angx))!TEMPORANEO                      
796                resxPAM = resxPAM*fbad_cog(3,icx)
797    
798             elseif(PFAx.eq.'COG4')then
799    
800                stripx  = stripx + cog(4,icx)            
801                resxPAM = risx_cog(abs(angx))!TEMPORANEO                      
802                resxPAM = resxPAM*fbad_cog(4,icx)
803    
804           elseif(PFAx.eq.'ETA2')then           elseif(PFAx.eq.'ETA2')then
805  c            cog2 = cog(2,icx)  
806  c            etacorr = pfaeta2(cog2,viewx,nldx,angx)                          stripx  = stripx + pfaeta2(icx,angx)          
807  c            stripx = stripx + etacorr              resxPAM = risxeta2(abs(angx))
             stripx = stripx + pfaeta2(icx,angx)            !(3)  
             resxPAM = risx_eta2(angx)                       !   (4)  
             if(DEBUG.and.fbad_cog(2,icx).ne.1)  
      $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)  
808              resxPAM = resxPAM*fbad_cog(2,icx)              resxPAM = resxPAM*fbad_cog(2,icx)
809           elseif(PFAx.eq.'ETA3')then                         !(3)  c$$$            if(DEBUG.EQ.1.and.fbad_cog(2,icx).ne.1)
810              stripx = stripx + pfaeta3(icx,angx)            !(3)  c$$$     $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)
811              resxPAM = risx_eta3(angx)                       !   (4)  
812              if(DEBUG.and.fbad_cog(3,icx).ne.1)              !(3)           elseif(PFAx.eq.'ETA3')then                        
813       $           print*,'BAD icx >>> ',viewx,fbad_cog(3,icx)!(3)  
814              resxPAM = resxPAM*fbad_cog(3,icx)               !(3)              stripx  = stripx + pfaeta3(icx,angx)          
815           elseif(PFAx.eq.'ETA4')then                         !(3)              resxPAM = risxeta3(abs(angx))                      
816              stripx = stripx + pfaeta4(icx,angx)            !(3)              resxPAM = resxPAM*fbad_cog(3,icx)              
817              resxPAM = risx_eta4(angx)                       !   (4)  c            if(DEBUG.and.fbad_cog(3,icx).ne.1)            
818              if(DEBUG.and.fbad_cog(4,icx).ne.1)              !(3)  c     $           print*,'BAD icx >>> ',viewx,fbad_cog(3,icx)
819       $           print*,'BAD icx >>> ',viewx,fbad_cog(4,icx)!(3)  
820              resxPAM = resxPAM*fbad_cog(4,icx)               !(3)           elseif(PFAx.eq.'ETA4')then                        
821           elseif(PFAx.eq.'ETA')then                          !(3)  
822              stripx = stripx + pfaeta(icx,angx)             !(3)              stripx  = stripx + pfaeta4(icx,angx)            
823              resxPAM = ris_eta(icx,angx)                     !   (4)              resxPAM = risxeta4(abs(angx))                      
824              if(DEBUG.and.fbad_cog(2,icx).ne.1)              !(3)              resxPAM = resxPAM*fbad_cog(4,icx)              
825       $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)!(3)  c            if(DEBUG.and.fbad_cog(4,icx).ne.1)              
826  c            resxPAM = resxPAM*fbad_cog(2,icx)               !(3)TEMPORANEO  c     $           print*,'BAD icx >>> ',viewx,fbad_cog(4,icx)
827              resxPAM = resxPAM*fbad_eta(icx,angx)             !(3)(4)  
828           elseif(PFAx.eq.'COG')then           !(2)           elseif(PFAx.eq.'ETA')then  
829              stripx = stripx + cog(0,icx)     !(2)          
830              resxPAM = risx_cog(angx)                        !   (4)              stripx  = stripx + pfaeta(icx,angx)            
831              resxPAM = resxPAM*fbad_cog(0,icx)!(2)  c            resxPAM = riseta(icx,angx)                    
832                resxPAM = riseta(viewx,angx)                    
833                resxPAM = resxPAM*fbad_eta(icx,angx)            
834    c            if(DEBUG.and.fbad_cog(2,icx).ne.1)              
835    c     $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)
836    
837             elseif(PFAx.eq.'ETAL')then  
838    
839                stripx  = stripx + pfaetal(icx,angx)            
840                resxPAM = riseta(viewx,angx)                    
841                resxPAM = resxPAM*fbad_eta(icx,angx)            
842    c            if(DEBUG.and.fbad_cog(2,icx).ne.1)              
843    c     $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)
844    
845             elseif(PFAx.eq.'COG')then          
846    
847                stripx  = stripx + cog(0,icx)            
848                resxPAM = risx_cog(abs(angx))                    
849                resxPAM = resxPAM*fbad_cog(0,icx)
850    
851           else           else
852              print*,'*** Non valid p.f.a. (x) --> ',PFAx              if(DEBUG.EQ.1) print*,'*** Non valid p.f.a. (x) --> ',PFAx
853           endif           endif
854    
855        endif  
856  c      if(icy.eq.0.and.icx.ne.0)  *     ======================================
857  c     $     print*,PFAx,icx,angx,stripx,resxPAM,'***'  *     temporary patch for saturated clusters
858          *     ======================================
859             if( nsatstrips(icx).gt.0 )then
860                stripx  = stripx + cog(4,icx)            
861                resxPAM = pitchX*1e-4/sqrt(12.)
862    cc            cc=cog(4,icx)
863    c$$$            print*,icx,' *** ',cc
864    c$$$            print*,icx,' *** ',resxPAM
865             endif
866    
867     10   endif
868    
869        
870  *     -----------------  *     -----------------
871  *     CLUSTER Y  *     CLUSTER Y
872  *     -----------------  *     -----------------
873    
874        if(icy.ne.0)then        if(icy.ne.0)then
875    
876           viewy = VIEW(icy)           viewy = VIEW(icy)
877           nldy = nld(MAXS(icy),VIEW(icy))           nldy = nld(MAXS(icy),VIEW(icy))
878           nply = npl(VIEW(icy))           nply = npl(VIEW(icy))
879           resyPAM = RESYAV !!!!!!!TEMPORANEO!!!!!!!!!!!!!!!!           resyPAM = RESYAV
880             stripy = float(MAXS(icy))
881    
882             if(
883         $        viewy.lt.1.or.        
884         $        viewy.gt.12.or.
885         $        nldy.lt.1.or.
886         $        nldy.gt.3.or.
887         $        stripy.lt.1.or.
888         $        stripy.gt.3072.or.
889         $        .false.)then
890                print*,'xyz_PAM   ***ERROR*** wrong input '
891                print*,'icy ',icy,'view ',viewy,'nld ',nldy,'strip ',stripy
892                icy = 0
893                goto 20
894             endif
895    
896           if(icx.ne.0.and.(nply.ne.nplx.or.nldy.ne.nldx))then           if(icx.ne.0.and.(nply.ne.nplx.or.nldy.ne.nldx))then
897              print*,'xyz_PAM   ***ERROR*** invalid cluster couple!!! '              if(DEBUG.EQ.1) then
898       $           ,icx,icy                 print*,'xyz_PAM   ***ERROR*** invalid cluster couple!!! '
899         $              ,icx,icy
900                endif
901              goto 100              goto 100
902           endif           endif
903            *        --------------------------
904           stripy = float(MAXS(icy))  *        magnetic-field corrections
905           if(PFAy.eq.'COG1')then !(1)  *        --------------------------
906              stripy = stripy     !(1)           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001        
907              resyPAM = resyPAM   !(1)           angy    = 180.*atan(tgtemp)/acos(-1.)
908             stripy = stripy + 0.5*pmuH_e*bfx*0.00001*SiDimZ/pitchY
909    c$$$         if(bfx.ne.0.)print*,viewy,'-y- '
910    c$$$     $        ,bfx,0.5*pmuH_e*bfx*0.00001*SiDimZ
911    *        --------------------------
912            
913    c$$$         print*,'--- y-cl ---'
914    c$$$         istart = INDSTART(ICY)
915    c$$$         istop  = TOTCLLENGTH
916    c$$$         if(icy.lt.NCLSTR1)istop=INDSTART(ICY+1)-1
917    c$$$         print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)
918    c$$$         print*,(CLSIGNAL(i),i=istart,istop)
919    c$$$         print*,INDMAX(icy)
920    c$$$         print*,cog(4,icy)
921    c$$$         print*,fbad_cog(4,icy)
922    
923             if(PFAy.eq.'COG1')then
924    
925                stripy  = stripy    
926                resyPAM = 1e-4*pitchY/sqrt(12.)!resyPAM  
927    
928           elseif(PFAy.eq.'COG2')then           elseif(PFAy.eq.'COG2')then
929              stripy = stripy + cog(2,icy)  
930                stripy  = stripy + cog(2,icy)
931                resyPAM = risy_cog(abs(angy))!TEMPORANEO
932              resyPAM = resyPAM*fbad_cog(2,icy)              resyPAM = resyPAM*fbad_cog(2,icy)
933    
934             elseif(PFAy.eq.'COG3')then
935    
936                stripy  = stripy + cog(3,icy)
937                resyPAM = risy_cog(abs(angy))!TEMPORANEO
938                resyPAM = resyPAM*fbad_cog(3,icy)
939    
940             elseif(PFAy.eq.'COG4')then
941    
942                stripy  = stripy + cog(4,icy)
943                resyPAM = risy_cog(abs(angy))!TEMPORANEO
944                resyPAM = resyPAM*fbad_cog(4,icy)
945    
946           elseif(PFAy.eq.'ETA2')then           elseif(PFAy.eq.'ETA2')then
947  c            cog2 = cog(2,icy)  
948  c            etacorr = pfaeta2(cog2,viewy,nldy,angy)              stripy  = stripy + pfaeta2(icy,angy)          
949  c            stripy = stripy + etacorr              resyPAM = risyeta2(abs(angy))              
             stripy = stripy + pfaeta2(icy,angy)            !(3)  
             resyPAM = risy_eta2(angy)                       !   (4)  
950              resyPAM = resyPAM*fbad_cog(2,icy)              resyPAM = resyPAM*fbad_cog(2,icy)
951              if(DEBUG.and.fbad_cog(2,icy).ne.1)  c            if(DEBUG.and.fbad_cog(2,icy).ne.1)
952       $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)  c     $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)
953           elseif(PFAy.eq.'ETA3')then                         !(3)  
954              stripy = stripy + pfaeta3(icy,angy)            !(3)           elseif(PFAy.eq.'ETA3')then                      
955              resyPAM = resyPAM*fbad_cog(3,icy)               !(3)  
956              if(DEBUG.and.fbad_cog(3,icy).ne.1)              !(3)              stripy  = stripy + pfaeta3(icy,angy)
957       $           print*,'BAD icy >>> ',viewy,fbad_cog(3,icy)!(3)              resyPAM = resyPAM*fbad_cog(3,icy)  
958           elseif(PFAy.eq.'ETA4')then                         !(3)  c            if(DEBUG.and.fbad_cog(3,icy).ne.1)
959              stripy = stripy + pfaeta4(icy,angy)            !(3)  c     $           print*,'BAD icy >>> ',viewy,fbad_cog(3,icy)
960              resyPAM = resyPAM*fbad_cog(4,icy)               !(3)  
961              if(DEBUG.and.fbad_cog(4,icy).ne.1)              !(3)           elseif(PFAy.eq.'ETA4')then  
962       $           print*,'BAD icy >>> ',viewy,fbad_cog(4,icy)!(3)  
963           elseif(PFAy.eq.'ETA')then                          !(3)              stripy  = stripy + pfaeta4(icy,angy)
964              stripy = stripy + pfaeta(icy,angy)             !(3)              resyPAM = resyPAM*fbad_cog(4,icy)
965              resyPAM = ris_eta(icy,angy)                     !   (4)  c            if(DEBUG.and.fbad_cog(4,icy).ne.1)
966  c            resyPAM = resyPAM*fbad_cog(2,icy)              !(3)TEMPORANEO  c     $           print*,'BAD icy >>> ',viewy,fbad_cog(4,icy)
967              resyPAM = resyPAM*fbad_eta(icy,angy)            !   (4)  
968              if(DEBUG.and.fbad_cog(2,icy).ne.1)              !(3)           elseif(PFAy.eq.'ETA')then
969       $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)!(3)  
970                stripy  = stripy + pfaeta(icy,angy)
971    c            resyPAM = riseta(icy,angy)  
972                resyPAM = riseta(viewy,angy)  
973                resyPAM = resyPAM*fbad_eta(icy,angy)
974    c            if(DEBUG.and.fbad_cog(2,icy).ne.1)
975    c     $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)
976    
977             elseif(PFAy.eq.'ETAL')then
978    
979                stripy  = stripy + pfaetal(icy,angy)
980                resyPAM = riseta(viewy,angy)  
981                resyPAM = resyPAM*fbad_eta(icy,angy)
982    c            if(DEBUG.and.fbad_cog(2,icy).ne.1)
983    c     $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)
984    
985           elseif(PFAy.eq.'COG')then           elseif(PFAy.eq.'COG')then
986              stripy = stripy + cog(0,icy)              
987              resyPAM = risy_cog(angy)                        !   (4)              stripy  = stripy + cog(0,icy)            
988  c            resyPAM = ris_eta(icy,angy)                    !   (4)              resyPAM = risy_cog(abs(angy))
989              resyPAM = resyPAM*fbad_cog(0,icy)              resyPAM = resyPAM*fbad_cog(0,icy)
990    
991           else           else
992              print*,'*** Non valid p.f.a. (x) --> ',PFAx              if(DEBUG.EQ.1) print*,'*** Non valid p.f.a. (x) --> ',PFAx
993           endif           endif
994    
       endif  
995    
996          *     ======================================
997    *     temporary patch for saturated clusters
998    *     ======================================
999             if( nsatstrips(icy).gt.0 )then
1000                stripy  = stripy + cog(4,icy)            
1001                resyPAM = pitchY*1e-4/sqrt(12.)
1002    cc            cc=cog(4,icy)
1003    c$$$            print*,icy,' *** ',cc
1004    c$$$            print*,icy,' *** ',resyPAM
1005             endif
1006    
1007    
1008     20   endif
1009    
1010    c$$$      print*,'## stripx,stripy ',stripx,stripy
1011    
1012  c===========================================================  c===========================================================
1013  C     COUPLE  C     COUPLE
1014  C===========================================================  C===========================================================
# Line 777  c     (xi,yi,zi) = mechanical coordinate Line 1019  c     (xi,yi,zi) = mechanical coordinate
1019  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1020           if(((mod(int(stripx+0.5)-1,1024)+1).le.3)           if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
1021       $        .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...       $        .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
1022              print*,'xyz_PAM (couple):',              if(DEBUG.EQ.1) then
1023       $          ' WARNING: false X strip: strip ',stripx                 print*,'xyz_PAM (couple):',
1024         $              ' WARNING: false X strip: strip ',stripx
1025                endif
1026           endif           endif
1027           xi = acoordsi(stripx,viewx)           xi = acoordsi(stripx,viewx)
1028           yi = acoordsi(stripy,viewy)           yi = acoordsi(stripy,viewy)
# Line 870  c            print*,'X-singlet ',icx,npl Line 1114  c            print*,'X-singlet ',icx,npl
1114  c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...
1115              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
1116       $           .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...       $           .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
1117                 print*,'xyz_PAM (X-singlet):',                 if(DEBUG.EQ.1) then
1118       $             ' WARNING: false X strip: strip ',stripx                    print*,'xyz_PAM (X-singlet):',
1119         $                 ' WARNING: false X strip: strip ',stripx
1120                   endif
1121              endif              endif
1122              xi   = acoordsi(stripx,viewx)              xi   = acoordsi(stripx,viewx)
1123    
# Line 893  c            print*,'X-cl ',icx,stripx,' Line 1139  c            print*,'X-cl ',icx,stripx,'
1139  c            print*,yi_A,' <--> ',yi_B  c            print*,yi_A,' <--> ',yi_B
1140    
1141           else           else
1142                if(DEBUG.EQ.1) then
1143              print *,'routine xyz_PAM ---> not properly used !!!'                 print *,'routine xyz_PAM ---> not properly used !!!'
1144              print *,'icx = ',icx                 print *,'icx = ',icx
1145              print *,'icy = ',icy                 print *,'icy = ',icy
1146                endif
1147              goto 100              goto 100
1148                            
1149           endif           endif
# Line 961  c--------------------------------------- Line 1208  c---------------------------------------
1208  c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'  c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'
1209    
1210        else        else
1211                       if(DEBUG.EQ.1) then
1212           print *,'routine xyz_PAM ---> not properly used !!!'              print *,'routine xyz_PAM ---> not properly used !!!'
1213           print *,'icx = ',icx              print *,'icx = ',icx
1214           print *,'icy = ',icy              print *,'icy = ',icy
1215                         endif
1216        endif        endif
1217                    
1218    
1219    c      print*,'## xPAM,yPAM,zPAM       ',xPAM,yPAM,zPAM
1220    c      print*,'## xPAM_A,yPAM_A,zPAM_A ',xPAM_A,yPAM_A,zPAM_A
1221    c      print*,'## xPAM_B,yPAM_B,zPAM_B ',xPAM_B,yPAM_B,zPAM_B
1222    
1223   100  continue   100  continue
1224        end        end
1225    
1226    ************************************************************************
1227    *     Call xyz_PAM subroutine with default PFA and fill the mini2 common.
1228    *     (done to be called from c/c++)
1229    ************************************************************************
1230    
1231          subroutine xyzpam(ip,icx,icy,lad,sensor,ax,ay,bfx,bfy)
1232    
1233          include 'commontracker.f'
1234          include 'level1.f'
1235          include 'common_mini_2.f'
1236          include 'common_xyzPAM.f'
1237          include 'common_mech.f'
1238          include 'calib.f'
1239          
1240    *     flag to chose PFA
1241    c$$$      character*10 PFA
1242    c$$$      common/FINALPFA/PFA
1243    
1244          integer icx,icy           !X-Y cluster ID
1245          integer sensor
1246          character*4 PFAx,PFAy     !PFA to be used
1247          real ax,ay                !X-Y geometric angle
1248          real bfx,bfy              !X-Y b-field components
1249    
1250          ipx=0
1251          ipy=0      
1252          
1253    c$$$      PFAx = 'COG4'!PFA
1254    c$$$      PFAy = 'COG4'!PFA
1255    
1256    
1257          if(icx.gt.nclstr1.or.icy.gt.nclstr1)then
1258                print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1259         $           ,' does not exists (nclstr1=',nclstr1,')'
1260                icx = -1*icx
1261                icy = -1*icy
1262                return
1263            
1264          endif
1265          
1266          call idtoc(pfaid,PFAx)
1267          call idtoc(pfaid,PFAy)
1268    
1269    cc      print*,PFAx,PFAy
1270    
1271    c$$$      call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1272    
1273    c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy
1274          
1275          if(icx.ne.0.and.icy.ne.0)then
1276    
1277             ipx=npl(VIEW(icx))
1278             ipy=npl(VIEW(icy))
1279    c$$$         if( (nplanes-ipx+1).ne.ip.or.(nplanes-ipy+1).ne.ip )
1280    c$$$     $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1281    c$$$     $        ,' does not belong to the correct plane: ',ip,ipx,ipy
1282            
1283             if( (nplanes-ipx+1).ne.ip )then
1284                print*,'xyzpam: ***WARNING*** cluster ',icx
1285         $           ,' does not belong to plane: ',ip
1286                icx = -1*icx
1287                return
1288             endif
1289             if( (nplanes-ipy+1).ne.ip )then
1290                print*,'xyzpam: ***WARNING*** cluster ',icy
1291         $           ,' does not belong to plane: ',ip
1292                icy = -1*icy
1293                return
1294             endif
1295    
1296             call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1297    
1298             xgood(ip) = 1.
1299             ygood(ip) = 1.
1300             resx(ip)  = resxPAM
1301             resy(ip)  = resyPAM
1302    
1303             xm(ip) = xPAM
1304             ym(ip) = yPAM
1305             zm(ip) = zPAM
1306             xm_A(ip) = 0.
1307             ym_A(ip) = 0.
1308             xm_B(ip) = 0.
1309             ym_B(ip) = 0.
1310    
1311    c         zv(ip) = zPAM
1312    
1313          elseif(icx.eq.0.and.icy.ne.0)then
1314    
1315             ipy=npl(VIEW(icy))
1316    c$$$         if((nplanes-ipy+1).ne.ip)
1317    c$$$     $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1318    c$$$     $        ,' does not belong to the correct plane: ',ip,ipx,ipy
1319             if( (nplanes-ipy+1).ne.ip )then
1320                print*,'xyzpam: ***WARNING*** cluster ',icy
1321         $           ,' does not belong to plane: ',ip
1322                icy = -1*icy
1323                return
1324             endif
1325    
1326             call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1327            
1328             xgood(ip) = 0.
1329             ygood(ip) = 1.
1330             resx(ip)  = 1000.
1331             resy(ip)  = resyPAM
1332    
1333             xm(ip) = -100.
1334             ym(ip) = -100.
1335             zm(ip) = (zPAM_A+zPAM_B)/2.
1336             xm_A(ip) = xPAM_A
1337             ym_A(ip) = yPAM_A
1338             xm_B(ip) = xPAM_B
1339             ym_B(ip) = yPAM_B
1340    
1341    c         zv(ip) = (zPAM_A+zPAM_B)/2.
1342            
1343          elseif(icx.ne.0.and.icy.eq.0)then
1344    
1345             ipx=npl(VIEW(icx))
1346    c$$$         if((nplanes-ipx+1).ne.ip)
1347    c$$$     $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1348    c$$$     $        ,' does not belong to the correct plane: ',ip,ipx,ipy
1349    
1350             if( (nplanes-ipx+1).ne.ip )then
1351                print*,'xyzpam: ***WARNING*** cluster ',icx
1352         $           ,' does not belong to plane: ',ip
1353                icx = -1*icx
1354                return
1355             endif
1356    
1357             call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1358          
1359             xgood(ip) = 1.
1360             ygood(ip) = 0.
1361             resx(ip)  = resxPAM
1362             resy(ip)  = 1000.
1363    
1364             xm(ip) = -100.
1365             ym(ip) = -100.
1366             zm(ip) = (zPAM_A+zPAM_B)/2.
1367             xm_A(ip) = xPAM_A
1368             ym_A(ip) = yPAM_A
1369             xm_B(ip) = xPAM_B
1370             ym_B(ip) = yPAM_B
1371            
1372    c         zv(ip) = (zPAM_A+zPAM_B)/2.
1373    
1374          else
1375    
1376             il = 2
1377             if(lad.ne.0)il=lad
1378             is = 1
1379             if(sensor.ne.0)is=sensor
1380    c         print*,nplanes-ip+1,il,is
1381    
1382             xgood(ip) = 0.
1383             ygood(ip) = 0.
1384             resx(ip)  = 1000.
1385             resy(ip)  = 1000.
1386    
1387             xm(ip) = -100.
1388             ym(ip) = -100.          
1389             zm(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4
1390             xm_A(ip) = 0.
1391             ym_A(ip) = 0.
1392             xm_B(ip) = 0.
1393             ym_B(ip) = 0.
1394    
1395    c         zv(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4
1396    
1397          endif
1398    
1399          if(DEBUG.EQ.1)then
1400    c         print*,'----------------------------- track coord'
1401    22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1402             write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1403         $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1404         $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)
1405    c$$$         print*,'-----------------------------'
1406          endif
1407          end
1408    
1409  ********************************************************************************  ********************************************************************************
1410  ********************************************************************************  ********************************************************************************
# Line 1046  c         print*,'A-(',xPAM_A,yPAM_A,') Line 1480  c         print*,'A-(',xPAM_A,yPAM_A,')
1480           endif                   endif        
1481    
1482           distance=           distance=
1483       $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2       $       ((xmi-XPP)**2+(ymi-YPP)**2)!QUIQUI
1484    cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1485           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1486    
1487  c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b
# Line 1071  c$$$         print*,' resolution ',re Line 1506  c$$$         print*,' resolution ',re
1506  *     ----------------------  *     ----------------------
1507                    
1508           distance=           distance=
1509       $        ((xPAM-XPP)/resxPAM)**2       $       ((xPAM-XPP))**2 !QUIQUI
1510       $        +       $       +
1511       $        ((yPAM-YPP)/resyPAM)**2       $       ((yPAM-YPP))**2
1512    c$$$     $        ((xPAM-XPP)/resxPAM)**2
1513    c$$$     $        +
1514    c$$$     $        ((yPAM-YPP)/resyPAM)**2
1515           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1516    
1517  c$$$         print*,xPAM,yPAM,zPAM  c$$$         print*,xPAM,yPAM,zPAM
# Line 1082  c$$$         print*,' resolution ',resxP Line 1520  c$$$         print*,' resolution ',resxP
1520                    
1521        else        else
1522                    
1523           print*  c         print*
1524       $        ,' function distance_to ---> wrong usage!!!'  c     $        ,' function distance_to ---> wrong usage!!!'
1525           print*,' xPAM,yPAM,zPAM ',xPAM,yPAM,zPAM  c         print*,' xPAM,yPAM,zPAM ',xPAM,yPAM,zPAM
1526           print*,' xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b '  c         print*,' xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b '
1527       $        ,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b
1528        endif          endif  
1529    
1530        distance_to = sngl(distance)        distance_to = sngl(distance)
# Line 1154  c--------------------------------------- Line 1592  c---------------------------------------
1592                 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)                 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
1593       $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...       $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
1594  c     if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  c     if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...
1595                    print*,'whichsensor: ',  c                  print*,'whichsensor: ',
1596       $                ' WARNING: false X strip: strip ',stripx  c     $                ' WARNING: false X strip: strip ',stripx
1597                 endif                 endif
1598                 xi = acoordsi(stripx,viewx)                 xi = acoordsi(stripx,viewx)
1599                 yi = acoordsi(stripy,viewy)                 yi = acoordsi(stripy,viewy)
# Line 1284  c     $              ,iv,xvv(iv),yvv(iv) Line 1722  c     $              ,iv,xvv(iv),yvv(iv)
1722  *     it returns the plane number  *     it returns the plane number
1723  *      *    
1724        include 'commontracker.f'        include 'commontracker.f'
1725          include 'level1.f'
1726  c      include 'common_analysis.f'  c      include 'common_analysis.f'
1727        include 'common_momanhough.f'        include 'common_momanhough.f'
1728                
# Line 1309  c      include 'common_analysis.f' Line 1748  c      include 'common_analysis.f'
1748        is_cp=0        is_cp=0
1749        if(id.lt.0)is_cp=1        if(id.lt.0)is_cp=1
1750        if(id.gt.0)is_cp=2        if(id.gt.0)is_cp=2
1751        if(id.eq.0)print*,'IS_CP ===> wrong couple id !!!'  c      if(id.eq.0)print*,'IS_CP ===> wrong couple id !!!'
1752    
1753        return        return
1754        end        end
# Line 1321  c      include 'common_analysis.f' Line 1760  c      include 'common_analysis.f'
1760  *     it returns the id number ON THE PLANE  *     it returns the id number ON THE PLANE
1761  *      *    
1762        include 'commontracker.f'        include 'commontracker.f'
1763          include 'level1.f'
1764  c      include 'common_analysis.f'  c      include 'common_analysis.f'
1765        include 'common_momanhough.f'        include 'common_momanhough.f'
1766                
# Line 1349  c      include 'common_analysis.f' Line 1789  c      include 'common_analysis.f'
1789  *     positive if sensor =2  *     positive if sensor =2
1790  *  *
1791        include 'commontracker.f'        include 'commontracker.f'
1792          include 'level1.f'
1793  c      include 'calib.f'  c      include 'calib.f'
1794  c      include 'level1.f'  c      include 'level1.f'
1795  c      include 'common_analysis.f'  c      include 'common_analysis.f'
# Line 1378  c      include 'common_analysis.f' Line 1819  c      include 'common_analysis.f'
1819  *************************************************************************  *************************************************************************
1820  *************************************************************************  *************************************************************************
1821  *************************************************************************  *************************************************************************
 c$$$      subroutine book_debug  
 c$$$  
 c$$$      include 'commontracker.f'  
 c$$$      include 'common_momanhough.f'  
 c$$$      include 'common_level2debug.f'  
 c$$$  
 c$$$      character*35 block1,block2,block3!,block4  
 c$$$     $     ,block5!,block6        
 c$$$        
 c$$$* * * * * * * * * * * * * * * * * * * * * * * *  
 c$$$*     HOUGH TRANSFORM PARAMETERS  
 c$$$        
 c$$$      call HBOOK2(1003  
 c$$$     $     ,'y vs tg thyz'  
 c$$$     $     ,300,-1.,1.         !x          
 c$$$     $     ,3000,-70.,70.,0.)   !y  
 c$$$  
 c$$$      call HBOOK1(1004  
 c$$$     $     ,'Dy'  
 c$$$     $     ,100,0.,2.,0.)    
 c$$$  
 c$$$      call HBOOK1(1005  
 c$$$     $     ,'D thyz'  
 c$$$     $     ,100,0.,.05,0.)    
 c$$$  
 c$$$  
 c$$$  
 c$$$*     DEBUG ntuple:  
 c$$$      call HBNT(ntp_level2+1,'LEVEL2',' ')  
 c$$$        
 c$$$      call HBNAME(ntp_level2+1,'EVENT',good2_nt,  
 c$$$     $     'GOOD2:L,NEV2:I')  
 c$$$  
 c$$$ 411  format('NDBLT:I::[0,',I5,']')  
 c$$$      write(block1,411) ndblt_max_nt  
 c$$$      call HBNAME(ntp_level2+1,'HOUGH YZ',ndblt_nt,  
 c$$$     $     block1//'  
 c$$$     $     ,ALFAYZ1(NDBLT):R  
 c$$$     $     ,ALFAYZ2(NDBLT):R  
 c$$$     $     ,DB_CLOUD(NDBLT):I  
 c$$$     $     ')    
 c$$$  
 c$$$ 412  format('NTRPT:I::[0,',I5,']')  
 c$$$      write(block2,412) ntrpt_max_nt  
 c$$$      call HBNAME(ntp_level2+1,'HOUGH XZ',NTRPT_nt,  
 c$$$     $     block2//'  
 c$$$     $     ,ALFAXZ1(NTRPT):R  
 c$$$     $     ,ALFAXZ2(NTRPT):R    
 c$$$     $     ,ALFAXZ3(NTRPT):R  
 c$$$     $     ,TR_CLOUD(NTRPT):I  
 c$$$     $     ')  
 c$$$        
 c$$$    
 c$$$ 413  format('NCLOUDS_YZ:I::[0,',I4,']')  
 c$$$c$$$ 414  format('DB_CLOUD(',I4,'):I')  
 c$$$      write(block3,413) ncloyz_max  
 c$$$c$$$      write(block4,414) ndblt_max_nt  
 c$$$      call HBNAME(ntp_level2+1,'CLOUD YZ',NCLOUDS_YZ,  
 c$$$     $     block3//'  
 c$$$     $     ,ALFAYZ1_AV(NCLOUDS_YZ):R  
 c$$$     $     ,ALFAYZ2_AV(NCLOUDS_YZ):R  
 c$$$     $     ,PTCLOUD_YZ(NCLOUDS_YZ):I'  
 c$$$c$$$     $     ,'//block4  
 c$$$     $     )  
 c$$$  
 c$$$ 415  format('NCLOUDS_XZ:I::[0,',I4,']')  
 c$$$c$$$ 416  format('TR_CLOUD(',I5,'):I')  
 c$$$      write(block5,415) ncloxz_max  
 c$$$c$$$      write(block6,416) ntrpt_max_nt  
 c$$$      call HBNAME(ntp_level2+1,'CLOUD XZ',NCLOUDS_XZ,  
 c$$$     $     block5//'  
 c$$$     $     ,ALFAXZ1_AV(NCLOUDS_XZ):R  
 c$$$     $     ,ALFAXZ2_AV(NCLOUDS_XZ):R  
 c$$$     $     ,ALFAXZ3_AV(NCLOUDS_XZ):R  
 c$$$     $     ,PTCLOUD_XZ(NCLOUDS_XZ):I'  
 c$$$c$$$     $     ,'//block6  
 c$$$     $     )  
 c$$$  
 c$$$        
 c$$$      return  
 c$$$      end  
 ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  
 *  
 *  
 *  
 *  
 *  
 *  
 *  
 *  
 *  
 ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  
 c$$$      subroutine book_level2  
 c$$$c*****************************************************  
 c$$$cccccc 11/9/2005 modified by david fedele  
 c$$$cccccc 07/10/2005 modified by elena vannuccini --> (2)  
 c$$$c*****************************************************  
 c$$$  
 c$$$      include 'commontracker.f'  
 c$$$      include 'common_momanhough.f'  
 c$$$      include 'level2.f'  
 c$$$  
 c$$$      character*35 block1,block2  
 c$$$  
 c$$$c      print*,'__________ booking LEVEL2 n-tuple __________'  
 c$$$  
 c$$$*     LEVEL1 ntuple:  
 c$$$      call HBNT(ntp_level2,'LEVEL2',' ')  
 c$$$        
 c$$$c*****************************************************  
 c$$$cccccc 11/9/2005 modified by david fedele  
 c$$$c      call HBNAME(ntp_level2,'EVENT',good2,'GOOD2:L,NEV2:I')  
 c$$$cccccc 06/10/2005 modified by elena vannuccini  
 c$$$c      call HBNAME(ntp_level2,'GENERAL',good2,'GOOD2:L,NEV2:I  
 c$$$c     $     ,WHIC_CALIB:I,SWCODE:I')  
 c$$$      call HBNAME(ntp_level2,'GENERAL',good2,'GOOD2:L,NEV2:I  
 c$$$     $     ,WHICH_CALIB:I,SWCODE:I,CRC(12):L')  
 c$$$c*********************************************************  
 c$$$    
 c$$$  
 c$$$c$$$# ifndef TEST2003  
 c$$$c$$$  
 c$$$c$$$      call HBNAME(ntp_level2,'CPU',pkt_type  
 c$$$c$$$     $     ,'PKT_TYPE:I::[0,50]  
 c$$$c$$$     $     ,PKT_NUM:I  
 c$$$c$$$     $     ,OBT:I'//  
 c$$$c$$$c********************************************************  
 c$$$c$$$cccccc 11/9/2005 modified by david fedele  
 c$$$c$$$c     $     ,WHICH_CALIB:I::[0,50]')  
 c$$$c$$$     $     ',CPU_CRC:L')  
 c$$$c$$$c********************************************************  
 c$$$c$$$  
 c$$$c$$$# endif  
 c$$$  
 c$$$ 417  format('NTRK:I::[0,',I4,']')  
 c$$$ 418  format(',IMAGE(NTRK):I::[0,',I4,']')  
 c$$$      write(block1,417)NTRKMAX  
 c$$$      write(block2,418)NTRKMAX  
 c$$$      call HBNAME(ntp_level2,'TRACKS',NTRK,  
 c$$$     $     block1//  
 c$$$     $     block2//'  
 c$$$     $     ,XM(6,NTRK):R  
 c$$$     $     ,YM(6,NTRK):R  
 c$$$     $     ,ZM(6,NTRK):R  
 c$$$     $     ,RESX(6,NTRK):R  
 c$$$     $     ,RESY(6,NTRK):R  
 c$$$     $     ,AL(5,NTRK):R  
 c$$$     $     ,COVAL(5,5,NTRK):R  
 c$$$     $     ,CHI2(NTRK):R  
 c$$$     $     ,XGOOD(6,NTRK):I::[0,1]  
 c$$$     $     ,YGOOD(6,NTRK):I::[0,1]  
 c$$$     $     ,XV(6,NTRK):R  
 c$$$     $     ,YV(6,NTRK):R  
 c$$$     $     ,ZV(6,NTRK):R  
 c$$$     $     ,AXV(6,NTRK):R  
 c$$$     $     ,AYV(6,NTRK):R'//  
 c$$$c*****************************************************  
 c$$$cccccc 11/9/2005 modified by david fedele  
 c$$$c     $     ,DEDXP(6,NTRK):R'//  
 c$$$c     $     ')  
 c$$$     $     ',DEDX_X(6,NTRK):R  
 c$$$     $     ,DEDX_Y(6,NTRK):R'//  
 c$$$c****************************************************  
 c$$$cccccc 06/10/2005 modified by elena vannuccini  
 c$$$c     $     ,CRC(12):L  
 c$$$     $     ',BdL(NTRK):R'  
 c$$$     $     )  
 c$$$c****************************************************  
 c$$$  
 c$$$    
 c$$$      call HBNAME(ntp_level2,'SINGLETX',nclsx,  
 c$$$c*****************************************************  
 c$$$cccccc 11/9/2005 modified by david fedele  
 c$$$c     $     'NCLSX(6):I,NCLSY(6):I')  
 c$$$     $     'NCLSX:I::[0,500],PLANEX(NCLSX):I  
 c$$$     $     ,XS(2,NCLSX):R,SGNLXS(NCLSX):R') !(2)  
 c$$$c    $     ,XS(NCLSX):R,SGNLXS(NCLSX):R')   !(2)  
 c$$$      call HBNAME(ntp_level2,'SINGLETY',nclsy,  
 c$$$     $     'NCLSY:I::[0,500],PLANEY(NCLSY):I  
 c$$$     $     ,YS(2,NCLSY):R,SGNLYS(NCLSY):R') !(2)  
 c$$$c    $     ,YS(NCLSY):R,SGNLYS(NCLSY):R')   !(2)  
 c$$$      return  
 c$$$      end  
   
 c$$$      subroutine fill_level2_clouds  
 c$$$c*****************************************************  
 c$$$c     29/11/2005 created by elena vannuccini  
 c$$$c*****************************************************  
 c$$$  
 c$$$*     -------------------------------------------------------  
 c$$$*     This routine fills the  variables related to the hough  
 c$$$*     transform, for the debig n-tuple  
 c$$$*     -------------------------------------------------------  
 c$$$  
 c$$$      include 'commontracker.f'  
 c$$$      include 'common_momanhough.f'  
 c$$$      include 'common_level2debug.f'  
 c$$$      include 'level2.f'  
 c$$$  
 c$$$      good2_nt=.true.!good2  
 c$$$c      nev2_nt=nev2  
 c$$$        
 c$$$      if(.false.  
 c$$$     $     .or.ntrpt.gt.ntrpt_max_nt  
 c$$$     $     .or.ndblt.gt.ndblt_max_nt  
 c$$$     $     .or.NCLOUDS_XZ.gt.ncloxz_max  
 c$$$     $     .or.NCLOUDS_yZ.gt.ncloyz_max  
 c$$$     $     )then  
 c$$$         good2_nt=.false.  
 c$$$         ntrpt_nt=0  
 c$$$         ndblt_nt=0  
 c$$$         NCLOUDS_XZ_nt=0  
 c$$$         NCLOUDS_YZ_nt=0  
 c$$$      else  
 c$$$         ndblt_nt=ndblt  
 c$$$         ntrpt_nt=ntrpt  
 c$$$         if(ndblt.ne.0)then  
 c$$$            do id=1,ndblt  
 c$$$               alfayz1_nt(id)=alfayz1(id) !Y0  
 c$$$               alfayz2_nt(id)=alfayz2(id) !tg theta-yz  
 c$$$c               db_cloud_nt(id)=db_cloud(id)  
 c$$$            enddo  
 c$$$         endif  
 c$$$         if(ndblt.ne.0)then  
 c$$$            do it=1,ntrpt  
 c$$$               alfaxz1_nt(it)=alfaxz1(it) !X0  
 c$$$               alfaxz2_nt(it)=alfaxz2(it) !tg theta-xz  
 c$$$               alfaxz3_nt(it)=alfaxz3(it) !1/r  
 c$$$c               tr_cloud_nt(it)=tr_cloud(it)  
 c$$$            enddo  
 c$$$         endif  
 c$$$         nclouds_yz_nt=nclouds_yz  
 c$$$         nclouds_xz_nt=nclouds_xz  
 c$$$         if(nclouds_yz.ne.0)then  
 c$$$            nnn=0  
 c$$$            do iyz=1,nclouds_yz  
 c$$$               ptcloud_yz_nt(iyz)=ptcloud_yz(iyz)  
 c$$$               alfayz1_av_nt(iyz)=alfayz1_av(iyz)  
 c$$$               alfayz2_av_nt(iyz)=alfayz2_av(iyz)  
 c$$$               nnn=nnn+ptcloud_yz(iyz)  
 c$$$            enddo  
 c$$$            do ipt=1,nnn  
 c$$$               db_cloud_nt(ipt)=db_cloud(ipt)  
 c$$$            enddo  
 c$$$c            print*,'#### ntupla #### ptcloud_yz '  
 c$$$c     $           ,(ptcloud_yz(i),i=1,nclouds_yz)  
 c$$$c            print*,'#### ntupla #### db_cloud '  
 c$$$c     $           ,(db_cloud(i),i=1,nnn)  
 c$$$         endif  
 c$$$         if(nclouds_xz.ne.0)then  
 c$$$            nnn=0  
 c$$$            do ixz=1,nclouds_xz  
 c$$$               ptcloud_xz_nt(ixz)=ptcloud_xz(ixz)  
 c$$$               alfaxz1_av_nt(ixz)=alfaxz1_av(ixz)  
 c$$$               alfaxz2_av_nt(ixz)=alfaxz2_av(ixz)  
 c$$$               alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)  
 c$$$               nnn=nnn+ptcloud_xz(ixz)                
 c$$$            enddo  
 c$$$            do ipt=1,nnn  
 c$$$               tr_cloud_nt(ipt)=tr_cloud(ipt)  
 c$$$            enddo  
 c$$$c            print*,'#### ntupla #### ptcloud_xz '  
 c$$$c     $           ,(ptcloud_xz(i),i=1,nclouds_xz)  
 c$$$c            print*,'#### ntupla #### tr_cloud '  
 c$$$c     $           ,(tr_cloud(i),i=1,nnn)  
 c$$$         endif  
 c$$$      endif  
 c$$$      end  
1822                
1823    
1824  ***************************************************  ***************************************************
# Line 1660  c$$$      end Line 1833  c$$$      end
1833        subroutine cl_to_couples(iflag)        subroutine cl_to_couples(iflag)
1834    
1835        include 'commontracker.f'        include 'commontracker.f'
1836          include 'level1.f'
1837        include 'common_momanhough.f'        include 'common_momanhough.f'
1838        include 'momanhough_init.f'  c      include 'momanhough_init.f'
1839        include 'calib.f'        include 'calib.f'
1840        include 'level1.f'  c      include 'level1.f'
   
 c      logical DEBUG  
 c      common/dbg/DEBUG  
1841    
1842  *     output flag  *     output flag
1843  *     --------------  *     --------------
# Line 1676  c      common/dbg/DEBUG Line 1847  c      common/dbg/DEBUG
1847        integer iflag        integer iflag
1848    
1849        integer badseed,badclx,badcly        integer badseed,badclx,badcly
1850        
1851          if(DEBUG.EQ.1)print*,'cl_to_couples:'
1852    
1853  *     init variables  *     init variables
1854        ncp_tot=0        ncp_tot=0
# Line 1691  c      common/dbg/DEBUG Line 1864  c      common/dbg/DEBUG
1864           ncls(ip)=0           ncls(ip)=0
1865        enddo        enddo
1866        do icl=1,nclstrmax_level2        do icl=1,nclstrmax_level2
1867           cl_single(icl)=1           cl_single(icl) = 1
1868           cl_good(icl)=0           cl_good(icl)   = 0
1869        enddo        enddo
1870                do iv=1,nviews
1871  *     start association           ncl_view(iv)  = 0
1872        ncouples=0           mask_view(iv) = 0      !all included
       do icx=1,nclstr1          !loop on cluster (X)  
          if(mod(VIEW(icx),2).eq.1)goto 10  
           
 *     ----------------------------------------------------  
 *     cut on charge (X VIEW)  
 *     ----------------------------------------------------  
          if(dedx(icx).lt.dedx_x_min)then  
             cl_single(icx)=0  
             goto 10  
          endif  
 *     ----------------------------------------------------  
 *     cut BAD (X VIEW)              
 *     ----------------------------------------------------  
          badseed=BAD(VIEW(icx),nvk(MAXS(icx)),nst(MAXS(icx)))  
          ifirst=INDSTART(icx)  
          if(icx.ne.nclstr1) then  
             ilast=INDSTART(icx+1)-1  
          else  
             ilast=TOTCLLENGTH  
          endif  
          badclx=badseed  
          do igood=-ngoodstr,ngoodstr  
             ibad=1  
             if((INDMAX(icx)+igood).gt.ifirst.and.  
      $           (INDMAX(icx)+igood).lt.ilast.and.  
      $           .true.)then  
                ibad=BAD(VIEW(icx),  
      $              nvk(MAXS(icx)+igood),  
      $              nst(MAXS(icx)+igood))  
             endif  
             badclx=badclx*ibad  
          enddo  
 *     ----------------------------------------------------  
 *     >>> eliminato il taglio sulle BAD <<<  
 *     ----------------------------------------------------  
 c     if(badcl.eq.0)then  
 c     cl_single(icx)=0  
 c     goto 10  
 c     endif  
 *     ----------------------------------------------------  
           
          cl_good(icx)=1  
          nplx=npl(VIEW(icx))  
          nldx=nld(MAXS(icx),VIEW(icx))  
           
          do icy=1,nclstr1       !loop on cluster (Y)  
             if(mod(VIEW(icy),2).eq.0)goto 20  
               
 *     ----------------------------------------------------  
 *     cut on charge (Y VIEW)  
 *     ----------------------------------------------------  
             if(dedx(icy).lt.dedx_y_min)then  
                cl_single(icy)=0  
                goto 20  
             endif  
 *     ----------------------------------------------------  
 *     cut BAD (Y VIEW)              
 *     ----------------------------------------------------  
             badseed=BAD(VIEW(icy),nvk(MAXS(icy)),nst(MAXS(icy)))  
             ifirst=INDSTART(icy)  
             if(icy.ne.nclstr1) then  
                ilast=INDSTART(icy+1)-1  
             else  
                ilast=TOTCLLENGTH  
             endif  
             badcly=badseed  
             do igood=-ngoodstr,ngoodstr  
                ibad=1  
                if((INDMAX(icy)+igood).gt.ifirst.and.  
      $              (INDMAX(icy)+igood).lt.ilast.and.  
      $              .true.)  
      $              ibad=BAD(VIEW(icy),  
      $              nvk(MAXS(icy)+igood),  
      $              nst(MAXS(icy)+igood))  
                badcly=badcly*ibad  
             enddo  
 *     ----------------------------------------------------  
 *     >>> eliminato il taglio sulle BAD <<<  
 *     ----------------------------------------------------  
 c     if(badcl.eq.0)then  
 c     cl_single(icy)=0  
 c     goto 20  
 c     endif  
 *     ----------------------------------------------------  
               
             cl_good(icy)=1                    
             nply=npl(VIEW(icy))  
             nldy=nld(MAXS(icy),VIEW(icy))  
               
 *     ----------------------------------------------  
 *     CONDITION TO FORM A COUPLE  
 *     ----------------------------------------------  
 *     geometrical consistency (same plane and ladder)  
             if(nply.eq.nplx.and.nldy.eq.nldx)then  
 *     charge correlation  
 *     (modified to be applied only below saturation... obviously)  
   
 *     -------------------------------------------------------------  
 *     >>> eliminata (TEMPORANEAMENTE) la correlazione di carica <<<  
 *     -------------------------------------------------------------  
                if(  .not.(dedx(icy).gt.chsaty.and.dedx(icx).gt.chsatx)  
      $              .and.  
      $              .not.(dedx(icy).lt.chmipy.and.dedx(icx).lt.chmipx)  
      $              .and.  
      $              (badclx.eq.1.and.badcly.eq.1)  
      $              .and.  
      $              .true.)then  
   
                   ddd=(dedx(icy)  
      $                 -kch(nplx,nldx)*dedx(icx)-cch(nplx,nldx))  
                   ddd=ddd/sqrt(kch(nplx,nldx)**2+1)  
   
 c                  cut = chcut * sch(nplx,nldx)  
   
                   sss=(kch(nplx,nldx)*dedx(icy)+dedx(icx)  
      $                 -kch(nplx,nldx)*cch(nplx,nldx))  
                   sss=sss/sqrt(kch(nplx,nldx)**2+1)  
                   cut = chcut * (16 + sss/50.)  
   
                   if(abs(ddd).gt.cut)then  
                      goto 20    !charge not consistent  
                   endif  
                endif  
                 
 *     ------------------> COUPLE <------------------  
 *     check to do not overflow vector dimentions  
 c$$$               if(ncp_plane(nplx).gt.ncouplemax)then  
 c$$$                  if(DEBUG)print*,  
 c$$$     $                    ' ** warning ** number of identified'//  
 c$$$     $                    ' couples on plane ',nplx,  
 c$$$     $                    ' exceeds vector dimention'//  
 c$$$     $                    ' ( ',ncouplemax,' )'  
 c$$$c     good2=.false.  
 c$$$c     goto 880   !fill ntp and go to next event  
 c$$$                  iflag=1  
 c$$$                  return  
 c$$$               endif  
                 
                if(ncp_plane(nplx).eq.ncouplemax)then  
                   if(verbose)print*,  
      $                 '** warning ** number of identified '//  
      $                 'couples on plane ',nplx,  
      $                 'exceeds vector dimention '  
      $                 ,'( ',ncouplemax,' )'  
 c     good2=.false.  
 c     goto 880   !fill ntp and go to next event                      
                   iflag=1  
                   return  
                endif  
                 
                ncp_plane(nplx) = ncp_plane(nplx) + 1  
                clx(nplx,ncp_plane(nplx))=icx  
                cly(nply,ncp_plane(nplx))=icy  
                cl_single(icx)=0  
                cl_single(icy)=0  
             endif                                
 *     ----------------------------------------------  
   
  20         continue  
          enddo                  !end loop on clusters(Y)  
           
  10      continue  
       enddo                     !end loop on clusters(X)  
         
         
       do icl=1,nclstr1  
          if(cl_single(icl).eq.1)then  
             ip=npl(VIEW(icl))  
             ncls(ip)=ncls(ip)+1  
             cls(ip,ncls(ip))=icl  
          endif  
1873        enddo        enddo
1874                
1875          *     count number of cluster per view
1876        if(DEBUG)then        do icl=1,nclstr1
1877           print*,'clusters  ',nclstr1           ncl_view(VIEW(icl)) = ncl_view(VIEW(icl)) + 1        
          print*,'good    ',(cl_good(i),i=1,nclstr1)  
          print*,'singles ',(cl_single(i),i=1,nclstr1)  
          print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)  
       endif  
         
       do ip=1,6  
          ncp_tot=ncp_tot+ncp_plane(ip)  
       enddo  
 c     if(ncp_tot.gt.ncp_max)goto 100!next event (TEMPORANEO!!!)  
         
       if(ncp_tot.gt.ncp_max)then  
          if(verbose)print*,  
      $           '** warning ** number of identified '//  
      $           'couples exceeds upper limit for Hough tr. '  
      $           ,'( ',ncp_max,' )'              
 c            good2=.false.  
 c     goto 880       !fill ntp and go to next event  
          iflag=1  
          return  
       endif  
         
       return  
       end  
         
 ***************************************************  
 *                                                 *  
 *                                                 *  
 *                                                 *  
 *                                                 *  
 *                                                 *  
 *                                                 *  
 **************************************************  
       subroutine cl_to_couples_nocharge(iflag)  
   
       include 'commontracker.f'  
       include 'common_momanhough.f'  
       include 'momanhough_init.f'  
       include 'calib.f'  
       include 'level1.f'  
   
 c      logical DEBUG  
 c      common/dbg/DEBUG  
   
 *     output flag  
 *     --------------  
 *     0 = good event  
 *     1 = bad event  
 *     --------------  
       integer iflag  
   
       integer badseed,badcl  
   
 *     init variables  
       ncp_tot=0  
       do ip=1,nplanes  
          do ico=1,ncouplemax  
             clx(ip,ico)=0  
             cly(ip,ico)=0  
          enddo  
          ncp_plane(ip)=0  
          do icl=1,nclstrmax_level2  
             cls(ip,icl)=1  
          enddo  
          ncls(ip)=0  
1878        enddo        enddo
1879        do icl=1,nclstrmax_level2  *     mask views with too many clusters
1880           cl_single(icl)=1        do iv=1,nviews
1881           cl_good(icl)=0           if( ncl_view(iv).gt. nclusterlimit)then
1882    c            mask_view(iv) = 1
1883                mask_view(iv) = mask_view(iv) + 2**0
1884                if(DEBUG.EQ.1)
1885         $        print*,' * WARNING * cl_to_couple: n.clusters > '
1886         $        ,nclusterlimit,' on view ', iv,' --> masked!'
1887             endif
1888        enddo        enddo
1889          
1890    
1891  *     start association  *     start association
1892        ncouples=0        ncouples=0
1893        do icx=1,nclstr1          !loop on cluster (X)        do icx=1,nclstr1          !loop on cluster (X)
1894           if(mod(VIEW(icx),2).eq.1)goto 10           if(mod(VIEW(icx),2).eq.1)goto 10
1895                    
1896  *     ----------------------------------------------------  *     ----------------------------------------------------
1897    *     jump masked views (X VIEW)
1898    *     ----------------------------------------------------
1899             if( mask_view(VIEW(icx)).ne.0 ) goto 10
1900    *     ----------------------------------------------------
1901  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1902           if(dedx(icx).lt.dedx_x_min)then  *     ----------------------------------------------------
1903             if(sgnl(icx).lt.dedx_x_min)then
1904              cl_single(icx)=0              cl_single(icx)=0
1905              goto 10              goto 10
1906           endif           endif
1907    *     ----------------------------------------------------
1908  *     cut BAD (X VIEW)              *     cut BAD (X VIEW)            
1909    *     ----------------------------------------------------
1910           badseed=BAD(VIEW(icx),nvk(MAXS(icx)),nst(MAXS(icx)))           badseed=BAD(VIEW(icx),nvk(MAXS(icx)),nst(MAXS(icx)))
1911           ifirst=INDSTART(icx)           ifirst=INDSTART(icx)
1912           if(icx.ne.nclstr1) then           if(icx.ne.nclstr1) then
# Line 1962  c      common/dbg/DEBUG Line 1914  c      common/dbg/DEBUG
1914           else           else
1915              ilast=TOTCLLENGTH              ilast=TOTCLLENGTH
1916           endif           endif
1917           badcl=badseed           badclx=badseed
1918           do igood=-ngoodstr,ngoodstr           do igood=-ngoodstr,ngoodstr
1919              ibad=1              ibad=1
1920              if((INDMAX(icx)+igood).gt.ifirst.and.              if((INDMAX(icx)+igood).gt.ifirst.and.
# Line 1972  c      common/dbg/DEBUG Line 1924  c      common/dbg/DEBUG
1924       $              nvk(MAXS(icx)+igood),       $              nvk(MAXS(icx)+igood),
1925       $              nst(MAXS(icx)+igood))       $              nst(MAXS(icx)+igood))
1926              endif              endif
1927              badcl=badcl*ibad              badclx=badclx*ibad
1928           enddo           enddo
1929           if(badcl.eq.0)then     !<<<<<<<<<<<<<< BAD cut  *     ----------------------------------------------------
1930              cl_single(icx)=0    !<<<<<<<<<<<<<< BAD cut  *     >>> eliminato il taglio sulle BAD <<<
1931              goto 10             !<<<<<<<<<<<<<< BAD cut  *     ----------------------------------------------------
1932           endif                  !<<<<<<<<<<<<<< BAD cut  c     if(badcl.eq.0)then
1933    c     cl_single(icx)=0
1934    c     goto 10
1935    c     endif
1936  *     ----------------------------------------------------  *     ----------------------------------------------------
1937                    
1938           cl_good(icx)=1           cl_good(icx)=1
# Line 1988  c      common/dbg/DEBUG Line 1943  c      common/dbg/DEBUG
1943              if(mod(VIEW(icy),2).eq.0)goto 20              if(mod(VIEW(icy),2).eq.0)goto 20
1944                            
1945  *     ----------------------------------------------------  *     ----------------------------------------------------
1946    *     jump masked views (Y VIEW)
1947    *     ----------------------------------------------------
1948                if( mask_view(VIEW(icy)).ne.0 ) goto 20
1949    
1950    *     ----------------------------------------------------
1951  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1952              if(dedx(icy).lt.dedx_y_min)then  *     ----------------------------------------------------
1953                if(sgnl(icy).lt.dedx_y_min)then
1954                 cl_single(icy)=0                 cl_single(icy)=0
1955                 goto 20                 goto 20
1956              endif              endif
1957    *     ----------------------------------------------------
1958  *     cut BAD (Y VIEW)              *     cut BAD (Y VIEW)            
1959    *     ----------------------------------------------------
1960              badseed=BAD(VIEW(icy),nvk(MAXS(icy)),nst(MAXS(icy)))              badseed=BAD(VIEW(icy),nvk(MAXS(icy)),nst(MAXS(icy)))
1961              ifirst=INDSTART(icy)              ifirst=INDSTART(icy)
1962              if(icy.ne.nclstr1) then              if(icy.ne.nclstr1) then
# Line 2001  c      common/dbg/DEBUG Line 1964  c      common/dbg/DEBUG
1964              else              else
1965                 ilast=TOTCLLENGTH                 ilast=TOTCLLENGTH
1966              endif              endif
1967              badcl=badseed              badcly=badseed
1968              do igood=-ngoodstr,ngoodstr              do igood=-ngoodstr,ngoodstr
1969                 ibad=1                 ibad=1
1970                 if((INDMAX(icy)+igood).gt.ifirst.and.                 if((INDMAX(icy)+igood).gt.ifirst.and.
# Line 2010  c      common/dbg/DEBUG Line 1973  c      common/dbg/DEBUG
1973       $              ibad=BAD(VIEW(icy),       $              ibad=BAD(VIEW(icy),
1974       $              nvk(MAXS(icy)+igood),       $              nvk(MAXS(icy)+igood),
1975       $              nst(MAXS(icy)+igood))       $              nst(MAXS(icy)+igood))
1976                 badcl=badcl*ibad                 badcly=badcly*ibad
1977              enddo              enddo
             if(badcl.eq.0)then  !<<<<<<<<<<<<<< BAD cut  
                cl_single(icy)=0 !<<<<<<<<<<<<<< BAD cut  
                goto 20          !<<<<<<<<<<<<<< BAD cut  
             endif               !<<<<<<<<<<<<<< BAD cut  
1978  *     ----------------------------------------------------  *     ----------------------------------------------------
1979                *     >>> eliminato il taglio sulle BAD <<<
1980    *     ----------------------------------------------------
1981    c     if(badcl.eq.0)then
1982    c     cl_single(icy)=0
1983    c     goto 20
1984    c     endif
1985    *     ----------------------------------------------------
1986                            
1987              cl_good(icy)=1                                cl_good(icy)=1                  
1988              nply=npl(VIEW(icy))              nply=npl(VIEW(icy))
# Line 2028  c      common/dbg/DEBUG Line 1993  c      common/dbg/DEBUG
1993  *     ----------------------------------------------  *     ----------------------------------------------
1994  *     geometrical consistency (same plane and ladder)  *     geometrical consistency (same plane and ladder)
1995              if(nply.eq.nplx.and.nldy.eq.nldx)then              if(nply.eq.nplx.and.nldy.eq.nldx)then
1996  *     charge correlation  *     charge correlation
1997  *     ===========================================================  *     (modified to be applied only below saturation... obviously)
1998  *     this version of the subroutine is used for the calibration  
1999  *     thus charge-correlation selection is obviously removed                 if(  .not.(sgnl(icy).gt.chsaty.and.sgnl(icx).gt.chsatx)
2000  *     ===========================================================       $              .and.
2001  c$$$               ddd=(dedx(icy)       $              .not.(sgnl(icy).lt.chmipy.and.sgnl(icx).lt.chmipx)
2002  c$$$     $              -kch(nplx,nldx)*dedx(icx)-cch(nplx,nldx))       $              .and.
2003  c$$$               ddd=ddd/sqrt(kch(nplx,nldx)**2+1)       $              (badclx.eq.1.and.badcly.eq.1)
2004  c$$$               cut=chcut*sch(nplx,nldx)       $              .and.
2005  c$$$               if(abs(ddd).gt.cut)goto 20 !charge not consistent       $              .true.)then
2006  *     ===========================================================  
2007                                    ddd=(sgnl(icy)
2008                       $                 -kch(nplx,nldx)*sgnl(icx)-cch(nplx,nldx))
2009  *     ------------------> COUPLE <------------------                    ddd=ddd/sqrt(kch(nplx,nldx)**2+1)
2010  *     check to do not overflow vector dimentions  
2011  c$$$               if(ncp_plane(nplx).gt.ncouplemax)then  c                  cut = chcut * sch(nplx,nldx)
2012  c$$$                  if(DEBUG)print*,  
2013  c$$$     $                    ' ** warning ** number of identified'//                    sss=(kch(nplx,nldx)*sgnl(icy)+sgnl(icx)
2014  c$$$     $                    ' couples on plane ',nplx,       $                 -kch(nplx,nldx)*cch(nplx,nldx))
2015  c$$$     $                    ' exceeds vector dimention'//                    sss=sss/sqrt(kch(nplx,nldx)**2+1)
2016  c$$$     $                    ' ( ',ncouplemax,' )'                    cut = chcut * (16 + sss/50.)
2017  c$$$c     good2=.false.  
2018  c$$$c     goto 880   !fill ntp and go to next event                    if(abs(ddd).gt.cut)then
2019  c$$$                  iflag=1                       goto 20    !charge not consistent
2020  c$$$                  return                    endif
2021  c$$$               endif                 endif
2022                  
2023                 if(ncp_plane(nplx).eq.ncouplemax)then                 if(ncp_plane(nplx).gt.ncouplemax)then
2024                    if(verbose)print*,                    if(verbose.eq.1)print*,
2025       $                 '** warning ** number of identified '//       $                 '** warning ** number of identified '//
2026       $                 'couples on plane ',nplx,       $                 'couples on plane ',nplx,
2027       $                 'exceeds vector dimention '       $                 'exceeds vector dimention '
2028       $                 ,'( ',ncouplemax,' )'       $                 ,'( ',ncouplemax,' ) --> masked!'
2029  c     good2=.false.  c                  mask_view(nviewx(nplx)) = 2
2030  c     goto 880   !fill ntp and go to next event                      c                  mask_view(nviewy(nply)) = 2
2031                    iflag=1                    mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1
2032                    return                    mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1
2033                      goto 10
2034                 endif                 endif
2035                                
2036    *     ------------------> COUPLE <------------------
2037                 ncp_plane(nplx) = ncp_plane(nplx) + 1                 ncp_plane(nplx) = ncp_plane(nplx) + 1
2038                 clx(nplx,ncp_plane(nplx))=icx                 clx(nplx,ncp_plane(nplx))=icx
2039                 cly(nply,ncp_plane(nplx))=icy                 cly(nply,ncp_plane(nplx))=icy
2040                 cl_single(icx)=0                 cl_single(icx)=0
2041                 cl_single(icy)=0                 cl_single(icy)=0
             endif                                
2042  *     ----------------------------------------------  *     ----------------------------------------------
2043    
2044                endif                              
2045    
2046   20         continue   20         continue
2047           enddo                  !end loop on clusters(Y)           enddo                  !end loop on clusters(Y)
2048                    
# Line 2091  c     goto 880   !fill ntp and go to nex Line 2059  c     goto 880   !fill ntp and go to nex
2059        enddo        enddo
2060                
2061                
2062        if(DEBUG)then        if(DEBUG.EQ.1)then
2063           print*,'clusters  ',nclstr1           print*,'clusters  ',nclstr1
2064           print*,'good    ',(cl_good(i),i=1,nclstr1)           print*,'good    ',(cl_good(i),i=1,nclstr1)
2065           print*,'singles ',(cl_single(i),i=1,nclstr1)           print*,'singlets',(cl_single(i),i=1,nclstr1)
2066           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
2067        endif        endif
2068                
2069        do ip=1,6        do ip=1,6
2070           ncp_tot=ncp_tot+ncp_plane(ip)           ncp_tot = ncp_tot + ncp_plane(ip)
2071        enddo        enddo
 c     if(ncp_tot.gt.ncp_max)goto 100!next event (TEMPORANEO!!!)  
         
       if(ncp_tot.gt.ncp_max)then  
          if(verbose)print*,  
      $           '** warning ** number of identified '//  
      $           'couples exceeds upper limit for Hough tr. '  
      $           ,'( ',ncp_max,' )'              
 c            good2=.false.  
 c     goto 880       !fill ntp and go to next event  
          iflag=1  
          return  
       endif  
2072                
2073        return        return
2074        end        end
   
2075                
2076  ***************************************************  ***************************************************
2077  *                                                 *  *                                                 *
# Line 2128  c     goto 880       !fill ntp and go to Line 2083  c     goto 880       !fill ntp and go to
2083  **************************************************  **************************************************
2084    
2085        subroutine cp_to_doubtrip(iflag)        subroutine cp_to_doubtrip(iflag)
 c*****************************************************  
 c     02/02/2006 modified by Elena Vannuccini --> (1)  
 c*****************************************************  
2086    
2087        include 'commontracker.f'        include 'commontracker.f'
2088          include 'level1.f'
2089        include 'common_momanhough.f'        include 'common_momanhough.f'
       include 'momanhough_init.f'  
2090        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
2091        include 'common_mini_2.f'        include 'common_mini_2.f'
2092        include 'calib.f'        include 'calib.f'
       include 'level1.f'  
2093    
 c      logical DEBUG  
 c      common/dbg/DEBUG  
2094    
2095  *     output flag  *     output flag
2096  *     --------------  *     --------------
# Line 2173  c      double precision xm3,ym3,zm3 Line 2122  c      double precision xm3,ym3,zm3
2122        real xc,zc,radius        real xc,zc,radius
2123  *     -----------------------------  *     -----------------------------
2124    
2125          if(DEBUG.EQ.1)print*,'cp_to_doubtrip:'
2126    
2127    *     --------------------------------------------
2128    *     put a limit to the maximum number of couples
2129    *     per plane, in order to apply hough transform
2130    *     (couples recovered during track refinement)
2131    *     --------------------------------------------
2132          do ip=1,nplanes
2133             if(ncp_plane(ip).gt.ncouplelimit)then
2134    c            mask_view(nviewx(ip)) = 8
2135    c            mask_view(nviewy(ip)) = 8
2136                mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7
2137                mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7
2138             endif
2139          enddo
2140    
2141    
2142        ndblt=0                   !number of doublets        ndblt=0                   !number of doublets
2143        ntrpt=0                   !number of triplets        ntrpt=0                   !number of triplets
2144                
2145        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1
2146           do is1=1,2             !loop on sensors - COPPIA 1           if(  mask_view(nviewx(ip1)).ne.0 .or.
2147                     $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
2148             do is1=1,2             !loop on sensors - COPPIA 1            
2149              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
2150                 icx1=clx(ip1,icp1)                 icx1=clx(ip1,icp1)
2151                 icy1=cly(ip1,icp1)                 icy1=cly(ip1,icp1)
2152  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
2153                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
2154                   call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
2155                 xm1=xPAM                 xm1=xPAM
2156                 ym1=yPAM                 ym1=yPAM
2157                 zm1=zPAM                                   zm1=zPAM                  
2158  c     print*,'***',is1,xm1,ym1,zm1  c     print*,'***',is1,xm1,ym1,zm1
2159    
2160                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
2161                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                    if(  mask_view(nviewx(ip2)).ne.0 .or.
2162                             $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
2163                      do is2=1,2    !loop on sensors -ndblt COPPIA 2                    
2164                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
2165                          icx2=clx(ip2,icp2)                          icx2=clx(ip2,icp2)
2166                          icy2=cly(ip2,icp2)                          icy2=cly(ip2,icp2)
2167  c                        call xyz_PAM  c                        call xyz_PAM
2168  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
2169    c                        call xyz_PAM
2170    c     $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.) !(1)
2171                          call xyz_PAM                          call xyz_PAM
2172       $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.) !(1)       $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.,0.,0.)
2173                          xm2=xPAM                          xm2=xPAM
2174                          ym2=yPAM                          ym2=yPAM
2175                          zm2=zPAM                          zm2=zPAM
# Line 2209  c     $                       (icx2,icy2 Line 2179  c     $                       (icx2,icy2
2179  *     (2 couples needed)  *     (2 couples needed)
2180  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2181                          if(ndblt.eq.ndblt_max)then                          if(ndblt.eq.ndblt_max)then
2182                             if(verbose)print*,                             if(verbose.eq.1)print*,
2183       $                          '** warning ** number of identified '//       $                          '** warning ** number of identified '//
2184       $                          'doublets exceeds vector dimention '       $                          'doublets exceeds vector dimention '
2185       $                          ,'( ',ndblt_max,' )'       $                          ,'( ',ndblt_max,' )'
2186  c                           good2=.false.  c                           good2=.false.
2187  c                           goto 880 !fill ntp and go to next event  c                           goto 880 !fill ntp and go to next event
2188                               do iv=1,12
2189    c                              mask_view(iv) = 3
2190                                  mask_view(iv) = mask_view(iv)+ 2**2
2191                               enddo
2192                             iflag=1                             iflag=1
2193                             return                             return
2194                          endif                          endif
# Line 2248  c$$$ Line 2222  c$$$
2222  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2223    
2224    
2225                          if(ip2.eq.nplanes)goto 30 !no possible combination with 3 couples                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2226    
2227                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2228                               if(  mask_view(nviewx(ip3)).ne.0 .or.
2229         $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2230                             do is3=1,2 !loop on sensors - COPPIA 3                             do is3=1,2 !loop on sensors - COPPIA 3
2231                                                                
2232                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
# Line 2257  c$$$ Line 2234  c$$$
2234                                   icy3=cly(ip3,icp3)                                   icy3=cly(ip3,icp3)
2235  c                                 call xyz_PAM  c                                 call xyz_PAM
2236  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2237    c                                 call xyz_PAM
2238    c     $                               (icx3,icy3,is3,PFAdef,PFAdef,0.,0.) !(1)
2239                                   call xyz_PAM                                   call xyz_PAM
2240       $                               (icx3,icy3,is3,PFAdef,PFAdef,0.,0.) !(1)       $                                (icx3,icy3,is3,PFAdef,PFAdef
2241         $                                ,0.,0.,0.,0.)
2242                                   xm3=xPAM                                   xm3=xPAM
2243                                   ym3=yPAM                                   ym3=yPAM
2244                                   zm3=zPAM                                   zm3=zPAM
2245  *     find the circle passing through the three points  *     find the circle passing through the three points
2246    c$$$                                 call tricircle(3,xp,zp,angp,resp,chi
2247    c$$$     $                                ,xc,zc,radius,iflag)
2248                                     iflag = DEBUG
2249                                   call tricircle(3,xp,zp,angp,resp,chi                                   call tricircle(3,xp,zp,angp,resp,chi
2250       $                                ,xc,zc,radius,iflag)       $                                ,xc,zc,radius,iflag)
2251  c     print*,xc,zc,radius  c     print*,xc,zc,radius
# Line 2279  c     $                                 Line 2262  c     $                                
2262  *     (3 couples needed)  *     (3 couples needed)
2263  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2264                                   if(ntrpt.eq.ntrpt_max)then                                   if(ntrpt.eq.ntrpt_max)then
2265                                      if(verbose)print*,                                      if(verbose.eq.1)print*,
2266       $                     '** warning ** number of identified '//       $                     '** warning ** number of identified '//
2267       $                     'triplets exceeds vector dimention '       $                     'triplets exceeds vector dimention '
2268       $                    ,'( ',ntrpt_max,' )'       $                    ,'( ',ntrpt_max,' )'
2269  c                                    good2=.false.  c                                    good2=.false.
2270  c                                    goto 880 !fill ntp and go to next event  c                                    goto 880 !fill ntp and go to next event
2271                                        do iv=1,nviews
2272    c                                       mask_view(iv) = 4
2273                                           mask_view(iv)=mask_view(iv)+ 2**3
2274                                        enddo
2275                                      iflag=1                                      iflag=1
2276                                      return                                      return
2277                                   endif                                   endif
# Line 2323  c     print*,alfaxz1(ntrpt),alfaxz2(ntrp Line 2310  c     print*,alfaxz1(ntrpt),alfaxz2(ntrp
2310                                endif                                endif
2311                             enddo !end loop on COPPIA 3                             enddo !end loop on COPPIA 3
2312                          enddo   !end loop on sensors - COPPIA 3                          enddo   !end loop on sensors - COPPIA 3
2313     30                     continue
2314                       enddo      !end loop on planes  - COPPIA 3                       enddo      !end loop on planes  - COPPIA 3
2315   30                  continue   31                  continue
2316                                            
2317   1                enddo         !end loop on COPPIA 2   1                enddo         !end loop on COPPIA 2
2318                 enddo            !end loop on sensors - COPPIA 2                 enddo            !end loop on sensors - COPPIA 2
2319     20            continue
2320              enddo               !end loop on planes  - COPPIA 2              enddo               !end loop on planes  - COPPIA 2
2321                            
2322           enddo                  !end loop on COPPIA1           enddo                  !end loop on COPPIA1
2323        enddo                     !end loop on sensors - COPPIA 1        enddo                     !end loop on sensors - COPPIA 1
2324     10   continue
2325        enddo                     !end loop on planes  - COPPIA 1        enddo                     !end loop on planes  - COPPIA 1
2326                
2327        if(DEBUG)then        if(DEBUG.EQ.1)then
2328           print*,'--- doublets ',ndblt           print*,'--- doublets ',ndblt
2329           print*,'--- triplets ',ntrpt           print*,'--- triplets ',ntrpt
2330        endif        endif
# Line 2359  c     goto 880               !ntp fill Line 2349  c     goto 880               !ntp fill
2349        subroutine doub_to_YZcloud(iflag)        subroutine doub_to_YZcloud(iflag)
2350    
2351        include 'commontracker.f'        include 'commontracker.f'
2352          include 'level1.f'
2353        include 'common_momanhough.f'        include 'common_momanhough.f'
2354        include 'momanhough_init.f'  c      include 'momanhough_init.f'
2355    
 c      logical DEBUG  
 c      common/dbg/DEBUG  
2356    
2357  *     output flag  *     output flag
2358  *     --------------  *     --------------
# Line 2382  c      common/dbg/DEBUG Line 2371  c      common/dbg/DEBUG
2371        integer cp_useds1(ncouplemaxtot) ! sensor 1        integer cp_useds1(ncouplemaxtot) ! sensor 1
2372        integer cp_useds2(ncouplemaxtot) ! sensor 2        integer cp_useds2(ncouplemaxtot) ! sensor 2
2373    
2374          if(DEBUG.EQ.1)print*,'doub_to_YZcloud:'
2375    
2376  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2377  *     classification of DOUBLETS  *     classification of DOUBLETS
# Line 2395  c      common/dbg/DEBUG Line 2385  c      common/dbg/DEBUG
2385        distance=0        distance=0
2386        nclouds_yz=0              !number of clouds        nclouds_yz=0              !number of clouds
2387        npt_tot=0        npt_tot=0
2388          nloop=0                  
2389     90   continue                  
2390        do idb1=1,ndblt           !loop (1) on DOUBLETS        do idb1=1,ndblt           !loop (1) on DOUBLETS
2391           if(db_used(idb1).eq.1)goto 2228 !db already included in a cloud           if(db_used(idb1).eq.1)goto 2228 !db already included in a cloud
2392                            
# Line 2498  c     print*,'*   idbref,idb2 ',idbref,i Line 2490  c     print*,'*   idbref,idb2 ',idbref,i
2490              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2491           enddo           enddo
2492  c     print*,'>>>> ',ncpused,npt,nplused  c     print*,'>>>> ',ncpused,npt,nplused
2493           if(ncpused.lt.ncpyz_min)goto 2228 !next doublet  c         if(ncpused.lt.ncpyz_min)goto 2228 !next doublet
2494           if(npt.lt.nptyz_min)goto 2228 !next doublet           if(npt.lt.nptyz_min)goto 2228 !next doublet
2495           if(nplused.lt.nplyz_min)goto 2228 !next doublet           if(nplused.lt.nplyz_min)goto 2228 !next doublet
2496                    
# Line 2506  c     print*,'>>>> ',ncpused,npt,nplused Line 2498  c     print*,'>>>> ',ncpused,npt,nplused
2498  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2499    
2500           if(nclouds_yz.ge.ncloyz_max)then           if(nclouds_yz.ge.ncloyz_max)then
2501              if(verbose)print*,              if(verbose.eq.1)print*,
2502       $           '** warning ** number of identified '//       $           '** warning ** number of identified '//
2503       $           'YZ clouds exceeds vector dimention '       $           'YZ clouds exceeds vector dimention '
2504       $           ,'( ',ncloyz_max,' )'       $           ,'( ',ncloyz_max,' )'
2505  c               good2=.false.  c               good2=.false.
2506  c     goto 880         !fill ntp and go to next event  c     goto 880         !fill ntp and go to next event
2507                do iv=1,nviews
2508    c               mask_view(iv) = 5
2509                   mask_view(iv) = mask_view(iv) + 2**4
2510                enddo
2511              iflag=1              iflag=1
2512              return              return
2513           endif           endif
# Line 2530  c     ptcloud_yz_nt(nclouds_yz)=npt Line 2526  c     ptcloud_yz_nt(nclouds_yz)=npt
2526  c     print*,'>> ',ipt,db_all(ipt)  c     print*,'>> ',ipt,db_all(ipt)
2527           enddo             enddo  
2528           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2529           if(DEBUG)then           if(DEBUG.EQ.1)then
2530              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'
2531              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2532              print*,'- alfayz1 ',alfayz1_av(nclouds_yz)              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)
2533              print*,'- alfayz2 ',alfayz2_av(nclouds_yz)              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)
2534              print*,'cp_useds1 ',(cp_useds1(icp),icp=1,ncp_tot)              print*,'cp_useds1  ',(cp_useds1(icp),icp=1,ncp_tot)
2535              print*,'cp_useds2 ',(cp_useds2(icp),icp=1,ncp_tot)              print*,'cp_useds2  ',(cp_useds2(icp),icp=1,ncp_tot)
2536              print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)              print*,'cpcloud_yz '
2537         $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)
2538                print*,'hit_plane  ',(hit_plane(ip),ip=1,nplanes)
2539  c$$$            print*,'nt-uple: ptcloud_yz(',nclouds_yz,') = '  c$$$            print*,'nt-uple: ptcloud_yz(',nclouds_yz,') = '
2540  c$$$     $           ,ptcloud_yz(nclouds_yz)  c$$$     $           ,ptcloud_yz(nclouds_yz)
2541  c$$$            print*,'nt-uple: db_cloud(...) = '  c$$$            print*,'nt-uple: db_cloud(...) = '
# Line 2549  c$$$     $           ,(db_cloud(iii),iii Line 2547  c$$$     $           ,(db_cloud(iii),iii
2547        enddo                     !end loop (1) on DOUBLETS        enddo                     !end loop (1) on DOUBLETS
2548                
2549                
2550        if(DEBUG)then        if(nloop.lt.nstepy)then      
2551            cutdistyz = cutdistyz+cutystep
2552            nloop     = nloop+1          
2553            goto 90                
2554          endif                    
2555          
2556          if(DEBUG.EQ.1)then
2557           print*,'---------------------- '           print*,'---------------------- '
2558           print*,'Y-Z total clouds ',nclouds_yz           print*,'Y-Z total clouds ',nclouds_yz
2559           print*,' '           print*,' '
# Line 2575  c$$$     $           ,(db_cloud(iii),iii Line 2579  c$$$     $           ,(db_cloud(iii),iii
2579        subroutine trip_to_XZcloud(iflag)        subroutine trip_to_XZcloud(iflag)
2580    
2581        include 'commontracker.f'        include 'commontracker.f'
2582          include 'level1.f'
2583        include 'common_momanhough.f'        include 'common_momanhough.f'
2584        include 'momanhough_init.f'  c      include 'momanhough_init.f'
2585    
 c      logical DEBUG  
 c      common/dbg/DEBUG  
2586    
2587  *     output flag  *     output flag
2588  *     --------------  *     --------------
# Line 2599  c      common/dbg/DEBUG Line 2602  c      common/dbg/DEBUG
2602        integer cp_useds1(ncouplemaxtot) ! sensor 1        integer cp_useds1(ncouplemaxtot) ! sensor 1
2603        integer cp_useds2(ncouplemaxtot) ! sensor 2        integer cp_useds2(ncouplemaxtot) ! sensor 2
2604    
2605          if(DEBUG.EQ.1)print*,'trip_to_XZcloud:'
2606    
2607  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2608  *     classification of TRIPLETS  *     classification of TRIPLETS
2609  *     according to distance in parameter space  *     according to distance in parameter space
# Line 2610  c      common/dbg/DEBUG Line 2615  c      common/dbg/DEBUG
2615        distance=0        distance=0
2616        nclouds_xz=0              !number of clouds                nclouds_xz=0              !number of clouds        
2617        npt_tot=0                 !total number of selected triplets        npt_tot=0                 !total number of selected triplets
2618          nloop=0                  
2619     91   continue                  
2620        do itr1=1,ntrpt           !loop (1) on TRIPLETS        do itr1=1,ntrpt           !loop (1) on TRIPLETS
2621           if(tr_used(itr1).eq.1)goto 22288 !already included in a cloud           if(tr_used(itr1).eq.1)goto 22288 !already included in a cloud
2622  c     print*,'--------------'  c     print*,'--------------'
# Line 2654  c         tr_temp(1)=itr1 Line 2661  c         tr_temp(1)=itr1
2661       $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2                     $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2              
2662                 distance = sqrt(distance)                 distance = sqrt(distance)
2663                                
2664                 if(distance.lt.cutdistxz)then  *     ------------------------------------------------------------------------
2665    *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE
2666    *     ------------------------------------------------------------------------
2667    *     (added in august 2007)
2668                   istrimage=0
2669                   if(
2670         $              abs(cpxz1(itrref)).eq.abs(cpxz1(itr2)).and.
2671         $              abs(cpxz2(itrref)).eq.abs(cpxz2(itr2)).and.
2672         $              abs(cpxz3(itrref)).eq.abs(cpxz3(itr2)).and.
2673         $              .true.)istrimage=1
2674    
2675                   if(distance.lt.cutdistxz.or.istrimage.eq.1)then
2676  c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  c     print*,idb1,idb2,distance,' cloud ',nclouds_yz
2677                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2678                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
# Line 2711  c     print*,'check cp_used' Line 2729  c     print*,'check cp_used'
2729           do ip=1,nplanes           do ip=1,nplanes
2730              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2731           enddo           enddo
2732           if(ncpused.lt.ncpxz_min)goto 22288 !next triplet  c         if(ncpused.lt.ncpxz_min)goto 22288 !next triplet
2733           if(npt.lt.nptxz_min)goto 22288     !next triplet           if(npt.lt.nptxz_min)goto 22288     !next triplet
2734           if(nplused.lt.nplxz_min)goto 22288 !next doublet           if(nplused.lt.nplxz_min)goto 22288 !next triplet
2735                    
2736  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
2737  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2738           if(nclouds_xz.ge.ncloxz_max)then           if(nclouds_xz.ge.ncloxz_max)then
2739              if(verbose)print*,              if(verbose.eq.1)print*,
2740       $           '** warning ** number of identified '//       $           '** warning ** number of identified '//
2741       $           'XZ clouds exceeds vector dimention '       $           'XZ clouds exceeds vector dimention '
2742       $           ,'( ',ncloxz_max,' )'       $           ,'( ',ncloxz_max,' )'
2743  c     good2=.false.  c     good2=.false.
2744  c     goto 880         !fill ntp and go to next event  c     goto 880         !fill ntp and go to next event
2745                do iv=1,nviews
2746    c               mask_view(iv) = 6
2747                   mask_view(iv) =  mask_view(iv) + 2**5
2748                enddo
2749              iflag=1              iflag=1
2750              return              return
2751           endif           endif
# Line 2741  c     goto 880         !fill ntp and go Line 2763  c     goto 880         !fill ntp and go
2763           enddo           enddo
2764           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2765                    
2766           if(DEBUG)then           if(DEBUG.EQ.1)then
2767              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'
2768              print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'                            print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'              
2769              print*,'- alfaxz1 ',alfaxz1_av(nclouds_xz)              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)
2770              print*,'- alfaxz2 ',alfaxz2_av(nclouds_xz)              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)
2771              print*,'- alfaxz3 ',alfaxz3_av(nclouds_xz)              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)
2772              print*,'cp_useds1 ',(cp_useds1(icp),icp=1,ncp_tot)              print*,'cp_useds1  ',(cp_useds1(icp),icp=1,ncp_tot)
2773              print*,'cp_useds2 ',(cp_useds2(icp),icp=1,ncp_tot)              print*,'cp_useds2  ',(cp_useds2(icp),icp=1,ncp_tot)
2774                print*,'cpcloud_xz '
2775         $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)
2776              print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)              print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)
2777  c$$$            print*,'nt-uple: ptcloud_xz(',nclouds_xz,') = '  c$$$            print*,'nt-uple: ptcloud_xz(',nclouds_xz,') = '
2778  c$$$     $           ,ptcloud_xz(nclouds_xz)  c$$$     $           ,ptcloud_xz(nclouds_xz)
# Line 2759  c$$$     $           ,(tr_cloud(iii),iii Line 2783  c$$$     $           ,(tr_cloud(iii),iii
2783  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
2784  22288    continue  22288    continue
2785        enddo                     !end loop (1) on DOUBLETS        enddo                     !end loop (1) on DOUBLETS
2786          
2787        if(DEBUG)then         if(nloop.lt.nstepx)then      
2788             cutdistxz=cutdistxz+cutxstep
2789             nloop=nloop+1          
2790             goto 91                
2791           endif                    
2792          
2793          if(DEBUG.EQ.1)then
2794           print*,'---------------------- '           print*,'---------------------- '
2795           print*,'X-Z total clouds ',nclouds_xz           print*,'X-Z total clouds ',nclouds_xz
2796           print*,' '           print*,' '
# Line 2781  c$$$     $           ,(tr_cloud(iii),iii Line 2811  c$$$     $           ,(tr_cloud(iii),iii
2811  **************************************************  **************************************************
2812    
2813        subroutine clouds_to_ctrack(iflag)        subroutine clouds_to_ctrack(iflag)
 c*****************************************************  
 c     02/02/2006 modified by Elena Vannuccini --> (1)  
 c*****************************************************  
2814    
2815        include 'commontracker.f'        include 'commontracker.f'
2816          include 'level1.f'
2817        include 'common_momanhough.f'        include 'common_momanhough.f'
2818        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
2819        include 'common_mini_2.f'        include 'common_mini_2.f'
2820        include 'common_mech.f'        include 'common_mech.f'
       include 'momanhough_init.f'  
2821    
2822  c      logical DEBUG  
 c      common/dbg/DEBUG  
2823    
2824  *     output flag  *     output flag
2825  *     --------------  *     --------------
# Line 2809  c      common/dbg/DEBUG Line 2835  c      common/dbg/DEBUG
2835  *     -----------------------------------------------------------  *     -----------------------------------------------------------
2836  *     list of matching couples in the combination  *     list of matching couples in the combination
2837  *     between a XZ and YZ cloud  *     between a XZ and YZ cloud
2838        integer cp_match(nplanes,ncouplemax)        integer cp_match(nplanes,2*ncouplemax)
2839        integer ncp_match(nplanes)        integer ncp_match(nplanes)
2840  *     -----------------------------------------------------------  *     -----------------------------------------------------------
2841        integer hit_plane(nplanes)        integer hit_plane(nplanes)
2842  *     -----------------------------------------------------------  *     -----------------------------------------------------------
2843  *     variables for track fitting  *     variables for track fitting
2844        double precision AL_INI(5)        double precision AL_INI(5)
       double precision tath  
2845  *     -----------------------------------------------------------  *     -----------------------------------------------------------
 c      real fitz(nplanes)        !z coordinates of the planes in cm  
2846    
2847          if(DEBUG.EQ.1)print*,'clouds_to_ctrack:'
2848    
2849    
2850        ntracks=0                 !counter of track candidates        ntracks=0                 !counter of track candidates
# Line 2841  c      real fitz(nplanes)        !z coor Line 2866  c      real fitz(nplanes)        !z coor
2866                 enddo                 enddo
2867              enddo              enddo
2868              ncp_ok=0              ncp_ok=0
2869              do icp=1,ncp_tot    !loop on couples              do icp=1,ncp_tot    !loop over couples
2870  *     get info on  *     get info on
2871                 cpintersec(icp)=min(                 cpintersec(icp)=min(
2872       $              cpcloud_yz(iyz,icp),       $              cpcloud_yz(iyz,icp),
# Line 2850  c      real fitz(nplanes)        !z coor Line 2875  c      real fitz(nplanes)        !z coor
2875       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2876       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2877       $              .false.)cpintersec(icp)=0       $              .false.)cpintersec(icp)=0
2878    *     cpintersec is >0 if yz and xz clouds contain the same image of couple icp
2879                 if(cpintersec(icp).ne.0)then                 if(cpintersec(icp).ne.0)then
2880                    ncp_ok=ncp_ok+1                      ncp_ok=ncp_ok+1  
2881                                        
# Line 2882  c      real fitz(nplanes)        !z coor Line 2908  c      real fitz(nplanes)        !z coor
2908                 nplused=nplused+ hit_plane(ip)                 nplused=nplused+ hit_plane(ip)
2909              enddo              enddo
2910                            
             if(nplused.lt.nplxz_min)goto 888 !next doublet  
             if(ncp_ok.lt.ncpok)goto 888 !next cloud  
2911                            
2912              if(DEBUG)then              if(DEBUG.EQ.1)then
2913                 print*,'Combination ',iyz,ixz                 print*,'Combination ',iyz,ixz
2914       $              ,' db ',ptcloud_yz(iyz)       $              ,' db ',ptcloud_yz(iyz)
2915       $              ,' tr ',ptcloud_xz(ixz)       $              ,' tr ',ptcloud_xz(ixz)
2916       $              ,'  -----> # matching couples ',ncp_ok       $              ,'  -----> # matching couples ',ncp_ok
2917              endif              endif
2918    
2919    c            if(nplused.lt.nplxz_min)goto 888 !next combination
2920                if(nplused.lt.nplyz_min)goto 888 !next combination
2921                if(ncp_ok.lt.ncpok)goto 888 !next combination
2922    
2923  c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'  c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'
2924  c$$$  print*,'Configurazione cluster XZ'  c$$$  print*,'Configurazione cluster XZ'
2925  c$$$  print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))  c$$$  print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))
# Line 2909  c$$$  print*,'6 -- ',(cly(6,i),i=1,ncp_p Line 2938  c$$$  print*,'6 -- ',(cly(6,i),i=1,ncp_p
2938  c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'  c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'
2939                            
2940  *     -------> INITIAL GUESS <-------  *     -------> INITIAL GUESS <-------
2941              AL_INI(1)=dreal(alfaxz1_av(ixz))  cccc       SBAGLIATO
2942              AL_INI(2)=dreal(alfayz1_av(iyz))  c$$$            AL_INI(1) = dreal(alfaxz1_av(ixz))
2943              AL_INI(4)=datan(dreal(alfayz2_av(iyz))  c$$$            AL_INI(2) = dreal(alfayz1_av(iyz))
2944       $           /dreal(alfaxz2_av(ixz)))  c$$$            AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))
2945              tath=-dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))  c$$$     $           /dreal(alfaxz2_av(ixz)))
2946              AL_INI(3)=tath/sqrt(1+tath**2)  c$$$            tath      = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))
2947              AL_INI(5)=(1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.  c$$$            AL_INI(3) = tath/sqrt(1+tath**2)
2948                c$$$            AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.
2949  c     print*,'*******',AL_INI(5)  cccc       GIUSTO (ma si sua guess())
2950              if(AL_INI(5).gt.defmax)goto 888 !next cloud  c$$$            AL_INI(1) = dreal(alfaxz1_av(ixz))
2951                c$$$            AL_INI(2) = dreal(alfayz1_av(iyz))
2952  c     print*,'alfaxz2, alfayz2 '  c$$$            tath      = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))
2953  c     $              ,alfaxz2_av(ixz),alfayz2_av(iyz)  c$$$            AL_INI(3) = tath/sqrt(1+tath**2)
2954                c$$$            IF(alfaxz2_av(ixz).NE.0)THEN
2955  *     -------> INITIAL GUESS <-------  c$$$            AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))
2956  c     print*,'AL_INI ',(al_ini(i),i=1,5)  c$$$     $           /dreal(alfaxz2_av(ixz)))
2957                c$$$            ELSE
2958              if(DEBUG)then  c$$$               AL_INI(4) = acos(-1.)/2
2959    c$$$               IF(alfayz2_av(iyz).LT.0)AL_INI(4) = AL_INI(4)+acos(-1.)
2960    c$$$            ENDIF
2961    c$$$            IF(alfaxz2_av(ixz).LT.0)AL_INI(4)= acos(-1.)+ AL_INI(4)
2962    c$$$            AL_INI(4) = -acos(-1.) + AL_INI(4) !from incidence direction to tracking rs
2963    c$$$            
2964    c$$$            AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.
2965    c$$$            
2966    c$$$            if(AL_INI(5).gt.defmax)goto 888 !next cloud
2967                            
2968                if(DEBUG.EQ.1)then
2969                   print*,'track candidate', ntracks+1
2970                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2971                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2972                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
# Line 2959  c     print*,'AL_INI ',(al_ini(i),i=1,5) Line 2999  c     print*,'AL_INI ',(al_ini(i),i=1,5)
2999                                hit_plane(6)=icp6                                hit_plane(6)=icp6
3000                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
3001                                                                
3002                                  *                             ---------------------------------------
3003    *                             check if this group of couples has been
3004    *                             already fitted    
3005    *                             ---------------------------------------
3006                                  do ica=1,ntracks
3007                                     isthesame=1
3008                                     do ip=1,NPLANES
3009                                        if(hit_plane(ip).ne.0)then
3010                                           if(  CP_STORE(nplanes-ip+1,ica)
3011         $                                      .ne.
3012         $                                      cp_match(ip,hit_plane(ip)) )
3013         $                                      isthesame=0
3014                                        else
3015                                           if(  CP_STORE(nplanes-ip+1,ica)
3016         $                                      .ne.
3017         $                                      0 )
3018         $                                      isthesame=0
3019                                        endif
3020                                     enddo
3021                                     if(isthesame.eq.1)then
3022                                        if(DEBUG.eq.1)
3023         $                                   print*,'(already fitted)'
3024                                        goto 666 !jump to next combination
3025                                     endif
3026                                  enddo
3027    
3028                                call track_init !init TRACK common                                call track_init !init TRACK common
3029    
3030                                do ip=1,nplanes !loop on planes                                do ip=1,nplanes !loop on planes (bottom to top)
3031                                   if(hit_plane(ip).ne.0)then                                   if(hit_plane(ip).ne.0)then
3032                                      id=cp_match(ip,hit_plane(ip))                                      id=cp_match(ip,hit_plane(ip))
3033                                      is=is_cp(id)                                      is=is_cp(id)
# Line 2976  c     print*,'AL_INI ',(al_ini(i),i=1,5) Line 3041  c     print*,'AL_INI ',(al_ini(i),i=1,5)
3041  *                                   *************************  *                                   *************************
3042  c                                    call xyz_PAM(icx,icy,is,  c                                    call xyz_PAM(icx,icy,is,
3043  c     $                                   'COG2','COG2',0.,0.)  c     $                                   'COG2','COG2',0.,0.)
3044    c                                    call xyz_PAM(icx,icy,is, !(1)
3045    c     $                                   PFAdef,PFAdef,0.,0.) !(1)
3046                                      call xyz_PAM(icx,icy,is, !(1)                                      call xyz_PAM(icx,icy,is, !(1)
3047       $                                   PFAdef,PFAdef,0.,0.) !(1)       $                                   PFAdef,PFAdef,0.,0.,0.,0.)
3048  *                                   *************************  *                                   *************************
3049  *                                   -----------------------------  *                                   -----------------------------
3050                                      xgood(nplanes-ip+1)=1.                                      xgood(nplanes-ip+1)=1.
# Line 2993  c     $                                 Line 3060  c     $                                
3060  *     **********************************************************  *     **********************************************************
3061  *     ************************** FIT *** FIT *** FIT *** FIT ***  *     ************************** FIT *** FIT *** FIT *** FIT ***
3062  *     **********************************************************  *     **********************************************************
3063    cccc  scommentare se si usa al_ini della nuvola
3064    c$$$                              do i=1,5
3065    c$$$                                 AL(i)=AL_INI(i)
3066    c$$$                              enddo
3067                                  call guess()
3068                                do i=1,5                                do i=1,5
3069                                   AL(i)=AL_INI(i)                                   AL_INI(i)=AL(i)
3070                                enddo                                enddo
3071                                ifail=0 !error flag in chi^2 computation                                ifail=0 !error flag in chi^2 computation
3072                                jstep=0 !number of  minimization steps                                jstep=0 !number of  minimization steps
3073                                call mini_2(jstep,ifail)                                iprint=0
3074    c                              if(DEBUG.EQ.1)iprint=1
3075                                  if(DEBUG.EQ.1)iprint=2
3076                                  call mini2(jstep,ifail,iprint)
3077                                if(ifail.ne.0) then                                if(ifail.ne.0) then
3078                                   if(DEBUG)then                                   if(DEBUG.EQ.1)then
3079                                      print *,                                      print *,
3080       $                              '*** MINIMIZATION FAILURE *** '       $                              '*** MINIMIZATION FAILURE *** '
3081       $                              //'(mini_2 in clouds_to_ctrack)'       $                              //'(clouds_to_ctrack)'
3082                                        print*,'initial guess: '
3083    
3084                                        print*,'AL_INI(1) = ',AL_INI(1)
3085                                        print*,'AL_INI(2) = ',AL_INI(2)
3086                                        print*,'AL_INI(3) = ',AL_INI(3)
3087                                        print*,'AL_INI(4) = ',AL_INI(4)
3088                                        print*,'AL_INI(5) = ',AL_INI(5)
3089                                   endif                                   endif
3090                                   chi2=-chi2  c                                 chi2=-chi2
3091                                endif                                endif
3092  *     **********************************************************  *     **********************************************************
3093  *     ************************** FIT *** FIT *** FIT *** FIT ***  *     ************************** FIT *** FIT *** FIT *** FIT ***
# Line 3018  c     $                                 Line 3100  c     $                                
3100  *     --------------------------  *     --------------------------
3101                                if(ntracks.eq.NTRACKSMAX)then                                if(ntracks.eq.NTRACKSMAX)then
3102                                                                    
3103                                   if(verbose)print*,                                   if(verbose.eq.1)print*,
3104       $                 '** warning ** number of candidate tracks '//       $                 '** warning ** number of candidate tracks '//
3105       $                 ' exceeds vector dimension '       $                 ' exceeds vector dimension '
3106       $                ,'( ',NTRACKSMAX,' )'       $                ,'( ',NTRACKSMAX,' )'
3107  c                                 good2=.false.  c                                 good2=.false.
3108  c                                 goto 880 !fill ntp and go to next event                      c                                 goto 880 !fill ntp and go to next event                    
3109                                     do iv=1,nviews
3110    c                                    mask_view(iv) = 7
3111                                        mask_view(iv) = mask_view(iv) + 2**6
3112                                     enddo
3113                                   iflag=1                                   iflag=1
3114                                   return                                   return
3115                                endif                                endif
3116                                                                
3117                                ntracks = ntracks + 1                                ntracks = ntracks + 1
3118                                                                
3119  c$$$                              ndof=0                                                                do ip=1,nplanes !top to bottom
3120                                do ip=1,nplanes  
 c$$$                                 ndof=ndof  
 c$$$     $                                +int(xgood(ip))  
 c$$$     $                                +int(ygood(ip))  
3121                                   XV_STORE(ip,ntracks)=sngl(xv(ip))                                   XV_STORE(ip,ntracks)=sngl(xv(ip))
3122                                   YV_STORE(ip,ntracks)=sngl(yv(ip))                                   YV_STORE(ip,ntracks)=sngl(yv(ip))
3123                                   ZV_STORE(ip,ntracks)=sngl(zv(ip))                                                                       ZV_STORE(ip,ntracks)=sngl(zv(ip))                                    
# Line 3050  c$$$     $                               Line 3133  c$$$     $                              
3133                                   AYV_STORE(ip,ntracks)=sngl(ayv(ip))                                   AYV_STORE(ip,ntracks)=sngl(ayv(ip))
3134                                   XGOOD_STORE(ip,ntracks)=sngl(xgood(ip))                                   XGOOD_STORE(ip,ntracks)=sngl(xgood(ip))
3135                                   YGOOD_STORE(ip,ntracks)=sngl(ygood(ip))                                   YGOOD_STORE(ip,ntracks)=sngl(ygood(ip))
3136    *                                NB! hit_plane is defined from bottom to top
3137                                   if(hit_plane(ip).ne.0)then                                   if(hit_plane(ip).ne.0)then
3138                                      CP_STORE(nplanes-ip+1,ntracks)=                                      CP_STORE(nplanes-ip+1,ntracks)=
3139       $                                   cp_match(ip,hit_plane(ip))       $                                   cp_match(ip,hit_plane(ip))
3140                                        SENSOR_STORE(nplanes-ip+1,ntracks)
3141         $                              = is_cp(cp_match(ip,hit_plane(ip)))
3142                                        LADDER_STORE(nplanes-ip+1,ntracks)
3143         $                                   = LADDER(
3144         $                                   clx(ip,icp_cp(
3145         $                                   cp_match(ip,hit_plane(ip)
3146         $                                   ))));
3147                                   else                                   else
3148                                      CP_STORE(nplanes-ip+1,ntracks)=0                                      CP_STORE(nplanes-ip+1,ntracks)=0
3149                                        SENSOR_STORE(nplanes-ip+1,ntracks)=0
3150                                        LADDER_STORE(nplanes-ip+1,ntracks)=0
3151                                   endif                                   endif
3152                                   CLS_STORE(nplanes-ip+1,ntracks)=0                                   BX_STORE(ip,ntracks)=0!I dont need it now
3153                                     BY_STORE(ip,ntracks)=0!I dont need it now
3154                                     CLS_STORE(ip,ntracks)=0
3155                                   do i=1,5                                   do i=1,5
3156                                      AL_STORE(i,ntracks)=sngl(AL(i))                                      AL_STORE(i,ntracks)=sngl(AL(i))
3157                                   enddo                                   enddo
3158                                enddo                                enddo
3159                                                                
 c$$$  *                             Number of Degree Of Freedom  
 c$$$  ndof=ndof-5                            
 c$$$  *                             reduced chi^2  
 c$$$  rchi2=chi2/dble(ndof)  
3160                                RCHI2_STORE(ntracks)=chi2                                RCHI2_STORE(ntracks)=chi2
3161                                                                
3162  *     --------------------------------  *     --------------------------------
# Line 3089  c$$$  rchi2=chi2/dble(ndof) Line 3180  c$$$  rchi2=chi2/dble(ndof)
3180           return           return
3181        endif        endif
3182                
3183        if(DEBUG)then  c$$$      if(DEBUG.EQ.1)then
3184           print*,'****** TRACK CANDIDATES ***********'  c$$$         print*,'****** TRACK CANDIDATES ***********'
3185           print*,'#         R. chi2        RIG'  c$$$         print*,'#         R. chi2        RIG'
3186           do i=1,ntracks  c$$$         do i=1,ntracks
3187              print*,i,' --- ',rchi2_store(i),' --- '  c$$$            print*,i,' --- ',rchi2_store(i),' --- '
3188       $           ,1./abs(AL_STORE(5,i))  c$$$     $           ,1./abs(AL_STORE(5,i))
3189           enddo  c$$$         enddo
3190           print*,'***********************************'  c$$$         print*,'***********************************'
3191    c$$$      endif
3192          if(DEBUG.EQ.1)then
3193            print*,'****** TRACK CANDIDATES *****************'
3194            print*,'#         R. chi2        RIG         ndof'
3195            do i=1,ntracks
3196              ndof=0                !(1)
3197              do ii=1,nplanes       !(1)
3198                ndof=ndof           !(1)
3199         $           +int(xgood_store(ii,i)) !(1)
3200         $           +int(ygood_store(ii,i)) !(1)
3201              enddo                 !(1)
3202              print*,i,' --- ',rchi2_store(i),' --- '
3203         $         ,1./abs(AL_STORE(5,i)),' --- ',ndof
3204            enddo
3205            print*,'*****************************************'
3206        endif        endif
3207                
3208                
# Line 3115  c$$$  rchi2=chi2/dble(ndof) Line 3221  c$$$  rchi2=chi2/dble(ndof)
3221    
3222        subroutine refine_track(ibest)        subroutine refine_track(ibest)
3223    
 c******************************************************  
 cccccc 06/10/2005 modified by elena vannuccini ---> (1)  
 cccccc 31/01/2006 modified by elena vannuccini ---> (2)  
 cccccc 12/08/2006 modified by elena vannucicni ---> (3)  
 c******************************************************  
3224    
3225        include 'commontracker.f'        include 'commontracker.f'
3226          include 'level1.f'
3227        include 'common_momanhough.f'        include 'common_momanhough.f'
3228        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
3229        include 'common_mini_2.f'        include 'common_mini_2.f'
3230        include 'common_mech.f'        include 'common_mech.f'
       include 'momanhough_init.f'  
       include 'level1.f'  
3231        include 'calib.f'        include 'calib.f'
3232    
 c      logical DEBUG  
 c      common/dbg/DEBUG  
   
3233  *     flag to chose PFA  *     flag to chose PFA
3234        character*10 PFA        character*10 PFA
3235        common/FINALPFA/PFA        common/FINALPFA/PFA
3236    
3237          real k(6)
3238          DATA k/1.099730,0.418900,0.220939,0.220907,0.418771,1.100674/
3239    
3240          real xp,yp,zp
3241          real xyzp(3),bxyz(3)
3242          equivalence (xp,xyzp(1)),(yp,xyzp(2)),(zp,xyzp(3))
3243    
3244          if(DEBUG.EQ.1)print*,'refine_track:'
3245  *     =================================================  *     =================================================
3246  *     new estimate of positions using ETA algorithm  *     new estimate of positions using ETA algorithm
3247  *                          and  *                          and
# Line 3145  c      common/dbg/DEBUG Line 3250  c      common/dbg/DEBUG
3250        call track_init        call track_init
3251        do ip=1,nplanes           !loop on planes        do ip=1,nplanes           !loop on planes
3252    
3253             xP=XV_STORE(nplanes-ip+1,ibest)
3254             yP=YV_STORE(nplanes-ip+1,ibest)
3255             zP=ZV_STORE(nplanes-ip+1,ibest)
3256             call gufld(xyzp,bxyz)
3257             BX_STORE(nplanes-ip+1,ibest)=bxyz(1)
3258             BY_STORE(nplanes-ip+1,ibest)=bxyz(2)
3259    c$$$  bxyz(1)=0
3260    c$$$         bxyz(2)=0
3261    c$$$         bxyz(3)=0
3262    *     |||||||||||||||||||||||||||||||||||||||||||||||||
3263  *     -------------------------------------------------  *     -------------------------------------------------
3264  *     If the plane has been already included, it just  *     If the plane has been already included, it just
3265  *     computes again the coordinates of the x-y couple  *     computes again the coordinates of the x-y couple
3266  *     using improved PFAs  *     using improved PFAs
3267  *     -------------------------------------------------  *     -------------------------------------------------
3268    *     |||||||||||||||||||||||||||||||||||||||||||||||||
3269           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
3270       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3271                            
# Line 3163  c      common/dbg/DEBUG Line 3279  c      common/dbg/DEBUG
3279       $           ,ip_cp(id),ip       $           ,ip_cp(id),ip
3280              icx=clx(ip,icp)              icx=clx(ip,icp)
3281              icy=cly(ip,icp)              icy=cly(ip,icp)
3282    c            call xyz_PAM(icx,icy,is,
3283    c     $           PFA,PFA,
3284    c     $           AXV_STORE(nplanes-ip+1,ibest),
3285    c     $           AYV_STORE(nplanes-ip+1,ibest))
3286              call xyz_PAM(icx,icy,is,              call xyz_PAM(icx,icy,is,
 c     $           'ETA2','ETA2',  
3287       $           PFA,PFA,       $           PFA,PFA,
3288       $           AXV_STORE(nplanes-ip+1,ibest),       $           AXV_STORE(nplanes-ip+1,ibest),
3289       $           AYV_STORE(nplanes-ip+1,ibest))       $           AYV_STORE(nplanes-ip+1,ibest),
3290  c$$$  call xyz_PAM(icx,icy,is,       $           bxyz(1),
3291  c$$$  $              'COG2','COG2',       $           bxyz(2)
3292  c$$$  $              0.,       $           )
3293  c$$$  $              0.)  
3294              xm(nplanes-ip+1) = xPAM              xm(nplanes-ip+1) = xPAM
3295              ym(nplanes-ip+1) = yPAM              ym(nplanes-ip+1) = yPAM
3296              zm(nplanes-ip+1) = zPAM              zm(nplanes-ip+1) = zPAM
# Line 3180  c$$$  $              0.) Line 3299  c$$$  $              0.)
3299              resx(nplanes-ip+1) = resxPAM              resx(nplanes-ip+1) = resxPAM
3300              resy(nplanes-ip+1) = resyPAM              resy(nplanes-ip+1) = resyPAM
3301    
3302  c            dedxtrk(nplanes-ip+1) = (dedx(icx)+dedx(icy))/2. !(1)              dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3303              dedxtrk_x(nplanes-ip+1)=dedx(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)              dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
             dedxtrk_y(nplanes-ip+1)=dedx(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)  
3304                            
3305    *     |||||||||||||||||||||||||||||||||||||||||||||||||
3306  *     -------------------------------------------------  *     -------------------------------------------------
3307  *     If the plane has NOT  been already included,  *     If the plane has NOT  been already included,
3308  *     it tries to include a COUPLE or a single cluster  *     it tries to include a COUPLE or a single cluster
3309  *     -------------------------------------------------  *     -------------------------------------------------
3310    *     |||||||||||||||||||||||||||||||||||||||||||||||||
3311           else                             else                  
3312                                
3313              xgood(nplanes-ip+1)=0              xgood(nplanes-ip+1)=0
# Line 3195  c            dedxtrk(nplanes-ip+1) = (de Line 3315  c            dedxtrk(nplanes-ip+1) = (de
3315                                
3316  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3317  *     determine which ladder and sensor are intersected by the track  *     determine which ladder and sensor are intersected by the track
             xP=XV_STORE(nplanes-ip+1,ibest)  
             yP=YV_STORE(nplanes-ip+1,ibest)  
             zP=ZV_STORE(nplanes-ip+1,ibest)  
3318              call whichsensor(ip,xP,yP,nldt,ist)              call whichsensor(ip,xP,yP,nldt,ist)
3319  *     if the track hit the plane in a dead area, go to the next plane  *     if the track hit the plane in a dead area, go to the next plane
3320              if(nldt.eq.0.or.ist.eq.0)goto 133              if(nldt.eq.0.or.ist.eq.0)goto 133
3321    
3322                SENSOR_STORE(nplanes-ip+1,IBEST)=ist
3323                LADDER_STORE(nplanes-ip+1,IBEST)=nldt
3324  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3325    
3326              if(DEBUG)then              if(DEBUG.EQ.1)then
3327                 print*,                 print*,
3328       $              '------ Plane ',ip,' intersected on LADDER ',nldt       $              '------ Plane ',ip,' intersected on LADDER ',nldt
3329       $              ,' SENSOR ',ist       $              ,' SENSOR ',ist
# Line 3214  c            dedxtrk(nplanes-ip+1) = (de Line 3334  c            dedxtrk(nplanes-ip+1) = (de
3334  *     ===========================================  *     ===========================================
3335  *     STEP 1 >>>>>>>  try to include a new couple  *     STEP 1 >>>>>>>  try to include a new couple
3336  *     ===========================================  *     ===========================================
3337  c            if(DEBUG)print*,'>>>> try to include a new couple'  c            if(DEBUG.EQ.1)print*,'>>>> try to include a new couple'
3338              distmin=1000000.              distmin=1000000.
3339              xmm = 0.              xmm = 0.
3340              ymm = 0.              ymm = 0.
# Line 3237  c     $              cl_used(icy).eq.1.o Line 3357  c     $              cl_used(icy).eq.1.o
3357  *            *          
3358                 call xyz_PAM(icx,icy,ist,                 call xyz_PAM(icx,icy,ist,
3359       $              PFA,PFA,       $              PFA,PFA,
 c     $              'ETA2','ETA2',  
3360       $              AXV_STORE(nplanes-ip+1,ibest),       $              AXV_STORE(nplanes-ip+1,ibest),
3361       $              AYV_STORE(nplanes-ip+1,ibest))       $              AYV_STORE(nplanes-ip+1,ibest),
3362         $              bxyz(1),
3363         $              bxyz(2)
3364         $              )
3365                                
3366                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3367    c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3368                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3369                 if(DEBUG)print*,'( couple ',id                 if(DEBUG.EQ.1)print*,'( couple ',id
3370       $              ,' ) normalized distance ',distance       $              ,' ) distance ',distance
3371                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3372                    xmm = xPAM                    xmm = xPAM
3373                    ymm = yPAM                    ymm = yPAM
# Line 3253  c     $              'ETA2','ETA2', Line 3376  c     $              'ETA2','ETA2',
3376                    rymm = resyPAM                    rymm = resyPAM
3377                    distmin = distance                    distmin = distance
3378                    idm = id                                      idm = id                  
3379  c                 dedxmm = (dedx(icx)+dedx(icy))/2. !(1)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3380                    dedxmmx = dedx(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3381                    dedxmmy = dedx(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)  c     QUIQUI --> non devo moltiplicare per clinc?!?!?!
3382                      clincnewc=10*sqrt(rymm**2+rxmm**2 !QUIQUI
3383         $                 +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2))) !QUIQUI
3384                 endif                 endif
3385   1188          continue   1188          continue
3386              enddo               !end loop on couples on plane icp              enddo               !end loop on couples on plane icp
3387              if(distmin.le.clinc)then                    c            if(distmin.le.clinc)then     !QUIQUI              
3388                if(distmin.le.clincnewc)then     !QUIQUI              
3389  *              -----------------------------------  *              -----------------------------------
3390                 xm(nplanes-ip+1) = xmm         !<<<                 xm(nplanes-ip+1) = xmm !<<<
3391                 ym(nplanes-ip+1) = ymm         !<<<                 ym(nplanes-ip+1) = ymm !<<<
3392                 zm(nplanes-ip+1) = zmm         !<<<                 zm(nplanes-ip+1) = zmm !<<<
3393                 xgood(nplanes-ip+1) = 1        !<<<                 xgood(nplanes-ip+1) = 1 !<<<
3394                 ygood(nplanes-ip+1) = 1        !<<<                 ygood(nplanes-ip+1) = 1 !<<<
3395                 resx(nplanes-ip+1)=rxmm        !<<<                 resx(nplanes-ip+1)=rxmm !<<<
3396                 resy(nplanes-ip+1)=rymm        !<<<                 resy(nplanes-ip+1)=rymm !<<<
3397  c              dedxtrk(nplanes-ip+1) = dedxmm !<<<  !(1)                 dedxtrk_x(nplanes-ip+1) = dedxmmx !<<<
3398                 dedxtrk_x(nplanes-ip+1) = dedxmmx    !(1)                 dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<
                dedxtrk_y(nplanes-ip+1) = dedxmmy    !(1)  
3399  *              -----------------------------------  *              -----------------------------------
3400                 CP_STORE(nplanes-ip+1,ibest)=idm                       CP_STORE(nplanes-ip+1,ibest)=idm      
3401                 if(DEBUG)print*,'%%%% included couple ',idm                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm
3402       $              ,' (norm.dist.= ',distmin,', cut ',clinc,' )'       $              ,' (dist.= ',distmin,', cut ',clinc,' )'
3403                 goto 133         !next plane                 goto 133         !next plane
3404              endif              endif
3405  *     ================================================  *     ================================================
3406  *     STEP 2 >>>>>>>  try to include a single cluster  *     STEP 2 >>>>>>>  try to include a single cluster
3407  *                     either from a couple or single  *                     either from a couple or single
3408  *     ================================================  *     ================================================
3409  c            if(DEBUG)print*,'>>>> try to include a new cluster'  c            if(DEBUG.EQ.1)print*,'>>>> try to include a new cluster'
3410              distmin=1000000.              distmin=1000000.
3411              xmm_A = 0.          !---------------------------              xmm_A = 0.          !---------------------------
3412              ymm_A = 0.          ! init variables that              ymm_A = 0.          ! init variables that
# Line 3307  c            if(DEBUG)print*,'>>>> try t Line 3432  c            if(DEBUG)print*,'>>>> try t
3432  c               if(cl_used(icx).eq.1)goto 11881 !if the X cluster is already used  c               if(cl_used(icx).eq.1)goto 11881 !if the X cluster is already used
3433                 if(cl_used(icx).ne.0)goto 11881 !if the X cluster is already used  !(3)                 if(cl_used(icx).ne.0)goto 11881 !if the X cluster is already used  !(3)
3434  *                                              !jump to the Y cluster  *                                              !jump to the Y cluster
3435    c               call xyz_PAM(icx,0,ist,
3436    c     $              PFA,PFA,
3437    c     $              AXV_STORE(nplanes-ip+1,ibest),0.)              
3438                 call xyz_PAM(icx,0,ist,                 call xyz_PAM(icx,0,ist,
 c     $              'ETA2','ETA2',  
3439       $              PFA,PFA,       $              PFA,PFA,
3440       $              AXV_STORE(nplanes-ip+1,ibest),0.)                     $              AXV_STORE(nplanes-ip+1,ibest),0.,
3441         $              bxyz(1),
3442         $              bxyz(2)
3443         $              )              
3444                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3445  c     if(DEBUG)print*,'normalized distance ',distance  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3446                 if(DEBUG)print*,'( cl-X ',icx                 if(DEBUG.EQ.1)print*,'( cl-X ',icx
3447       $              ,' in cp ',id,' ) normalized distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3448                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3449                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3450                    ymm_A = yPAM_A                    ymm_A = yPAM_A
# Line 3326  c     if(DEBUG)print*,'normalized distan Line 3456  c     if(DEBUG)print*,'normalized distan
3456                    rymm = resyPAM                    rymm = resyPAM
3457                    distmin = distance                    distmin = distance
3458                    iclm = icx                    iclm = icx
3459  c                  dedxmm = dedx(icx) !(1)  c                  dedxmm = sgnl(icx) !(1)
3460                    dedxmmx = dedx(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3461                    dedxmmy = 0.        !(1)                    dedxmmy = 0.        !(1)
3462                 endif                                   endif                  
3463  11881          continue  11881          continue
# Line 3335  c                  dedxmm = dedx(icx) !( Line 3465  c                  dedxmm = dedx(icx) !(
3465  c               if(cl_used(icy).eq.1)goto 11882 !if the Y cluster is already used  c               if(cl_used(icy).eq.1)goto 11882 !if the Y cluster is already used
3466                 if(cl_used(icy).ne.0)goto 11882 !if the Y cluster is already used !(3)                 if(cl_used(icy).ne.0)goto 11882 !if the Y cluster is already used !(3)
3467  *                                              !jump to the next couple  *                                              !jump to the next couple
3468    c               call xyz_PAM(0,icy,ist,
3469    c     $              PFA,PFA,
3470    c     $              0.,AYV_STORE(nplanes-ip+1,ibest))
3471                 call xyz_PAM(0,icy,ist,                 call xyz_PAM(0,icy,ist,
 c     $              'ETA2','ETA2',  
3472       $              PFA,PFA,       $              PFA,PFA,
3473       $              0.,AYV_STORE(nplanes-ip+1,ibest))       $              0.,AYV_STORE(nplanes-ip+1,ibest),
3474         $              bxyz(1),
3475         $              bxyz(2)
3476         $              )
3477                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3478                 if(DEBUG)print*,'( cl-Y ',icy  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3479       $              ,' in cp ',id,' ) normalized distance ',distance                 if(DEBUG.EQ.1)print*,'( cl-Y ',icy
3480         $              ,' in cp ',id,' ) distance ',distance
3481                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3482                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3483                    ymm_A = yPAM_A                    ymm_A = yPAM_A
# Line 3353  c     $              'ETA2','ETA2', Line 3489  c     $              'ETA2','ETA2',
3489                    rymm = resyPAM                    rymm = resyPAM
3490                    distmin = distance                    distmin = distance
3491                    iclm = icy                    iclm = icy
3492  c                 dedxmm = dedx(icy)  !(1)  c                 dedxmm = sgnl(icy)  !(1)
3493                    dedxmmx = 0.        !(1)                    dedxmmx = 0.        !(1)
3494                    dedxmmy = dedx(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3495                 endif                                   endif                  
3496  11882          continue  11882          continue
3497              enddo               !end loop on cluster inside couples              enddo               !end loop on cluster inside couples
3498  *----- single clusters -----------------------------------------------      *----- single clusters -----------------------------------------------  
3499    c            print*,'## ncls(',ip,') ',ncls(ip)
3500              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
3501                 icl=cls(ip,ic)                 icl=cls(ip,ic)
3502  c               if(cl_used(icl).eq.1.or.     !if the cluster is already used  c               if(cl_used(icl).eq.1.or.     !if the cluster is already used
# Line 3368  c               if(cl_used(icl).eq.1.or. Line 3505  c               if(cl_used(icl).eq.1.or.
3505       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
3506                 if(mod(VIEW(icl),2).eq.0)then!<---- X view                 if(mod(VIEW(icl),2).eq.0)then!<---- X view
3507                    call xyz_PAM(icl,0,ist,                    call xyz_PAM(icl,0,ist,
 c     $                 'ETA2','ETA2',  
3508       $                 PFA,PFA,       $                 PFA,PFA,
3509       $                 AXV_STORE(nplanes-ip+1,ibest),0.)       $                 AXV_STORE(nplanes-ip+1,ibest),0.,
3510         $                 bxyz(1),
3511         $                 bxyz(2)
3512         $                 )
3513                 else                         !<---- Y view                 else                         !<---- Y view
3514                    call xyz_PAM(0,icl,ist,                    call xyz_PAM(0,icl,ist,
 c     $                 'ETA2','ETA2',  
3515       $                 PFA,PFA,       $                 PFA,PFA,
3516       $                 0.,AYV_STORE(nplanes-ip+1,ibest))       $                 0.,AYV_STORE(nplanes-ip+1,ibest),
3517         $                 bxyz(1),
3518         $                 bxyz(2)
3519         $                 )
3520                 endif                 endif
3521    
3522                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3523                 if(DEBUG)print*,'( cl-s ',icl  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3524       $              ,' ) normalized distance ',distance                 if(DEBUG.EQ.1)print*,'( cl-s ',icl
3525         $              ,' ) distance ',distance
3526                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3527    c                  if(DEBUG.EQ.1)print*,'YES'
3528                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3529                    ymm_A = yPAM_A                    ymm_A = yPAM_A
3530                    zmm_A = zPAM_A                    zmm_A = zPAM_A
# Line 3392  c     $                 'ETA2','ETA2', Line 3535  c     $                 'ETA2','ETA2',
3535                    rymm = resyPAM                    rymm = resyPAM
3536                    distmin = distance                      distmin = distance  
3537                    iclm = icl                    iclm = icl
 c                  dedxmm = dedx(icl)                   !(1)  
3538                    if(mod(VIEW(icl),2).eq.0)then !<---- X view                    if(mod(VIEW(icl),2).eq.0)then !<---- X view
3539                       dedxmmx = dedx(icl)/mip(VIEW(icl),LADDER(icl)) !(1)(2)                       dedxmmx = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
3540                       dedxmmy = 0.                       !(1)                       dedxmmy = 0.                  
3541                    else          !<---- Y view                    else          !<---- Y view
3542                       dedxmmx = 0.                       !(1)                       dedxmmx = 0.                  
3543                       dedxmmy = dedx(icl)/mip(VIEW(icl),LADDER(icl)) !(1)(2)                       dedxmmy = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
3544                    endif                    endif
3545                 endif                                   endif                  
3546  18882          continue  18882          continue
3547              enddo               !end loop on single clusters              enddo               !end loop on single clusters
3548    c            print*,'## distmin ', distmin,' clinc ',clinc
3549    
3550              if(distmin.le.clinc)then                    c     QUIQUI------------
3551                  c     anche qui: non ci vuole clinc???
3552                 CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<                  if(iclm.ne.0)then
 *              ----------------------------  
3553                 if(mod(VIEW(iclm),2).eq.0)then                 if(mod(VIEW(iclm),2).eq.0)then
3554                    XGOOD(nplanes-ip+1)=1.                    clincnew=
3555                    resx(nplanes-ip+1)=rxmm       $                 20*
3556                    if(DEBUG)print*,'%%%% included X-cl ',iclm       $                 sqrt(rxmm**2+RCHI2_STORE(ibest)*k(ip)*cov(1,1))
3557       $                 ,' ( norm.dist.= ',distmin,', cut ',clinc,' )'                 else if(mod(VIEW(iclm),2).ne.0)then
3558                 else                    clincnew=
3559                    YGOOD(nplanes-ip+1)=1.       $                 10*
3560                    resy(nplanes-ip+1)=rymm       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))
3561                    if(DEBUG)print*,'%%%% included Y-cl ',iclm                 endif
3562       $                 ,' ( norm.dist.= ',distmin,', cut ',clinc,' )'  c     QUIQUI------------
3563                  
3564                   if(distmin.le.clincnew)then   !QUIQUI
3565    c     if(distmin.le.clinc)then          !QUIQUI          
3566                      
3567                      CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<    
3568    *     ----------------------------
3569    c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
3570                      if(mod(VIEW(iclm),2).eq.0)then
3571                         XGOOD(nplanes-ip+1)=1.
3572                         resx(nplanes-ip+1)=rxmm
3573                         if(DEBUG.EQ.1)print*,'%%%% included X-cl ',iclm
3574         $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3575         $                    ,', dist.= ',distmin
3576         $                    ,', cut ',clinc,' )'
3577                      else
3578                         YGOOD(nplanes-ip+1)=1.
3579                         resy(nplanes-ip+1)=rymm
3580                         if(DEBUG.EQ.1)print*,'%%%% included Y-cl ',iclm
3581         $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3582         $                    ,', dist.= ', distmin
3583         $                    ,', cut ',clinc,' )'
3584                      endif
3585    c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
3586    *     ----------------------------
3587                      xm_A(nplanes-ip+1) = xmm_A
3588                      ym_A(nplanes-ip+1) = ymm_A
3589                      xm_B(nplanes-ip+1) = xmm_B
3590                      ym_B(nplanes-ip+1) = ymm_B
3591                      zm(nplanes-ip+1) = (zmm_A+zmm_B)/2.
3592                      dedxtrk_x(nplanes-ip+1) = dedxmmx !<<<
3593                      dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<
3594    *     ----------------------------
3595                 endif                 endif
 *              ----------------------------  
                xm_A(nplanes-ip+1) = xmm_A  
                ym_A(nplanes-ip+1) = ymm_A  
                xm_B(nplanes-ip+1) = xmm_B  
                ym_B(nplanes-ip+1) = ymm_B  
                zm(nplanes-ip+1) = (zmm_A+zmm_B)/2.  
 c              dedxtrk(nplanes-ip+1) = dedxmm !<<<    !(1)  
                dedxtrk_x(nplanes-ip+1) = dedxmmx !<<< !(1)  
                dedxtrk_y(nplanes-ip+1) = dedxmmy !<<< !(1)  
 *              ----------------------------  
3596              endif              endif
3597           endif           endif
3598   133     continue   133     continue
# Line 3447  c              dedxtrk(nplanes-ip+1) = d Line 3611  c              dedxtrk(nplanes-ip+1) = d
3611  *                                                 *  *                                                 *
3612  *                                                 *  *                                                 *
3613  **************************************************  **************************************************
 cccccc 12/08/2006 modified by elena ---> (1)  
3614  *  *
3615        subroutine clean_XYclouds(ibest,iflag)        subroutine clean_XYclouds(ibest,iflag)
3616    
3617        include 'commontracker.f'        include 'commontracker.f'
3618          include 'level1.f'
3619        include 'common_momanhough.f'        include 'common_momanhough.f'
3620        include 'momanhough_init.f'        include 'level2.f'      
       include 'level2.f'        !(1)  
 c      include 'calib.f'  
 c      include 'level1.f'  
   
 c      logical DEBUG  
 c      common/dbg/DEBUG  
3621    
3622          if(DEBUG.EQ.1)print*,'clean_XYclouds:'
3623    
3624        do ip=1,nplanes           !loop on planes        do ip=1,nplanes           !loop on planes
3625    
# Line 3470  c      common/dbg/DEBUG Line 3629  c      common/dbg/DEBUG
3629              if(id.ne.0)then              if(id.ne.0)then
3630                 iclx=clx(ip,icp_cp(id))                 iclx=clx(ip,icp_cp(id))
3631                 icly=cly(ip,icp_cp(id))                 icly=cly(ip,icp_cp(id))
3632  c               cl_used(iclx)=1  !tag used clusters  c$$$               cl_used(iclx)=ntrk  !tag used clusters
3633  c               cl_used(icly)=1  !tag used clusters  c$$$               cl_used(icly)=ntrk  !tag used clusters
                cl_used(iclx)=ntrk  !tag used clusters !(1)  
                cl_used(icly)=ntrk  !tag used clusters !(1)  
3634              elseif(icl.ne.0)then              elseif(icl.ne.0)then
3635  c               cl_used(icl)=1   !tag used clusters  c$$$               cl_used(icl)=ntrk   !tag used clusters
                cl_used(icl)=ntrk   !tag used clusters !1)  
3636              endif              endif
3637                            
 c               if(DEBUG)then  
 c                  print*,ip,' <<< ',id  
 c               endif  
3638  *     -----------------------------  *     -----------------------------
3639  *     remove the couple from clouds  *     remove the couple from clouds
3640  *     remove also vitual couples containing the  *     remove also vitual couples containing the
# Line 3498  c               endif Line 3651  c               endif
3651       $              cly(ip,icp).eq.icl       $              cly(ip,icp).eq.icl
3652       $              )then       $              )then
3653                    id=id_cp(ip,icp,1)                    id=id_cp(ip,icp,1)
3654                    if(DEBUG)then                    if(DEBUG.EQ.1)then
3655                       print*,ip,' <<< cp ',id                       print*,ip,' <<< cp ',id
3656       $                    ,' ( cl-x '       $                    ,' ( cl-x '
3657       $                    ,clx(ip,icp)       $                    ,clx(ip,icp)
# Line 3532  c               endif Line 3685  c               endif
3685    
3686    
3687    
 c$$$*** * * * *** * * * *** * * * *** * * * *** * * * *** * * * ***  
 c$$$      real function fbad_cog(ncog,ic)  
 c$$$  
 c$$$  
 c$$$      include 'commontracker.f'  
 c$$$      include 'level1.f'  
 c$$$      include 'calib.f'  
 c$$$  
 c$$$*     --> signal of the central strip  
 c$$$      sc = CLSIGNAL(INDMAX(ic)) !center  
 c$$$  
 c$$$*     signal of adjacent strips  
 c$$$*     --> left  
 c$$$      sl1 = 0                  !left 1  
 c$$$      if(  
 c$$$     $     (INDMAX(ic)-1).ge.INDSTART(ic)  
 c$$$     $     )  
 c$$$     $     sl1 = max(0.,CLSIGNAL(INDMAX(ic)-1))  
 c$$$  
 c$$$      sl2 = 0                  !left 2  
 c$$$      if(  
 c$$$     $     (INDMAX(ic)-2).ge.INDSTART(ic)  
 c$$$     $     )  
 c$$$     $     sl2 = max(0.,CLSIGNAL(INDMAX(ic)-2))  
 c$$$  
 c$$$*     --> right  
 c$$$      sr1 = 0                  !right 1  
 c$$$      if(  
 c$$$     $     (ic.ne.NCLSTR1.and.(INDMAX(ic)+1).lt.INDSTART(ic+1))  
 c$$$     $     .or.  
 c$$$     $     (ic.eq.NCLSTR1.and.(INDMAX(ic)+1).le.TOTCLLENGTH)  
 c$$$     $     )  
 c$$$     $     sr1 = max(0.,CLSIGNAL(INDMAX(ic)+1))  
 c$$$  
 c$$$      sr2 = 0                  !right 2  
 c$$$      if(  
 c$$$     $     (ic.ne.NCLSTR1.and.(INDMAX(ic)+2).lt.INDSTART(ic+1))  
 c$$$     $     .or.  
 c$$$     $     (ic.eq.NCLSTR1.and.(INDMAX(ic)+2).le.TOTCLLENGTH)  
 c$$$     $     )  
 c$$$     $     sr2 = max(0.,CLSIGNAL(INDMAX(ic)+2))  
 c$$$  
 c$$$  
 c$$$      if(mod(int(VIEW(ic)),2).eq.1)then !Y-view  
 c$$$         f  = 4.  
 c$$$         si = 8.4  
 c$$$      else                              !X-view  
 c$$$         f  = 6.  
 c$$$         si = 3.9  
 c$$$      endif  
 c$$$  
 c$$$      fbad_cog = 1.  
 c$$$      f0 = 1  
 c$$$      f1 = 1  
 c$$$      f2 = 1  
 c$$$      f3 = 1    
 c$$$      if(sl1.gt.sr1.and.sl1.gt.0.)then  
 c$$$          
 c$$$         if(BAD(VIEW(ic),nvk(MAXS(ic)),nst(MAXS(ic))  ).eq.0)f0=f  
 c$$$         if(BAD(VIEW(ic),nvk(MAXS(ic)),nst(MAXS(ic)-1)).eq.0)f1=f  
 c$$$c         if(BAD(VIEW(ic),nvk(MAXS(ic)),nst(MAXS(ic)+1)).eq.0)f3=f  
 c$$$  
 c$$$         if(ncog.eq.2.and.sl1.ne.0)then  
 c$$$            fbad_cog = (f1**2*sc**2/sl1**2+f0**2)/(sc**2/sl1**2+1.)  
 c$$$         elseif(ncog.eq.3.and.sl1.ne.0.and.sr1.ne.0)then  
 c$$$            fbad_cog = 1.  
 c$$$         elseif(ncog.eq.4.and.sl1.ne.0.and.sr1.ne.0.and.sl2.ne.0)then  
 c$$$            fbad_cog = 1.  
 c$$$         else  
 c$$$            fbad_cog = 1.  
 c$$$         endif  
 c$$$          
 c$$$      elseif(sl1.le.sr1.and.sr1.gt.0.)then  
 c$$$  
 c$$$  
 c$$$         if(BAD(VIEW(ic),nvk(MAXS(ic)),nst(MAXS(ic))  ).eq.0)f0=f  
 c$$$         if(BAD(VIEW(ic),nvk(MAXS(ic)),nst(MAXS(ic)+1)).eq.0)f1=f  
 c$$$c         if(BAD(VIEW(ic),nvk(MAXS(ic)),nst(MAXS(ic)-1)).eq.0)f3=f  
 c$$$  
 c$$$         if(ncog.eq.2.and.sr1.ne.0)then  
 c$$$            fbad_cog = (f1**2*sc**2/sr1**2+f0**2)/(sc**2/sr1**2+1.)  
 c$$$         elseif(ncog.eq.3.and.sr1.ne.0.and.sl1.ne.0)then  
 c$$$            fbad_cog = 1.  
 c$$$         elseif(ncog.eq.4.and.sr1.ne.0.and.sl1.ne.0.and.sr2.ne.0)then  
 c$$$            fbad_cog = 1.  
 c$$$         else  
 c$$$            fbad_cog = 1.  
 c$$$         endif  
 c$$$  
 c$$$      endif  
 c$$$  
 c$$$      fbad_cog = sqrt(fbad_cog)  
 c$$$  
 c$$$      return  
 c$$$      end  
 c$$$  
   
3688    
3689    
3690  *     ****************************************************  *     ****************************************************
3691    
3692        subroutine init_level2        subroutine init_level2
3693    
 c*****************************************************  
 c     07/10/2005 modified by elena vannuccini --> (1)  
 c*****************************************************  
   
3694        include 'commontracker.f'        include 'commontracker.f'
3695          include 'level1.f'
3696        include 'common_momanhough.f'        include 'common_momanhough.f'
3697        include 'level2.f'        include 'level2.f'
       include 'level1.f'  
3698    
3699    *     ---------------------------------
3700    *     variables initialized from level1
3701    *     ---------------------------------
3702        do i=1,nviews        do i=1,nviews
3703           good2(i)=good1(i)           good2(i)=good1(i)
3704             do j=1,nva1_view
3705                vkflag(i,j)=1
3706                if(cnnev(i,j).le.0)then
3707                   vkflag(i,j)=cnnev(i,j)
3708                endif
3709             enddo
3710        enddo        enddo
3711    *     ----------------
3712  c      good2 = 0!.false.  *     level2 variables
3713  c$$$      nev2 = nev1  *     ----------------
   
 c$$$# ifndef TEST2003  
 c$$$c*****************************************************  
 c$$$cccccc 11/9/2005 modified by david fedele  
 c$$$c      pkt_type = pkt_type1  
 c$$$c      pkt_num = pkt_num1  
 c$$$c      obt = obt1  
 c$$$c      which_calib = which_calib1  
 c$$$      swcode = 302  
 c$$$  
 c$$$      which_calib = which_calib1  
 c$$$      pkt_type = pkt_type1  
 c$$$      pkt_num = pkt_num1  
 c$$$      obt = obt1  
 c$$$      cpu_crc = cpu_crc1  
 c$$$      do iv=1,12  
 c$$$         crc(iv)=crc1(iv)  
 c$$$      enddo  
 c$$$# endif  
 c*****************************************************  
   
3714        NTRK = 0        NTRK = 0
3715        do it=1,NTRKMAX!NTRACKSMAX        do it=1,NTRKMAX
3716           IMAGE(IT)=0           IMAGE(IT)=0
3717           CHI2_nt(IT) = -100000.           CHI2_nt(IT) = -100000.
 c         BdL(IT) = 0.  
3718           do ip=1,nplanes           do ip=1,nplanes
3719              XM_nt(IP,IT) = 0              XM_nt(IP,IT) = 0
3720              YM_nt(IP,IT) = 0              YM_nt(IP,IT) = 0
3721              ZM_nt(IP,IT) = 0              ZM_nt(IP,IT) = 0
3722              RESX_nt(IP,IT) = 0              RESX_nt(IP,IT) = 0
3723              RESY_nt(IP,IT) = 0              RESY_nt(IP,IT) = 0
3724                TAILX_nt(IP,IT) = 0
3725                TAILY_nt(IP,IT) = 0
3726                XBAD(IP,IT) = 0
3727                YBAD(IP,IT) = 0
3728              XGOOD_nt(IP,IT) = 0              XGOOD_nt(IP,IT) = 0
3729              YGOOD_nt(IP,IT) = 0              YGOOD_nt(IP,IT) = 0
3730  c*****************************************************              LS(IP,IT) = 0
 cccccc 11/9/2005 modified by david fedele  
3731              DEDX_X(IP,IT) = 0              DEDX_X(IP,IT) = 0
3732              DEDX_Y(IP,IT) = 0              DEDX_Y(IP,IT) = 0
 c******************************************************  
 cccccc 17/8/2006 modified by elena  
3733              CLTRX(IP,IT) = 0              CLTRX(IP,IT) = 0
3734              CLTRY(IP,IT) = 0              CLTRY(IP,IT) = 0
3735           enddo           enddo
# Line 3700  cccccc 17/8/2006 modified by elena Line 3740  cccccc 17/8/2006 modified by elena
3740              enddo                                enddo                  
3741           enddo                             enddo                  
3742        enddo        enddo
         
         
 c*****************************************************  
 cccccc 11/9/2005 modified by david fedele  
3743        nclsx=0        nclsx=0
3744        nclsy=0              nclsy=0      
3745        do ip=1,NSINGMAX        do ip=1,NSINGMAX
3746          planex(ip)=0          planex(ip)=0
 c        xs(ip)=0  
3747          xs(1,ip)=0          xs(1,ip)=0
3748          xs(2,ip)=0          xs(2,ip)=0
3749          sgnlxs(ip)=0          sgnlxs(ip)=0
3750          planey(ip)=0          planey(ip)=0
 c        ys(ip)=0  
3751          ys(1,ip)=0          ys(1,ip)=0
3752          ys(2,ip)=0          ys(2,ip)=0
3753          sgnlys(ip)=0          sgnlys(ip)=0
3754        enddo        enddo
 c*******************************************************  
3755        end        end
3756    
3757    
# Line 3733  c*************************************** Line 3766  c***************************************
3766  ************************************************************  ************************************************************
3767    
3768    
3769          subroutine init_hough
3770    
3771          include 'commontracker.f'
3772          include 'level1.f'
3773          include 'common_momanhough.f'
3774          include 'common_hough.f'
3775          include 'level2.f'
3776    
3777          ntrpt_nt=0
3778          ndblt_nt=0
3779          NCLOUDS_XZ_nt=0
3780          NCLOUDS_YZ_nt=0
3781          do idb=1,ndblt_max_nt
3782             db_cloud_nt(idb)=0
3783             alfayz1_nt(idb)=0      
3784             alfayz2_nt(idb)=0      
3785          enddo
3786          do itr=1,ntrpt_max_nt
3787             tr_cloud_nt(itr)=0
3788             alfaxz1_nt(itr)=0      
3789             alfaxz2_nt(itr)=0      
3790             alfaxz3_nt(itr)=0      
3791          enddo
3792          do idb=1,ncloyz_max      
3793            ptcloud_yz_nt(idb)=0    
3794            alfayz1_av_nt(idb)=0    
3795            alfayz2_av_nt(idb)=0    
3796          enddo                    
3797          do itr=1,ncloxz_max      
3798            ptcloud_xz_nt(itr)=0    
3799            alfaxz1_av_nt(itr)=0    
3800            alfaxz2_av_nt(itr)=0    
3801            alfaxz3_av_nt(itr)=0    
3802          enddo                    
3803    
3804          ntrpt=0                  
3805          ndblt=0                  
3806          NCLOUDS_XZ=0              
3807          NCLOUDS_YZ=0              
3808          do idb=1,ndblt_max        
3809            db_cloud(idb)=0        
3810            cpyz1(idb)=0            
3811            cpyz2(idb)=0            
3812            alfayz1(idb)=0          
3813            alfayz2(idb)=0          
3814          enddo                    
3815          do itr=1,ntrpt_max        
3816            tr_cloud(itr)=0        
3817            cpxz1(itr)=0            
3818            cpxz2(itr)=0            
3819            cpxz3(itr)=0            
3820            alfaxz1(itr)=0          
3821            alfaxz2(itr)=0          
3822            alfaxz3(itr)=0          
3823          enddo                    
3824          do idb=1,ncloyz_max      
3825            ptcloud_yz(idb)=0      
3826            alfayz1_av(idb)=0      
3827            alfayz2_av(idb)=0      
3828            do idbb=1,ncouplemaxtot
3829              cpcloud_yz(idb,idbb)=0
3830            enddo                  
3831          enddo                    
3832          do itr=1,ncloxz_max      
3833            ptcloud_xz(itr)=0      
3834            alfaxz1_av(itr)=0      
3835            alfaxz2_av(itr)=0      
3836            alfaxz3_av(itr)=0      
3837            do itrr=1,ncouplemaxtot
3838              cpcloud_xz(itr,itrr)=0
3839            enddo                  
3840          enddo                    
3841          end
3842    ************************************************************
3843    *
3844    *
3845    *
3846    *
3847    *
3848    *
3849    *
3850    ************************************************************
3851    
3852    
3853        subroutine fill_level2_tracks(ntr)        subroutine fill_level2_tracks(ntr)
3854    
3855  *     -------------------------------------------------------  *     -------------------------------------------------------
# Line 3744  c*************************************** Line 3861  c***************************************
3861            
3862        include 'commontracker.f'        include 'commontracker.f'
3863        include 'level1.f'        include 'level1.f'
3864          include 'common_momanhough.f'
3865        include 'level2.f'        include 'level2.f'
3866        include 'common_mini_2.f'        include 'common_mini_2.f'
3867        include 'common_momanhough.f'        include 'calib.f'
3868        real sinth,phi,pig        !(4)  
3869          character*10 PFA
3870          common/FINALPFA/PFA
3871    
3872          real sinth,phi,pig
3873          integer ssensor,sladder
3874        pig=acos(-1.)        pig=acos(-1.)
3875    
3876  c      good2=1!.true.  *     -------------------------------------
3877        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3878        nstep_nt(ntr)       = 0!nstep        nstep_nt(ntr)       = nstep
3879    *     -------------------------------------
3880        phi   = al(4)             !(4)        phi   = al(4)          
3881        sinth = al(3)             !(4)        sinth = al(3)            
3882        if(sinth.lt.0)then        !(4)        if(sinth.lt.0)then      
3883           sinth = -sinth         !(4)           sinth = -sinth        
3884           phi = phi + pig        !(4)           phi = phi + pig      
3885        endif                     !(4)        endif                    
3886        npig = aint(phi/(2*pig))  !(4)        npig = aint(phi/(2*pig))
3887        phi = phi - npig*2*pig    !(4)        phi = phi - npig*2*pig  
3888        if(phi.lt.0)              !(4)        if(phi.lt.0)            
3889       $     phi = phi + 2*pig    !(4)       $     phi = phi + 2*pig  
3890        al(4) = phi               !(4)        al(4) = phi              
3891        al(3) = sinth             !(4)        al(3) = sinth            
 *****************************************************  
3892        do i=1,5        do i=1,5
3893           al_nt(i,ntr)     = sngl(al(i))           al_nt(i,ntr)     = sngl(al(i))
3894           do j=1,5           do j=1,5
3895              coval(i,j,ntr) = sngl(cov(i,j))              coval(i,j,ntr) = sngl(cov(i,j))
3896           enddo           enddo
 c     print*,al_nt(i,ntr)  
3897        enddo        enddo
3898          *     -------------------------------------      
3899        do ip=1,nplanes           ! loop on planes        do ip=1,nplanes           ! loop on planes
3900           xgood_nt(ip,ntr) = int(xgood(ip))           xgood_nt(ip,ntr) = int(xgood(ip))
3901           ygood_nt(ip,ntr) = int(ygood(ip))           ygood_nt(ip,ntr) = int(ygood(ip))
# Line 3783  c     print*,al_nt(i,ntr) Line 3904  c     print*,al_nt(i,ntr)
3904           zm_nt(ip,ntr)    = sngl(zm(ip))           zm_nt(ip,ntr)    = sngl(zm(ip))
3905           RESX_nt(IP,ntr)  = sngl(resx(ip))           RESX_nt(IP,ntr)  = sngl(resx(ip))
3906           RESY_nt(IP,ntr)  = sngl(resy(ip))           RESY_nt(IP,ntr)  = sngl(resy(ip))
3907             TAILX_nt(IP,ntr) = 0.
3908             TAILY_nt(IP,ntr) = 0.
3909           xv_nt(ip,ntr)    = sngl(xv(ip))           xv_nt(ip,ntr)    = sngl(xv(ip))
3910           yv_nt(ip,ntr)    = sngl(yv(ip))           yv_nt(ip,ntr)    = sngl(yv(ip))
3911           zv_nt(ip,ntr)    = sngl(zv(ip))           zv_nt(ip,ntr)    = sngl(zv(ip))
3912           axv_nt(ip,ntr)   = sngl(axv(ip))           axv_nt(ip,ntr)   = sngl(axv(ip))
3913           ayv_nt(ip,ntr)   = sngl(ayv(ip))           ayv_nt(ip,ntr)   = sngl(ayv(ip))  
3914  c        dedxp(ip,ntr)    = sngl(dedxtrk(ip))   !(1)  
3915           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)) !(2)           factor = sqrt(
3916           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)) !(2)         $        tan( acos(-1.) * sngl(axv(ip)) /180. )**2 +
3917         $        tan( acos(-1.) * sngl(ayv(ip)) /180. )**2 +
3918         $        1. )
3919    
3920             dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)
3921             dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)  
3922        
3923           id  = CP_STORE(ip,IDCAND)           ax   = axv_nt(ip,ntr)
3924             ay   = ayv_nt(ip,ntr)
3925             bfx  = BX_STORE(ip,IDCAND)
3926             bfy  = BY_STORE(ip,IDCAND)
3927             if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)
3928             if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)
3929             tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001
3930             angx     = 180.*atan(tgtemp)/acos(-1.)
3931             tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001        
3932             angy    = 180.*atan(tgtemp)/acos(-1.)
3933            
3934    c         print*,'* ',ip,bfx,bfy,angx,angy
3935    
3936             id  = CP_STORE(ip,IDCAND) ! couple id
3937           icl = CLS_STORE(ip,IDCAND)           icl = CLS_STORE(ip,IDCAND)
3938             ssensor = -1
3939             sladder = -1
3940             ssensor = SENSOR_STORE(ip,IDCAND)
3941             sladder = LADDER_STORE(ip,IDCAND)
3942             if(ip.eq.6.and.ssensor.ne.0)ssensor = 3 - ssensor !notazione paolo x align
3943             LS(IP,ntr)      = ssensor+10*sladder
3944    
3945           if(id.ne.0)then           if(id.ne.0)then
3946    c           >>> is a couple
3947              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3948              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3949  c            print*,ip,' ',cltrx(ip,ntr),cltry(ip,ntr)  
3950                cl_used(cltrx(ip,ntr)) = 1     !tag used clusters          
3951                cl_used(cltry(ip,ntr)) = 1     !tag used clusters          
3952    
3953    c$$$            nnnnx = npfastrips(clx(nplanes-ip+1,icp_cp(id)),PFA,angx)
3954    c$$$            nnnny = npfastrips(cly(nplanes-ip+1,icp_cp(id)),PFA,angy)            
3955    c$$$            xbad(ip,ntr)= nbadstrips(nnnnx,clx(nplanes-ip+1,icp_cp(id)))
3956    c$$$            ybad(ip,ntr)= nbadstrips(nnnny,cly(nplanes-ip+1,icp_cp(id)))
3957                xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))
3958                ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))
3959    
3960    
3961                if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3962         $           dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3963                if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3964         $           dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3965    
3966           elseif(icl.ne.0)then           elseif(icl.ne.0)then
3967              if(mod(VIEW(icl),2).eq.0)cltrx(ip,ntr)=icl  
3968              if(mod(VIEW(icl),2).eq.1)cltry(ip,ntr)=icl              cl_used(icl) = 1    !tag used clusters          
3969  c            print*,ip,' ',cltrx(ip,ntr),cltry(ip,ntr)  
3970                if(mod(VIEW(icl),2).eq.0)then
3971                   cltrx(ip,ntr)=icl
3972    c$$$               nnnnn = npfastrips(icl,PFA,angx)
3973    c$$$               xbad(ip,ntr) = nbadstrips(nnnnn,icl)
3974                   xbad(ip,ntr) = nbadstrips(4,icl)
3975    
3976                   if(nsatstrips(icl).gt.0)dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3977                elseif(mod(VIEW(icl),2).eq.1)then
3978                   cltry(ip,ntr)=icl
3979    c$$$               nnnnn = npfastrips(icl,PFA,angy)
3980    c$$$               ybad(ip,ntr) = nbadstrips(nnnnn,icl)
3981                   ybad(ip,ntr) = nbadstrips(4,icl)
3982                   if(nsatstrips(icl).gt.0)dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3983                endif
3984    
3985           endif                     endif          
3986    
3987        enddo        enddo
 c      call CalcBdL(100,xxxx,IFAIL)  
 c      if(ifps(xxxx).eq.1)BdL(ntr) = xxxx  
 c$$$      print*,'xgood(ip,ntr) ',(xgood_nt(ip,ntr),ip=1,6)  
 c$$$      print*,'ygood(ip,ntr) ',(ygood_nt(ip,ntr),ip=1,6)  
 c$$$      print*,'dedx_x(ip,ntr) ',(dedx_x(ip,ntr),ip=1,6)  
 c$$$      print*,'dedx_y(ip,ntr) ',(dedx_y(ip,ntr),ip=1,6)  
3988    
3989          if(DEBUG.eq.1)then
3990             print*,'> STORING TRACK ',ntr
3991             print*,'clusters: '
3992             do ip=1,6
3993                print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)
3994             enddo
3995          endif
3996    
3997    c$$$      print*,(xgood(i),i=1,6)
3998    c$$$      print*,(ygood(i),i=1,6)
3999    c$$$      print*,(ls(i,ntr),i=1,6)
4000    c$$$      print*,(dedx_x(i,ntr),i=1,6)
4001    c$$$      print*,(dedx_y(i,ntr),i=1,6)
4002    c$$$      print*,'-----------------------'
4003    
4004        end        end
4005    
4006        subroutine fill_level2_siglets        subroutine fill_level2_siglets
 c*****************************************************  
 c     07/10/2005 created by elena vannuccini  
 c     31/01/2006 modified by elena vannuccini  
 *     to convert adc to mip  --> (2)  
 c*****************************************************  
4007    
4008  *     -------------------------------------------------------  *     -------------------------------------------------------
4009  *     This routine fills the  elements of the variables  *     This routine fills the  elements of the variables
# Line 3829  c*************************************** Line 4012  c***************************************
4012  *     -------------------------------------------------------  *     -------------------------------------------------------
4013    
4014        include 'commontracker.f'        include 'commontracker.f'
       include 'level1.f'  
       include 'level2.f'  
4015        include 'calib.f'        include 'calib.f'
4016          include 'level1.f'
4017        include 'common_momanhough.f'        include 'common_momanhough.f'
4018          include 'level2.f'
4019        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
4020    
4021  *     count #cluster per plane not associated to any track  *     count #cluster per plane not associated to any track
 c      good2=1!.true.  
4022        nclsx = 0        nclsx = 0
4023        nclsy = 0        nclsy = 0
4024    
4025          do iv = 1,nviews
4026    c         if( mask_view(iv).ne.0 )good2(iv) = 20+mask_view(iv)
4027             good2(iv) = good2(iv) + mask_view(iv)*2**8
4028          enddo
4029    
4030          if(DEBUG.eq.1)then
4031             print*,'> STORING SINGLETS '
4032          endif
4033    
4034        do icl=1,nclstr1        do icl=1,nclstr1
4035    
4036             ip=nplanes-npl(VIEW(icl))+1            
4037            
4038           if(cl_used(icl).eq.0)then !cluster not included in any track           if(cl_used(icl).eq.0)then !cluster not included in any track
             ip=nplanes-npl(VIEW(icl))+1              
4039              if(mod(VIEW(icl),2).eq.0)then !=== X views              if(mod(VIEW(icl),2).eq.0)then !=== X views
4040                 nclsx = nclsx + 1                 nclsx = nclsx + 1
4041                 planex(nclsx) = ip                 planex(nclsx) = ip
4042                 sgnlxs(nclsx) = dedx(icl)/mip(VIEW(icl),LADDER(icl))!(2)                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4043                   if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)
4044                 clsx(nclsx)   = icl                 clsx(nclsx)   = icl
4045                 do is=1,2                 do is=1,2
4046  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4047                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
4048                      call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)
4049                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2
4050                 enddo                 enddo
4051  c$$$               print*,'nclsx         ',nclsx  c$$$               print*,'nclsx         ',nclsx
# Line 3861  c$$$               print*,'xs(2,nclsx)   Line 4056  c$$$               print*,'xs(2,nclsx)  
4056              else                          !=== Y views              else                          !=== Y views
4057                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4058                 planey(nclsy) = ip                 planey(nclsy) = ip
4059                 sgnlys(nclsy) = dedx(icl)/mip(VIEW(icl),LADDER(icl))!(2)                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4060                   if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)
4061                 clsy(nclsy)   = icl                 clsy(nclsy)   = icl
4062                 do is=1,2                 do is=1,2
4063  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4064                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
4065                      call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)
4066                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2
4067                 enddo                 enddo
4068  c$$$               print*,'nclsy         ',nclsy  c$$$               print*,'nclsy         ',nclsy
# Line 3875  c$$$               print*,'ys(1,nclsy)   Line 4072  c$$$               print*,'ys(1,nclsy)  
4072  c$$$               print*,'ys(2,nclsy)   ',ys(2,nclsy)  c$$$               print*,'ys(2,nclsy)   ',ys(2,nclsy)
4073              endif              endif
4074           endif           endif
 c      print*,icl,cl_used(icl),cl_good(icl),ip,VIEW(icl)!nclsx(ip),nclsy(ip)  
4075    
4076  ***** LO METTO QUI PERCHE` NON SO DOVE METTERLO  ***** LO METTO QUI PERCHE` NON SO DOVE METTERLO
4077           whichtrack(icl) = cl_used(icl)           whichtrack(icl) = cl_used(icl)
4078    *     --------------------------------------------------
4079    *     per non perdere la testa...
4080    *     whichtrack(icl) e` una variabile del common level1
4081    *     che serve solo per sapere quali cluster sono stati
4082    *     associati ad una traccia, e permettere di salvare
4083    *     solo questi nell'albero di uscita
4084    *     --------------------------------------------------
4085            
4086    
4087    c$$$         print*,' cl ',icl,' --> ',cl_used(icl)
4088    c$$$
4089    c$$$         if( cl_used(icl).ne.0 )then
4090    c$$$            if(
4091    c$$$     $           mod(VIEW(icl),2).eq.0.and.
4092    c$$$     $           cltrx(ip,whichtrack(icl)).ne.icl )
4093    c$$$     $           print*,'**WARNING** cltrx(',ip,',',whichtrack(icl)
4094    c$$$     $           ,')=',cltrx(ip,whichtrack(icl)),'.ne.',icl
4095    c$$$            if(
4096    c$$$     $           mod(VIEW(icl),2).eq.1.and.
4097    c$$$     $           cltry(ip,whichtrack(icl)).ne.icl )
4098    c$$$     $           print*,'**WARNING** cltry(',ip,',',whichtrack(icl)
4099    c$$$     $           ,')=',cltry(ip,whichtrack(icl)),'.ne.',icl
4100    c$$$         endif
4101            
4102    
4103        enddo        enddo
4104        end        end
4105    
4106    ***************************************************
4107    *                                                 *
4108    *                                                 *
4109    *                                                 *
4110    *                                                 *
4111    *                                                 *
4112    *                                                 *
4113    **************************************************
4114    
4115          subroutine fill_hough
4116    
4117    *     -------------------------------------------------------
4118    *     This routine fills the  variables related to the hough
4119    *     transform, for the debig n-tuple
4120    *     -------------------------------------------------------
4121    
4122          include 'commontracker.f'
4123          include 'level1.f'
4124          include 'common_momanhough.f'
4125          include 'common_hough.f'
4126          include 'level2.f'
4127    
4128          if(.false.
4129         $     .or.ntrpt.gt.ntrpt_max_nt
4130         $     .or.ndblt.gt.ndblt_max_nt
4131         $     .or.NCLOUDS_XZ.gt.ncloxz_max
4132         $     .or.NCLOUDS_yZ.gt.ncloyz_max
4133         $     )then
4134             ntrpt_nt=0
4135             ndblt_nt=0
4136             NCLOUDS_XZ_nt=0
4137             NCLOUDS_YZ_nt=0
4138          else
4139             ndblt_nt=ndblt
4140             ntrpt_nt=ntrpt
4141             if(ndblt.ne.0)then
4142                do id=1,ndblt
4143                   alfayz1_nt(id)=alfayz1(id) !Y0
4144                   alfayz2_nt(id)=alfayz2(id) !tg theta-yz
4145                enddo
4146             endif
4147             if(ndblt.ne.0)then
4148                do it=1,ntrpt
4149                   alfaxz1_nt(it)=alfaxz1(it) !X0
4150                   alfaxz2_nt(it)=alfaxz2(it) !tg theta-xz
4151                   alfaxz3_nt(it)=alfaxz3(it) !1/r
4152                enddo
4153             endif
4154             nclouds_yz_nt=nclouds_yz
4155             nclouds_xz_nt=nclouds_xz
4156             if(nclouds_yz.ne.0)then
4157                nnn=0
4158                do iyz=1,nclouds_yz
4159                   ptcloud_yz_nt(iyz)=ptcloud_yz(iyz)
4160                   alfayz1_av_nt(iyz)=alfayz1_av(iyz)
4161                   alfayz2_av_nt(iyz)=alfayz2_av(iyz)
4162                   nnn=nnn+ptcloud_yz(iyz)
4163                enddo
4164                do ipt=1,nnn
4165                   db_cloud_nt(ipt)=db_cloud(ipt)
4166                 enddo
4167             endif
4168             if(nclouds_xz.ne.0)then
4169                nnn=0
4170                do ixz=1,nclouds_xz
4171                   ptcloud_xz_nt(ixz)=ptcloud_xz(ixz)
4172                   alfaxz1_av_nt(ixz)=alfaxz1_av(ixz)
4173                   alfaxz2_av_nt(ixz)=alfaxz2_av(ixz)
4174                   alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)
4175                   nnn=nnn+ptcloud_xz(ixz)              
4176                enddo
4177                do ipt=1,nnn
4178                  tr_cloud_nt(ipt)=tr_cloud(ipt)
4179                 enddo
4180             endif
4181          endif
4182          end
4183          

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.30

  ViewVC Help
Powered by ViewVC 1.1.23