/[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.30 by pam-fi, Tue Aug 28 13:25:50 2007 UTC revision 1.37 by pam-fi, Fri Dec 5 08:26:47 2008 UTC
# Line 20  Line 20 
20        include 'calib.f'        include 'calib.f'
21        include 'level2.f'        include 'level2.f'
22    
   
   
23  c      print*,'======================================================'  c      print*,'======================================================'
24  c$$$      do ic=1,NCLSTR1  c$$$      do ic=1,NCLSTR1
25  c$$$         if(.false.  c$$$         if(.false.
# Line 74  c$$$      enddo Line 72  c$$$      enddo
72  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
73  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
74    
   
75        call cl_to_couples(iflag)        call cl_to_couples(iflag)
76        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
77           goto 880               !go to next event           goto 880               !go to next event
78        endif        endif
79                if(ncp_tot.eq.0)goto 880  !go to next event    
80  *-----------------------------------------------------  *-----------------------------------------------------
81  *-----------------------------------------------------  *-----------------------------------------------------
82  *     HOUGH TRASFORM  *     HOUGH TRASFORM
# Line 113  c$$$      enddo Line 110  c$$$      enddo
110        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
111           goto 880               !go to next event                       goto 880               !go to next event            
112        endif        endif
113          if(ndblt.eq.0.or.ntrpt.eq.0)goto 880 !go to next event    
114                
115                
116  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
# Line 163  c$$$      enddo Line 161  c$$$      enddo
161        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
162           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
163        endif        endif
164    *     ------------------------------------------------
165    *     first try to release the tolerance
166    *     ------------------------------------------------
167        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then
168          if(cutdistyz.lt.maxcuty/2)then           if(cutdistyz.lt.maxcuty/2)then
169            cutdistyz=cutdistyz+cutystep              cutdistyz=cutdistyz+cutystep
170          else           else
171            cutdistyz=cutdistyz+(3*cutystep)              cutdistyz=cutdistyz+(3*cutystep)
172          endif           endif
173          goto 878                           if(DEBUG.EQ.1)print*,'try again - cutdistyz ',cutdistyz
174        endif                               goto 878                
175          endif    
176    *     ------------------------------------------------
177    *     hence reduce the minimum number of plane
178    *     ------------------------------------------------
179          if(nclouds_yz.eq.0.and.nplyz_min.gt.3)then
180             nplyz_min=nplyz_min-1
181             if(DEBUG.EQ.1)print*,'try again - nplyz_min ',nplyz_min
182             goto 878
183          endif
184    
185          if(nclouds_yz.eq.0)goto 880 !go to next event    
186    
187        if(planehit.eq.3) goto 881            
188    ccc   if(planehit.eq.3) goto 881    
189                
190   879  continue     879  continue  
191        call trip_to_XZcloud(iflag)        call trip_to_XZcloud(iflag)
192        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
193           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
194        endif        endif
195                              *     ------------------------------------------------
196    *     first try to release the tolerance
197    *     ------------------------------------------------                          
198        if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then        if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then
199          cutdistxz=cutdistxz+cutxstep          cutdistxz=cutdistxz+cutxstep
200             if(DEBUG.EQ.1)print*,'try again - cutdistxz ',cutdistxz
201          goto 879                          goto 879                
202        endif                            endif                    
203    *     ------------------------------------------------
204    *     hence reduce the minimum number of plane
205    *     ------------------------------------------------
206          if(nclouds_xz.eq.0.and.nplxz_min.gt.3)then
207             nplxz_min=nplxz_min-1
208             if(DEBUG.EQ.1)print*,'try again - nplxz_min ',nplxz_min
209             goto 879
210          endif
211    
212          if(nclouds_xz.eq.0)goto 880 !go to next event    
213    
214            
215   881  continue    c$$$ 881  continue  
216  *     if there is at least three planes on the Y view decreases cuts on X view  c$$$*     if there is at least three planes on the Y view decreases cuts on X view
217        if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.  c$$$      if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.
218       $     nplxz_min.ne.y_min_start)then  c$$$     $     nplxz_min.ne.y_min_start)then
219          nptxz_min=x_min_step      c$$$        nptxz_min=x_min_step    
220          nplxz_min=x_min_start-x_min_step                c$$$        nplxz_min=x_min_start-x_min_step              
221          goto 879                  c$$$        goto 879                
222        endif                      c$$$      endif                    
223                    
224   880  return   880  return
225        end        end
# Line 243  c      include 'momanhough_init.f' Line 269  c      include 'momanhough_init.f'
269  *  *
270  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
271  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
272           ntrk=0                 !counter of identified physical tracks  ccc         ntrk=0                 !counter of identified physical tracks
273    
274  11111    continue               !<<<<<<< come here when performing a new search  11111    continue               !<<<<<<< come here when performing a new search
275    
276             if(nclouds_xz.eq.0)goto 880 !go to next event    
277             if(nclouds_yz.eq.0)goto 880 !go to next event    
278    
279  c         iflag=0  c         iflag=0
280           call clouds_to_ctrack(iflag)           call clouds_to_ctrack(iflag)
281           if(iflag.eq.1)then     !no candidate tracks found           if(iflag.eq.1)then     !no candidate tracks found
282              goto 880            !fill ntp and go to next event                goto 880            !fill ntp and go to next event  
283           endif           endif
284             if(ntracks.eq.0)goto 880 !go to next event    
285    
286           FIMAGE=.false.         !processing best track (not track image)           FIMAGE=.false.         !processing best track (not track image)
287           ibest=0                !best track among candidates           ibest=0                !best track among candidates
# Line 295  c$$$         if(ibest.eq.0)goto 880 !>> Line 325  c$$$         if(ibest.eq.0)goto 880 !>>
325             endif             endif
326           enddo           enddo
327    
 c$$$         rchi2best=1000000000.  
 c$$$         ndofbest=0             !(1)  
 c$$$         do i=1,ntracks  
 c$$$           if(RCHI2_STORE(i).lt.rchi2best.and.  
 c$$$     $          RCHI2_STORE(i).gt.0)then  
 c$$$             ndof=0             !(1)  
 c$$$             do ii=1,nplanes    !(1)  
 c$$$               ndof=ndof        !(1)  
 c$$$     $              +int(xgood_store(ii,i)) !(1)  
 c$$$     $              +int(ygood_store(ii,i)) !(1)  
 c$$$             enddo              !(1)  
 c$$$             if(ndof.ge.ndofbest)then !(1)  
 c$$$               ibest=i  
 c$$$               rchi2best=RCHI2_STORE(i)  
 c$$$               ndofbest=ndof    !(1)  
 c$$$             endif              !(1)  
 c$$$           endif  
 c$$$         enddo  
328    
329           if(ibest.eq.0)goto 880 !>> no good candidates           if(ibest.eq.0)goto 880 !>> no good candidates
330  *-------------------------------------------------------------------------------      *-------------------------------------------------------------------------------    
# Line 350  c$$$         enddo Line 362  c$$$         enddo
362           do i=1,5           do i=1,5
363              AL_GUESS(i)=AL(i)              AL_GUESS(i)=AL(i)
364           enddo           enddo
 c         print*,'## guess: ',al  
365    
366           do i=1,5           do i=1,5
367              AL(i)=dble(AL_STORE(i,icand))                          AL(i)=dble(AL_STORE(i,icand))            
# Line 371  c         if(DEBUG.EQ.1)iprint=1 Line 382  c         if(DEBUG.EQ.1)iprint=1
382       $              '*** MINIMIZATION FAILURE *** (after refinement) '       $              '*** MINIMIZATION FAILURE *** (after refinement) '
383       $              ,iev       $              ,iev
384    
 c$$$               print*,'guess:   ',(al_guess(i),i=1,5)  
 c$$$               print*,'previous: ',(al_store(i,icand),i=1,5)  
 c$$$               print*,'result:   ',(al(i),i=1,5)  
 c$$$               print*,'xgood ',xgood  
 c$$$               print*,'ygood ',ygood  
 c$$$               print*,'----------------------------------------------'  
385              endif              endif
 c            chi2=-chi2  
386           endif           endif
387                    
388           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
# Line 424  c         rchi2=chi2/dble(ndof) Line 428  c         rchi2=chi2/dble(ndof)
428              if(WARNING.EQ.1)print*,'** WARNING ** sensor=0'              if(WARNING.EQ.1)print*,'** WARNING ** sensor=0'
429              goto 122            !jump              goto 122            !jump
430           endif           endif
 c         print*,'is1 ',is1  
431           do ip=1,NPLANES           do ip=1,NPLANES
432              is2 = SENSOR_STORE(ip,icand) !sensor              is2 = SENSOR_STORE(ip,icand) !sensor
 c            print*,'is2 ',is2,' ip ',ip  
433              if(ip.eq.6.and.is2.ne.0)is2=3-is2 !last plane inverted              if(ip.eq.6.and.is2.ne.0)is2=3-is2 !last plane inverted
434              if(              if(
435       $           (is1.ne.is2.and.is2.ne.0)       $           (is1.ne.is2.and.is2.ne.0)
436       $           )goto 122      !jump (this track cannot have an image)       $           )goto 122      !jump (this track cannot have an image)
437           enddo           enddo
438           if(DEBUG.eq.1)print*,' >>> ambiguous track! '           if(DEBUG.eq.1)print*,' >>> ambiguous track! '
 *     now search for track-image among track candidates  
 c$$$         do i=1,ntracks  
 c$$$            iimage=i  
 c$$$            do ip=1,nplanes  
 c$$$               if(     CP_STORE(nplanes-ip+1,icand).ne.  
 c$$$     $              -1*CP_STORE(nplanes-ip+1,i).and.  
 c$$$     $              CP_STORE(nplanes-ip+1,i).ne.0.and.  
 c$$$     $              CP_STORE(nplanes-ip+1,icand).ne.0 )iimage=0  
 c$$$               print*,' track ',i,' CP ',CP_STORE(nplanes-ip+1,i)  
 c$$$     $              ,CP_STORE(nplanes-ip+1,icand),iimage  
 c$$$            enddo  
 c$$$            if(  iimage.ne.0.and.  
 c$$$c     $           RCHI2_STORE(i).le.CHI2MAX.and.  
 c$$$c     $           RCHI2_STORE(i).gt.0.and.  
 c$$$     $           .true.)then  
 c$$$               if(DEBUG.EQ.1)print*,'Track candidate ',iimage  
 c$$$     $              ,' >>> TRACK IMAGE >>> of'  
 c$$$     $              ,ibest  
 c$$$               goto 122         !image track found  
 c$$$            endif  
 c$$$         enddo  
439  *     ---------------------------------------------------------------  *     ---------------------------------------------------------------
440  *     take the candidate with the greatest number of matching couples  *     take the candidate with the greatest number of matching couples
441  *     if more than one satisfies the requirement,  *     if more than one satisfies the requirement,
# Line 486  c$$$         enddo Line 467  c$$$         enddo
467                                            
468                    endif                    endif
469                 endif                 endif
 c$$$               print*,' track ',i,' CP ',CP_STORE(nplanes-ip+1,i)  
 c$$$     $              ,CP_STORE(nplanes-ip+1,icand),ncp  
470              enddo              enddo
471   117        continue   117        continue
472              trackimage(i)=ncp   !number of matching couples              trackimage(i)=ncp   !number of matching couples
# Line 501  c$$$     $              ,CP_STORE(nplane Line 480  c$$$     $              ,CP_STORE(nplane
480           do i=1,ntracks           do i=1,ntracks
481              if( ncpmax.ne.0.and.trackimage(i).eq.ncpmax )ngood=ngood+1              if( ncpmax.ne.0.and.trackimage(i).eq.ncpmax )ngood=ngood+1
482           enddo           enddo
483             if(DEBUG.eq.1)print*,' n.image-candidates : ',ngood
484  *     if there are, choose the best one  *     if there are, choose the best one
485           if(ngood.gt.1)then           if(ngood.gt.0)then
486  *     -------------------------------------------------------  *     -------------------------------------------------------
487  *     order track-candidates according to:  *     order track-candidates according to:
488  *     1st) decreasing n.points  *     1st) decreasing n.points
# Line 532  c$$$     $              ,CP_STORE(nplane Line 512  c$$$     $              ,CP_STORE(nplane
512                    endif                    endif
513                 endif                 endif
514              enddo              enddo
515    
516                if(DEBUG.EQ.1)then
517                   print*,'Track candidate ',iimage
518         $              ,' >>> TRACK IMAGE >>> of'
519         $              ,ibest
520                endif
521                            
522           endif           endif
523    
          if(DEBUG.EQ.1)print*,'Track candidate ',iimage  
      $        ,' >>> TRACK IMAGE >>> of'  
      $        ,ibest  
524    
525   122     continue   122     continue
526    
# Line 550  c$$$     $              ,CP_STORE(nplane Line 533  c$$$     $              ,CP_STORE(nplane
533       $        .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next       $        .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next
534           if(FIMAGE)     image(ntrk)=ntrk-1 !this is the image of the previous           if(FIMAGE)     image(ntrk)=ntrk-1 !this is the image of the previous
535           call fill_level2_tracks(ntrk)     !==> good2=.true.           call fill_level2_tracks(ntrk)     !==> good2=.true.
 c         print*,'++++++++++ iimage,fimage,ntrk,image '  
 c     $        ,iimage,fimage,ntrk,image(ntrk)  
536    
537           if(ntrk.eq.NTRKMAX)then           if(ntrk.eq.NTRKMAX)then
538              if(verbose.eq.1)              if(verbose.eq.1)
# Line 567  cc            good2=.false. Line 548  cc            good2=.false.
548              goto 1212           !>>> fit image-track              goto 1212           !>>> fit image-track
549           endif           endif
550    
 *     --- then remove selected clusters (ibest+iimage) from clouds ----  
          call clean_XYclouds(ibest,iflag)  
          if(iflag.eq.1)then     !bad event  
             goto 880            !fill ntp and go to next event              
          endif  
   
 *     **********************************************************  
 *     condition to start a new search  
 *     **********************************************************  
          ixznew=0  
          do ixz=1,nclouds_xz  
             if(ptcloud_xz(ixz).ge.nptxz_min)ixznew=1  
          enddo  
          iyznew=0  
          do iyz=1,nclouds_yz  
             if(ptcloud_yz(iyz).ge.nptyz_min)iyznew=1  
          enddo  
           
          if(ixznew.ne.0.and.  
      $      iyznew.ne.0.and.  
      $        rchi2best.le.CHI2MAX.and.  
 c     $        rchi2best.lt.15..and.  
      $        .true.)then  
             if(DEBUG.EQ.1)then  
                print*,'***** NEW SEARCH ****'  
             endif  
             goto 11111          !try new search  
               
          endif  
 *     **********************************************  
   
   
551    
552   880     return   880     return
553        end        end
# Line 688  c     $        rchi2best.lt.15..and. Line 637  c     $        rchi2best.lt.15..and.
637    
638        real stripx,stripy        real stripx,stripy
639    
640          double precision xi,yi,zi
641          double precision xi_A,yi_A,zi_A
642          double precision xi_B,yi_B,zi_B
643        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
644        double precision xrt_A,yrt_A,zrt_A        double precision xrt_A,yrt_A,zrt_A
645        double precision xrt_B,yrt_B,zrt_B        double precision xrt_B,yrt_B,zrt_B
# Line 696  c     $        rchi2best.lt.15..and. Line 648  c     $        rchi2best.lt.15..and.
648        parameter (ndivx=30)        parameter (ndivx=30)
649    
650    
 c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy  
651                
652        resxPAM = 0        resxPAM = 0
653        resyPAM = 0        resyPAM = 0
654    
655        xPAM = 0.        xPAM = 0.D0
656        yPAM = 0.        yPAM = 0.D0
657        zPAM = 0.        zPAM = 0.D0
658        xPAM_A = 0.        xPAM_A = 0.D0
659        yPAM_A = 0.        yPAM_A = 0.D0
660        zPAM_A = 0.        zPAM_A = 0.D0
661        xPAM_B = 0.        xPAM_B = 0.D0
662        yPAM_B = 0.        yPAM_B = 0.D0
663        zPAM_B = 0.        zPAM_B = 0.D0
 c      print*,'## xyz_PAM: ',icx,icy,sensor,PFAx,PFAy,angx,angy  
664    
665        if(sensor.lt.1.or.sensor.gt.2)then        if(sensor.lt.1.or.sensor.gt.2)then
666           print*,'xyz_PAM   ***ERROR*** wrong input '           print*,'xyz_PAM   ***ERROR*** wrong input '
# Line 727  c      print*,'## xyz_PAM: ',icx,icy,sen Line 677  c      print*,'## xyz_PAM: ',icx,icy,sen
677           viewx   = VIEW(icx)           viewx   = VIEW(icx)
678           nldx    = nld(MAXS(icx),VIEW(icx))           nldx    = nld(MAXS(icx),VIEW(icx))
679           nplx    = npl(VIEW(icx))           nplx    = npl(VIEW(icx))
680           resxPAM = RESXAV  c         resxPAM = RESXAV
681           stripx  = float(MAXS(icx))           stripx  = float(MAXS(icx))
682    
683           if(           if(
# Line 747  c      print*,'## xyz_PAM: ',icx,icy,sen Line 697  c      print*,'## xyz_PAM: ',icx,icy,sen
697  *        --------------------------  *        --------------------------
698  *        magnetic-field corrections  *        magnetic-field corrections
699  *        --------------------------  *        --------------------------
700           angtemp  = ax           stripx  = stripx +  fieldcorr(viewx,bfy)      
701           bfytemp  = bfy           angx    = effectiveangle(ax,viewx,bfy)
 *        /////////////////////////////////  
 *        AAAAHHHHHHHH!!!!!!!!!!!!!!!!!!!!!  
 *        *grvzkkjsdgjhhhgngbn###>:(  
 *        /////////////////////////////////  
 c         if(nplx.eq.6) angtemp = -1. * ax  
 c         if(nplx.eq.6) bfytemp = -1. * bfy  
          if(viewx.eq.12) angtemp = -1. * ax  
          if(viewx.eq.12) bfytemp = -1. * bfy  
          tgtemp   = tan(angtemp*acos(-1.)/180.) + pmuH_h*bfytemp*0.00001  
          angx     = 180.*atan(tgtemp)/acos(-1.)  
          stripx   = stripx - 0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX  
 c$$$         print*,nplx,ax,bfy/10.  
 c$$$         print*,angx,0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX  
 c$$$         print*,'========================'  
 c$$$         if(bfy.ne.0.)print*,viewx,'-x- '  
 c$$$     $        ,bfy,-1*0.5*pmuH_h*bfytemp*0.00001*SiDimZ  
 *        --------------------------  
   
 c$$$         print*,'--- x-cl ---'  
 c$$$         istart = INDSTART(ICX)  
 c$$$         istop  = TOTCLLENGTH  
 c$$$         if(icx.lt.NCLSTR1)istop=INDSTART(ICX+1)-1  
 c$$$         print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)  
 c$$$         print*,(CLSIGNAL(i),i=istart,istop)  
 c$$$         print*,INDMAX(icx)  
 c$$$         print*,cog(4,icx)  
 c$$$         print*,fbad_cog(4,icx)  
702                    
703             call applypfa(PFAx,icx,angx,corr,res)
704           if(PFAx.eq.'COG1')then           stripx  = stripx + corr
705             resxPAM = res
             stripx  = stripx  
             resxPAM = 1e-4*pitchX/sqrt(12.)!!resxPAM  
   
          elseif(PFAx.eq.'COG2')then  
   
             stripx  = stripx + cog(2,icx)              
             resxPAM = risx_cog(abs(angx))!TEMPORANEO                
             resxPAM = resxPAM*fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'COG3')then  
   
             stripx  = stripx + cog(3,icx)              
             resxPAM = risx_cog(abs(angx))!TEMPORANEO                        
             resxPAM = resxPAM*fbad_cog(3,icx)  
   
          elseif(PFAx.eq.'COG4')then  
   
             stripx  = stripx + cog(4,icx)              
             resxPAM = risx_cog(abs(angx))!TEMPORANEO                        
             resxPAM = resxPAM*fbad_cog(4,icx)  
   
          elseif(PFAx.eq.'ETA2')then  
   
             stripx  = stripx + pfaeta2(icx,angx)            
             resxPAM = risxeta2(abs(angx))  
             resxPAM = resxPAM*fbad_cog(2,icx)  
 c$$$            if(DEBUG.EQ.1.and.fbad_cog(2,icx).ne.1)  
 c$$$     $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'ETA3')then                          
   
             stripx  = stripx + pfaeta3(icx,angx)            
             resxPAM = risxeta3(abs(angx))                        
             resxPAM = resxPAM*fbad_cog(3,icx)                
 c            if(DEBUG.and.fbad_cog(3,icx).ne.1)              
 c     $           print*,'BAD icx >>> ',viewx,fbad_cog(3,icx)  
   
          elseif(PFAx.eq.'ETA4')then                          
   
             stripx  = stripx + pfaeta4(icx,angx)              
             resxPAM = risxeta4(abs(angx))                        
             resxPAM = resxPAM*fbad_cog(4,icx)                
 c            if(DEBUG.and.fbad_cog(4,icx).ne.1)                
 c     $           print*,'BAD icx >>> ',viewx,fbad_cog(4,icx)  
   
          elseif(PFAx.eq.'ETA')then    
   
             stripx  = stripx + pfaeta(icx,angx)              
 c            resxPAM = riseta(icx,angx)                      
             resxPAM = riseta(viewx,angx)                      
             resxPAM = resxPAM*fbad_eta(icx,angx)              
 c            if(DEBUG.and.fbad_cog(2,icx).ne.1)                
 c     $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'ETAL')then    
   
             stripx  = stripx + pfaetal(icx,angx)              
             resxPAM = riseta(viewx,angx)                      
             resxPAM = resxPAM*fbad_eta(icx,angx)              
 c            if(DEBUG.and.fbad_cog(2,icx).ne.1)                
 c     $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'COG')then            
   
             stripx  = stripx + cog(0,icx)              
             resxPAM = risx_cog(abs(angx))                      
             resxPAM = resxPAM*fbad_cog(0,icx)  
   
          else  
             if(DEBUG.EQ.1) print*,'*** Non valid p.f.a. (x) --> ',PFAx  
          endif  
   
   
 *     ======================================  
 *     temporary patch for saturated clusters  
 *     ======================================  
          if( nsatstrips(icx).gt.0 )then  
             stripx  = stripx + cog(4,icx)              
             resxPAM = pitchX*1e-4/sqrt(12.)  
 cc            cc=cog(4,icx)  
 c$$$            print*,icx,' *** ',cc  
 c$$$            print*,icx,' *** ',resxPAM  
          endif  
706    
707   10   endif   10   endif
   
708            
709  *     -----------------  *     -----------------
710  *     CLUSTER Y  *     CLUSTER Y
# Line 876  c$$$            print*,icx,' *** ',resxP Line 715  c$$$            print*,icx,' *** ',resxP
715           viewy = VIEW(icy)           viewy = VIEW(icy)
716           nldy = nld(MAXS(icy),VIEW(icy))           nldy = nld(MAXS(icy),VIEW(icy))
717           nply = npl(VIEW(icy))           nply = npl(VIEW(icy))
718           resyPAM = RESYAV  c         resyPAM = RESYAV
719           stripy = float(MAXS(icy))           stripy = float(MAXS(icy))
720    
721           if(           if(
# Line 900  c$$$            print*,icx,' *** ',resxP Line 739  c$$$            print*,icx,' *** ',resxP
739              endif              endif
740              goto 100              goto 100
741           endif           endif
742    
743  *        --------------------------  *        --------------------------
744  *        magnetic-field corrections  *        magnetic-field corrections
745  *        --------------------------  *        --------------------------
746           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001                   stripy  = stripy +  fieldcorr(viewy,bfx)      
747           angy    = 180.*atan(tgtemp)/acos(-1.)           angy    = effectiveangle(ay,viewy,bfx)
          stripy = stripy + 0.5*pmuH_e*bfx*0.00001*SiDimZ/pitchY  
 c$$$         if(bfx.ne.0.)print*,viewy,'-y- '  
 c$$$     $        ,bfx,0.5*pmuH_e*bfx*0.00001*SiDimZ  
 *        --------------------------  
748                    
749  c$$$         print*,'--- y-cl ---'           call applypfa(PFAy,icy,angy,corr,res)
750  c$$$         istart = INDSTART(ICY)           stripy  = stripy + corr
751  c$$$         istop  = TOTCLLENGTH           resyPAM = res
 c$$$         if(icy.lt.NCLSTR1)istop=INDSTART(ICY+1)-1  
 c$$$         print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)  
 c$$$         print*,(CLSIGNAL(i),i=istart,istop)  
 c$$$         print*,INDMAX(icy)  
 c$$$         print*,cog(4,icy)  
 c$$$         print*,fbad_cog(4,icy)  
   
          if(PFAy.eq.'COG1')then  
   
             stripy  = stripy      
             resyPAM = 1e-4*pitchY/sqrt(12.)!resyPAM    
   
          elseif(PFAy.eq.'COG2')then  
   
             stripy  = stripy + cog(2,icy)  
             resyPAM = risy_cog(abs(angy))!TEMPORANEO  
             resyPAM = resyPAM*fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'COG3')then  
   
             stripy  = stripy + cog(3,icy)  
             resyPAM = risy_cog(abs(angy))!TEMPORANEO  
             resyPAM = resyPAM*fbad_cog(3,icy)  
   
          elseif(PFAy.eq.'COG4')then  
   
             stripy  = stripy + cog(4,icy)  
             resyPAM = risy_cog(abs(angy))!TEMPORANEO  
             resyPAM = resyPAM*fbad_cog(4,icy)  
   
          elseif(PFAy.eq.'ETA2')then  
   
             stripy  = stripy + pfaeta2(icy,angy)            
             resyPAM = risyeta2(abs(angy))                
             resyPAM = resyPAM*fbad_cog(2,icy)  
 c            if(DEBUG.and.fbad_cog(2,icy).ne.1)  
 c     $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'ETA3')then                        
   
             stripy  = stripy + pfaeta3(icy,angy)  
             resyPAM = resyPAM*fbad_cog(3,icy)    
 c            if(DEBUG.and.fbad_cog(3,icy).ne.1)  
 c     $           print*,'BAD icy >>> ',viewy,fbad_cog(3,icy)  
   
          elseif(PFAy.eq.'ETA4')then    
   
             stripy  = stripy + pfaeta4(icy,angy)  
             resyPAM = resyPAM*fbad_cog(4,icy)  
 c            if(DEBUG.and.fbad_cog(4,icy).ne.1)  
 c     $           print*,'BAD icy >>> ',viewy,fbad_cog(4,icy)  
   
          elseif(PFAy.eq.'ETA')then  
   
             stripy  = stripy + pfaeta(icy,angy)  
 c            resyPAM = riseta(icy,angy)    
             resyPAM = riseta(viewy,angy)    
             resyPAM = resyPAM*fbad_eta(icy,angy)  
 c            if(DEBUG.and.fbad_cog(2,icy).ne.1)  
 c     $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'ETAL')then  
   
             stripy  = stripy + pfaetal(icy,angy)  
             resyPAM = riseta(viewy,angy)    
             resyPAM = resyPAM*fbad_eta(icy,angy)  
 c            if(DEBUG.and.fbad_cog(2,icy).ne.1)  
 c     $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'COG')then  
   
             stripy  = stripy + cog(0,icy)              
             resyPAM = risy_cog(abs(angy))  
             resyPAM = resyPAM*fbad_cog(0,icy)  
   
          else  
             if(DEBUG.EQ.1) print*,'*** Non valid p.f.a. (x) --> ',PFAx  
          endif  
   
   
 *     ======================================  
 *     temporary patch for saturated clusters  
 *     ======================================  
          if( nsatstrips(icy).gt.0 )then  
             stripy  = stripy + cog(4,icy)              
             resyPAM = pitchY*1e-4/sqrt(12.)  
 cc            cc=cog(4,icy)  
 c$$$            print*,icy,' *** ',cc  
 c$$$            print*,icy,' *** ',resyPAM  
          endif  
   
752    
753   20   endif   20   endif
754    
 c$$$      print*,'## stripx,stripy ',stripx,stripy  
755    
756  c===========================================================  c===========================================================
757  C     COUPLE  C     COUPLE
# Line 1024  c--------------------------------------- Line 768  c---------------------------------------
768       $              ' WARNING: false X strip: strip ',stripx       $              ' WARNING: false X strip: strip ',stripx
769              endif              endif
770           endif           endif
771           xi = acoordsi(stripx,viewx)           xi = dcoordsi(stripx,viewx)
772           yi = acoordsi(stripy,viewy)           yi = dcoordsi(stripy,viewy)
773           zi = 0.           zi = 0.D0
774                    
   
775  c------------------------------------------------------------------------  c------------------------------------------------------------------------
776  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
777  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 1062  c--------------------------------------- Line 805  c---------------------------------------
805           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
806           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
807    
808           xPAM_A = 0.           xPAM_A = 0.D0
809           yPAM_A = 0.           yPAM_A = 0.D0
810           zPAM_A = 0.           zPAM_A = 0.D0
811    
812           xPAM_B = 0.           xPAM_B = 0.D0
813           yPAM_B = 0.           yPAM_B = 0.D0
814           zPAM_B = 0.           zPAM_B = 0.D0
815    
816        elseif(        elseif(
817       $        (icx.ne.0.and.icy.eq.0).or.       $        (icx.ne.0.and.icy.eq.0).or.
# Line 1088  C======================================= Line 831  C=======================================
831              nldx = nldy              nldx = nldy
832              viewx = viewy + 1              viewx = viewy + 1
833    
834              yi   = acoordsi(stripy,viewy)              xi = dcoordsi(0.5*(nstrips+1),viewx) !sensor center
835                yi = dcoordsi(stripy,viewy)
836                zi = 0.D0
837    
838              xi_A = edgeY_d - SiDimX/2              xi_A = edgeY_d - SiDimX/2
839              yi_A = yi              yi_A = yi
# Line 1098  C======================================= Line 843  C=======================================
843              yi_B = yi              yi_B = yi
844              zi_B = 0.              zi_B = 0.
845    
 c            print*,'Y-cl ',icy,stripy,' --> ',yi  
 c            print*,xi_A,' <--> ',xi_B  
846                            
847           elseif(icx.ne.0)then           elseif(icx.ne.0)then
848  c===========================================================  c===========================================================
# Line 1110  C======================================= Line 853  C=======================================
853              nldy = nldx              nldy = nldx
854              viewy = viewx - 1              viewy = viewx - 1
855    
 c            print*,'X-singlet ',icx,nplx,nldx,viewx,stripx  
 c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  
856              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
857       $           .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...
858                 if(DEBUG.EQ.1) then                 if(DEBUG.EQ.1) then
# Line 1119  c            if((stripx.le.3).or.(stripx Line 860  c            if((stripx.le.3).or.(stripx
860       $                 ' WARNING: false X strip: strip ',stripx       $                 ' WARNING: false X strip: strip ',stripx
861                 endif                 endif
862              endif              endif
863              xi   = acoordsi(stripx,viewx)  
864                xi = dcoordsi(stripx,viewx)
865                yi = dcoordsi(0.5*(nstrips+1),viewy) !sensor center
866                zi = 0.D0
867    
868              xi_A = xi              xi_A = xi
869              yi_A = edgeX_d - SiDimY/2              yi_A = edgeX_d - SiDimY/2
# Line 1135  c            if((stripx.le.3).or.(stripx Line 879  c            if((stripx.le.3).or.(stripx
879                 yi_B = yi                 yi_B = yi
880              endif              endif
881    
 c            print*,'X-cl ',icx,stripx,' --> ',xi  
 c            print*,yi_A,' <--> ',yi_B  
882    
883           else           else
884              if(DEBUG.EQ.1) then              if(DEBUG.EQ.1) then
# Line 1182  c     N.B. I convert angles from microra Line 924  c     N.B. I convert angles from microra
924       $        + zi_B       $        + zi_B
925       $        + dz(nplx,nldx,sensor)       $        + dz(nplx,nldx,sensor)
926    
927    
928    
929             xrt = xi
930         $        - omega(nplx,nldx,sensor)*yi
931         $        + gamma(nplx,nldx,sensor)*zi
932         $        + dx(nplx,nldx,sensor)
933            
934             yrt = omega(nplx,nldx,sensor)*xi
935         $        + yi
936         $        - beta(nplx,nldx,sensor)*zi
937         $        + dy(nplx,nldx,sensor)
938            
939             zrt = -gamma(nplx,nldx,sensor)*xi
940         $        + beta(nplx,nldx,sensor)*yi
941         $        + zi
942         $        + dz(nplx,nldx,sensor)
943    
944    
945                    
946  c      xrt = xi  c      xrt = xi
947  c      yrt = yi  c      yrt = yi
# Line 1192  c     (xPAM,yPAM,zPAM) = measured coordi Line 952  c     (xPAM,yPAM,zPAM) = measured coordi
952  c                        in PAMELA reference system  c                        in PAMELA reference system
953  c------------------------------------------------------------------------  c------------------------------------------------------------------------
954    
955           xPAM = 0.           xPAM = dcoord(xrt,viewx,nldx,sensor) / 1.d4
956           yPAM = 0.           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
957           zPAM = 0.           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
958    c$$$         xPAM = 0.D0
959    c$$$         yPAM = 0.D0
960    c$$$         zPAM = 0.D0
961    
962           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4
963           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4
# Line 1205  c--------------------------------------- Line 968  c---------------------------------------
968           zPAM_B = ( zrt_B + z_mech_sensor(nplx,nldx,sensor)*1000.)/ 1.d4           zPAM_B = ( zrt_B + z_mech_sensor(nplx,nldx,sensor)*1000.)/ 1.d4
969                    
970    
 c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'  
971    
972        else        else
973           if(DEBUG.EQ.1) then           if(DEBUG.EQ.1) then
# Line 1216  c         print*,'A-(',xPAM_A,yPAM_A,') Line 978  c         print*,'A-(',xPAM_A,yPAM_A,')
978        endif        endif
979                    
980    
 c      print*,'## xPAM,yPAM,zPAM       ',xPAM,yPAM,zPAM  
 c      print*,'## xPAM_A,yPAM_A,zPAM_A ',xPAM_A,yPAM_A,zPAM_A  
 c      print*,'## xPAM_B,yPAM_B,zPAM_B ',xPAM_B,yPAM_B,zPAM_B  
981    
982   100  continue   100  continue
983        end        end
# Line 1256  c$$$      PFAy = 'COG4'!PFA Line 1015  c$$$      PFAy = 'COG4'!PFA
1015    
1016        if(icx.gt.nclstr1.or.icy.gt.nclstr1)then        if(icx.gt.nclstr1.or.icy.gt.nclstr1)then
1017              print*,'xyzpam: ***WARNING*** clusters ',icx,icy              print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1018       $           ,' does not exists (nclstr1=',nclstr1,')'       $           ,' do not exists (n.clusters=',nclstr1,')'
1019              icx = -1*icx              icx = -1*icx
1020              icy = -1*icy              icy = -1*icy
1021              return              return
# Line 1266  c$$$      PFAy = 'COG4'!PFA Line 1025  c$$$      PFAy = 'COG4'!PFA
1025        call idtoc(pfaid,PFAx)        call idtoc(pfaid,PFAx)
1026        call idtoc(pfaid,PFAy)        call idtoc(pfaid,PFAy)
1027    
 cc      print*,PFAx,PFAy  
   
 c$$$      call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)  
   
 c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy  
1028                
1029        if(icx.ne.0.and.icy.ne.0)then        if(icx.ne.0.and.icy.ne.0)then
1030    
1031           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
1032           ipy=npl(VIEW(icy))           ipy=npl(VIEW(icy))
 c$$$         if( (nplanes-ipx+1).ne.ip.or.(nplanes-ipy+1).ne.ip )  
 c$$$     $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy  
 c$$$     $        ,' does not belong to the correct plane: ',ip,ipx,ipy  
1033                    
1034           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1035              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster ',icx
# Line 1303  c$$$     $        ,' does not belong to Line 1054  c$$$     $        ,' does not belong to
1054           xm(ip) = xPAM           xm(ip) = xPAM
1055           ym(ip) = yPAM           ym(ip) = yPAM
1056           zm(ip) = zPAM           zm(ip) = zPAM
1057           xm_A(ip) = 0.           xm_A(ip) = 0.D0
1058           ym_A(ip) = 0.           ym_A(ip) = 0.D0
1059           xm_B(ip) = 0.           xm_B(ip) = 0.D0
1060           ym_B(ip) = 0.           ym_B(ip) = 0.D0
1061    
1062  c         zv(ip) = zPAM  c         zv(ip) = zPAM
1063    
1064        elseif(icx.eq.0.and.icy.ne.0)then        elseif(icx.eq.0.and.icy.ne.0)then
1065    
1066           ipy=npl(VIEW(icy))           ipy=npl(VIEW(icy))
 c$$$         if((nplanes-ipy+1).ne.ip)  
 c$$$     $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy  
 c$$$     $        ,' does not belong to the correct plane: ',ip,ipx,ipy  
1067           if( (nplanes-ipy+1).ne.ip )then           if( (nplanes-ipy+1).ne.ip )then
1068              print*,'xyzpam: ***WARNING*** cluster ',icy              print*,'xyzpam: ***WARNING*** cluster ',icy
1069       $           ,' does not belong to plane: ',ip       $           ,' does not belong to plane: ',ip
# Line 1330  c$$$     $        ,' does not belong to Line 1078  c$$$     $        ,' does not belong to
1078           resx(ip)  = 1000.           resx(ip)  = 1000.
1079           resy(ip)  = resyPAM           resy(ip)  = resyPAM
1080    
1081           xm(ip) = -100.  c$$$         xm(ip) = -100.
1082           ym(ip) = -100.  c$$$         ym(ip) = -100.
1083           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1084             xm(ip) = xPAM
1085             ym(ip) = yPAM
1086             zm(ip) = zPAM
1087           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1088           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1089           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1343  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1094  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1094        elseif(icx.ne.0.and.icy.eq.0)then        elseif(icx.ne.0.and.icy.eq.0)then
1095    
1096           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
 c$$$         if((nplanes-ipx+1).ne.ip)  
 c$$$     $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy  
 c$$$     $        ,' does not belong to the correct plane: ',ip,ipx,ipy  
1097    
1098           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1099              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster ',icx
# Line 1361  c$$$     $        ,' does not belong to Line 1109  c$$$     $        ,' does not belong to
1109           resx(ip)  = resxPAM           resx(ip)  = resxPAM
1110           resy(ip)  = 1000.           resy(ip)  = 1000.
1111    
1112           xm(ip) = -100.  c$$$         xm(ip) = -100.
1113           ym(ip) = -100.  c$$$         ym(ip) = -100.
1114           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1115             xm(ip) = xPAM
1116             ym(ip) = yPAM
1117             zm(ip) = zPAM
1118           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1119           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1120           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1377  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1128  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1128           if(lad.ne.0)il=lad           if(lad.ne.0)il=lad
1129           is = 1           is = 1
1130           if(sensor.ne.0)is=sensor           if(sensor.ne.0)is=sensor
 c         print*,nplanes-ip+1,il,is  
1131    
1132           xgood(ip) = 0.           xgood(ip) = 0.
1133           ygood(ip) = 0.           ygood(ip) = 0.
# Line 1397  c         zv(ip) = z_mech_sensor(nplanes Line 1147  c         zv(ip) = z_mech_sensor(nplanes
1147        endif        endif
1148    
1149        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
 c         print*,'----------------------------- track coord'  
1150  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1151           write(*,22222)ip,zm(ip),xm(ip),ym(ip)           write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1152       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1153       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)
 c$$$         print*,'-----------------------------'  
1154        endif        endif
1155        end        end
1156    
# Line 1426  c$$$         print*,'------------------- Line 1174  c$$$         print*,'-------------------
1174  *      *    
1175  ********************************************************************************  ********************************************************************************
1176    
1177        real function distance_to(XPP,YPP)        real function distance_to(rXPP,rYPP)
1178    
1179        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
1180    
# Line 1435  c$$$         print*,'------------------- Line 1183  c$$$         print*,'-------------------
1183  *     ( i.e. distance/resolution )  *     ( i.e. distance/resolution )
1184  *     -----------------------------------  *     -----------------------------------
1185    
1186          real rXPP,rYPP
1187          double precision XPP,YPP
1188        double precision distance,RE        double precision distance,RE
1189        double precision BETA,ALFA,xmi,ymi        double precision BETA,ALFA,xmi,ymi
1190    
1191          XPP=DBLE(rXPP)
1192          YPP=DBLE(rYPP)
1193    
1194  *     ----------------------  *     ----------------------
1195        if (        if (
1196       +     xPAM.eq.0.and.  c$$$     +     xPAM.eq.0.and.
1197       +     yPAM.eq.0.and.  c$$$     +     yPAM.eq.0.and.
1198       +     zPAM.eq.0.and.  c$$$     +     zPAM.eq.0.and.
1199       +     xPAM_A.ne.0.and.       +     xPAM_A.ne.0.and.
1200       +     yPAM_A.ne.0.and.       +     yPAM_A.ne.0.and.
1201       +     zPAM_A.ne.0.and.       +     zPAM_A.ne.0.and.
# Line 1484  c$$$         print*,'------------------- Line 1237  c$$$         print*,'-------------------
1237  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1238           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1239    
 c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',re  
1240    
1241                    
1242  *     ----------------------  *     ----------------------
1243        elseif(        elseif(
1244       +     xPAM.ne.0.and.  c$$$     +     xPAM.ne.0.and.
1245       +     yPAM.ne.0.and.  c$$$     +     yPAM.ne.0.and.
1246       +     zPAM.ne.0.and.  c$$$     +     zPAM.ne.0.and.
1247       +     xPAM_A.eq.0.and.       +     xPAM_A.eq.0.and.
1248       +     yPAM_A.eq.0.and.       +     yPAM_A.eq.0.and.
1249       +     zPAM_A.eq.0.and.       +     zPAM_A.eq.0.and.
# Line 1514  c$$$     $        + Line 1264  c$$$     $        +
1264  c$$$     $        ((yPAM-YPP)/resyPAM)**2  c$$$     $        ((yPAM-YPP)/resyPAM)**2
1265           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1266    
 c$$$         print*,xPAM,yPAM,zPAM  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',resxPAM,resyPAM  
1267                    
1268        else        else
1269                    
 c         print*  
 c     $        ,' function distance_to ---> wrong usage!!!'  
 c         print*,' xPAM,yPAM,zPAM ',xPAM,yPAM,zPAM  
 c         print*,' 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  
1270        endif          endif  
1271    
1272        distance_to = sngl(distance)        distance_to = sngl(distance)
# Line 1564  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1306  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1306        data c1/1.,0.,0.,1./        data c1/1.,0.,0.,1./
1307        data c2/1.,-1.,-1.,1./        data c2/1.,-1.,-1.,1./
1308        data c3/1.,1.,0.,0./        data c3/1.,1.,0.,0./
1309        real*8 yvvv,xvvv        double precision yvvv,xvvv
1310        double precision xi,yi,zi        double precision xi,yi,zi
1311        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
1312        real AA,BB        real AA,BB
1313        real yvv(4),xvv(4)        double precision yvv(4),xvv(4)
1314    
1315  *     tollerance to consider the track inside the sensitive area  *     tollerance to consider the track inside the sensitive area
1316        real ptoll        real ptoll
1317        data ptoll/150./          !um        data ptoll/150./          !um
1318    
1319        external nviewx,nviewy,acoordsi,dcoord        external nviewx,nviewy,dcoordsi,dcoord
1320    
1321        nplpt = nplPAM            !plane        nplpt = nplPAM            !plane
1322        viewx = nviewx(nplpt)        viewx = nviewx(nplpt)
# Line 1589  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1331  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1331  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1332  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1333  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1334                 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)                 xi = dcoordsi(stripx,viewx)
1335       $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...                 yi = dcoordsi(stripy,viewy)
1336  c     if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...                 zi = 0.D0
 c                  print*,'whichsensor: ',  
 c     $                ' WARNING: false X strip: strip ',stripx  
                endif  
                xi = acoordsi(stripx,viewx)  
                yi = acoordsi(stripy,viewy)  
                zi = 0.  
1337  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1338  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
1339  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 1622  c--------------------------------------- Line 1358  c---------------------------------------
1358    
1359                 yvv(iv)=sngl(yvvv)                 yvv(iv)=sngl(yvvv)
1360                 xvv(iv)=sngl(xvvv)                 xvv(iv)=sngl(xvvv)
 c               print*,'LADDER ',il,' SENSOR ',is,' vertexes >> '  
 c     $              ,iv,xvv(iv),yvv(iv)  
1361              enddo               !end loop on sensor vertexes              enddo               !end loop on sensor vertexes
1362    
1363              dtot=0.              dtot=0.
# Line 1748  c      include 'common_analysis.f' Line 1482  c      include 'common_analysis.f'
1482        is_cp=0        is_cp=0
1483        if(id.lt.0)is_cp=1        if(id.lt.0)is_cp=1
1484        if(id.gt.0)is_cp=2        if(id.gt.0)is_cp=2
 c      if(id.eq.0)print*,'IS_CP ===> wrong couple id !!!'  
1485    
1486        return        return
1487        end        end
# Line 1850  c      include 'level1.f' Line 1583  c      include 'level1.f'
1583            
1584        if(DEBUG.EQ.1)print*,'cl_to_couples:'        if(DEBUG.EQ.1)print*,'cl_to_couples:'
1585    
1586    cc      if(RECOVER_SINGLETS.and..not.SECOND_SEARCH)goto 80
1587    
1588  *     init variables  *     init variables
       ncp_tot=0  
1589        do ip=1,nplanes        do ip=1,nplanes
1590           do ico=1,ncouplemax           do ico=1,ncouplemax
1591              clx(ip,ico)=0              clx(ip,ico)=0
# Line 1864  c      include 'level1.f' Line 1598  c      include 'level1.f'
1598           ncls(ip)=0           ncls(ip)=0
1599        enddo        enddo
1600        do icl=1,nclstrmax_level2        do icl=1,nclstrmax_level2
1601           cl_single(icl) = 1           cl_single(icl) = 1     !all are single
1602           cl_good(icl)   = 0           cl_good(icl)   = 0     !all are bad
1603        enddo        enddo
1604        do iv=1,nviews        do iv=1,nviews
1605           ncl_view(iv)  = 0           ncl_view(iv)  = 0
# Line 1893  c            mask_view(iv) = 1 Line 1627  c            mask_view(iv) = 1
1627        do icx=1,nclstr1          !loop on cluster (X)        do icx=1,nclstr1          !loop on cluster (X)
1628           if(mod(VIEW(icx),2).eq.1)goto 10           if(mod(VIEW(icx),2).eq.1)goto 10
1629                    
1630             if(cl_used(icx).ne.0)goto 10
1631    
1632  *     ----------------------------------------------------  *     ----------------------------------------------------
1633  *     jump masked views (X VIEW)  *     jump masked views (X VIEW)
1634  *     ----------------------------------------------------  *     ----------------------------------------------------
# Line 1900  c            mask_view(iv) = 1 Line 1636  c            mask_view(iv) = 1
1636  *     ----------------------------------------------------  *     ----------------------------------------------------
1637  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1638  *     ----------------------------------------------------  *     ----------------------------------------------------
1639           if(sgnl(icx).lt.dedx_x_min)then           if(sgnl(icx)/mip(VIEW(icx),LADDER(icx)).lt.dedx_x_min)then
1640              cl_single(icx)=0              cl_single(icx)=0
1641              goto 10              goto 10
1642           endif           endif
# Line 1941  c     endif Line 1677  c     endif
1677                    
1678           do icy=1,nclstr1       !loop on cluster (Y)           do icy=1,nclstr1       !loop on cluster (Y)
1679              if(mod(VIEW(icy),2).eq.0)goto 20              if(mod(VIEW(icy),2).eq.0)goto 20
1680    
1681                if(cl_used(icx).ne.0)goto 20
1682                            
1683  *     ----------------------------------------------------  *     ----------------------------------------------------
1684  *     jump masked views (Y VIEW)  *     jump masked views (Y VIEW)
# Line 1950  c     endif Line 1688  c     endif
1688  *     ----------------------------------------------------  *     ----------------------------------------------------
1689  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1690  *     ----------------------------------------------------  *     ----------------------------------------------------
1691              if(sgnl(icy).lt.dedx_y_min)then              if(sgnl(icy)/mip(VIEW(icy),LADDER(icy)) .lt.dedx_y_min)then
1692                 cl_single(icy)=0                 cl_single(icy)=0
1693                 goto 20                 goto 20
1694              endif              endif
# Line 2049  c                  mask_view(nviewy(nply Line 1787  c                  mask_view(nviewy(nply
1787   10      continue   10      continue
1788        enddo                     !end loop on clusters(X)        enddo                     !end loop on clusters(X)
1789                
         
1790        do icl=1,nclstr1        do icl=1,nclstr1
1791           if(cl_single(icl).eq.1)then           if(cl_single(icl).eq.1)then
1792              ip=npl(VIEW(icl))              ip=npl(VIEW(icl))
# Line 2057  c                  mask_view(nviewy(nply Line 1794  c                  mask_view(nviewy(nply
1794              cls(ip,ncls(ip))=icl              cls(ip,ncls(ip))=icl
1795           endif           endif
1796        enddo        enddo
1797    
1798     80   continue
1799                
1800                
1801        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
1802           print*,'clusters  ',nclstr1           print*,'clusters  ',nclstr1
1803           print*,'good    ',(cl_good(i),i=1,nclstr1)           print*,'good    ',(cl_good(i),i=1,nclstr1)
1804             print*,'used    ',(cl_used(i),i=1,nclstr1)
1805           print*,'singlets',(cl_single(i),i=1,nclstr1)           print*,'singlets',(cl_single(i),i=1,nclstr1)
1806           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1807        endif        endif
1808    
1809      
1810          if(.not.RECOVER_SINGLETS)goto 81
1811    
1812    *     ////////////////////////////////////////////////
1813    *     PATCH to recover events with less than 3 couples
1814    *     ////////////////////////////////////////////////    
1815    *     loop over singlet and create "fake" couples
1816    *     (with clx=0 or cly=0)
1817    *    
1818    
1819          if(DEBUG.EQ.1)
1820         $     print*,'>>> Recover singlets '
1821         $     ,'(creates fake couples) <<<'
1822          do icl=1,nclstr1
1823             if(
1824         $        cl_single(icl).eq.1.and.
1825         $        cl_used(icl).eq.0.and.
1826         $        .true.)then
1827    *     ----------------------------------------------------
1828    *     jump masked views
1829    *     ----------------------------------------------------
1830                if( mask_view(VIEW(icl)).ne.0 ) goto 21
1831                if(mod(VIEW(icl),2).eq.0)then !=== X views
1832    *     ----------------------------------------------------
1833    *     cut on charge (X VIEW)
1834    *     ----------------------------------------------------
1835                   if(sgnl(icl).lt.dedx_x_min) goto 21
1836                  
1837                   nplx=npl(VIEW(icl))
1838    *     ------------------> (FAKE) COUPLE <-----------------
1839                   ncp_plane(nplx) = ncp_plane(nplx) + 1
1840                   clx(nplx,ncp_plane(nplx))=icl
1841                   cly(nplx,ncp_plane(nplx))=0
1842    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1843    *     ----------------------------------------------------
1844                  
1845                else                !=== Y views
1846    *     ----------------------------------------------------
1847    *     cut on charge (Y VIEW)
1848    *     ----------------------------------------------------
1849                   if(sgnl(icl).lt.dedx_y_min) goto 21
1850                  
1851                   nply=npl(VIEW(icl))
1852    *     ------------------> (FAKE) COUPLE <-----------------
1853                   ncp_plane(nply) = ncp_plane(nply) + 1
1854                   clx(nply,ncp_plane(nply))=0
1855                   cly(nply,ncp_plane(nply))=icl
1856    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1857    *     ----------------------------------------------------
1858                  
1859                endif
1860             endif                  !end "single" condition
1861     21      continue
1862          enddo                     !end loop over clusters
1863    
1864          if(DEBUG.EQ.1)
1865         $     print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1866    
1867    
1868     81   continue
1869                
1870        do ip=1,6        ncp_tot=0
1871          do ip=1,NPLANES
1872           ncp_tot = ncp_tot + ncp_plane(ip)           ncp_tot = ncp_tot + ncp_plane(ip)
1873        enddo        enddo
1874          if(DEBUG.EQ.1)
1875         $     print*,'n.couple tot:      ',ncp_tot
1876                
1877        return        return
1878        end        end
# Line 2131  c      double precision xm3,ym3,zm3 Line 1935  c      double precision xm3,ym3,zm3
1935  *     --------------------------------------------  *     --------------------------------------------
1936        do ip=1,nplanes        do ip=1,nplanes
1937           if(ncp_plane(ip).gt.ncouplelimit)then           if(ncp_plane(ip).gt.ncouplelimit)then
 c            mask_view(nviewx(ip)) = 8  
 c            mask_view(nviewy(ip)) = 8  
1938              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7
1939              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7
1940           endif           endif
# Line 2143  c            mask_view(nviewy(ip)) = 8 Line 1945  c            mask_view(nviewy(ip)) = 8
1945        ntrpt=0                   !number of triplets        ntrpt=0                   !number of triplets
1946                
1947        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1
1948    c$$$         print*,'(1) ip ',ip1
1949    c$$$     $        ,mask_view(nviewx(ip1))
1950    c$$$     $        ,mask_view(nviewy(ip1))        
1951           if(  mask_view(nviewx(ip1)).ne.0 .or.           if(  mask_view(nviewx(ip1)).ne.0 .or.
1952       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
1953           do is1=1,2             !loop on sensors - COPPIA 1                       do is1=1,2             !loop on sensors - COPPIA 1            
1954              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
1955                 icx1=clx(ip1,icp1)                 icx1=clx(ip1,icp1)
1956                 icy1=cly(ip1,icp1)                 icy1=cly(ip1,icp1)
1957                  
1958    c$$$               print*,'(1) ip ',ip1,' icp ',icp1
1959    
1960  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
1961  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
1962                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
1963                 xm1=xPAM                 xm1=xPAM
1964                 ym1=yPAM                 ym1=yPAM
1965                 zm1=zPAM                                   zm1=zPAM                  
 c     print*,'***',is1,xm1,ym1,zm1  
1966    
1967                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
1968    c$$$                  print*,'(2) ip ',ip2
1969    c$$$     $                 ,mask_view(nviewx(ip2))
1970    c$$$     $                 ,mask_view(nviewy(ip2))
1971                    if(  mask_view(nviewx(ip2)).ne.0 .or.                    if(  mask_view(nviewx(ip2)).ne.0 .or.
1972       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
1973                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                                        do is2=1,2    !loop on sensors -ndblt COPPIA 2                    
1974                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
1975                          icx2=clx(ip2,icp2)                          icx2=clx(ip2,icp2)
1976                          icy2=cly(ip2,icp2)                          icy2=cly(ip2,icp2)
1977    
1978    c$$$                        print*,'(2) ip ',ip2,' icp ',icp2
1979    
1980  c                        call xyz_PAM  c                        call xyz_PAM
1981  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
1982  c                        call xyz_PAM  c                        call xyz_PAM
# Line 2173  c     $                       (icx2,icy2 Line 1986  c     $                       (icx2,icy2
1986                          xm2=xPAM                          xm2=xPAM
1987                          ym2=yPAM                          ym2=yPAM
1988                          zm2=zPAM                          zm2=zPAM
1989                                                    
1990    *                       ---------------------------------------------------
1991    *                       both couples must have a y-cluster
1992    *                       (condition necessary when in RECOVER_SINGLETS mode)
1993    *                       ---------------------------------------------------
1994                            if(icy1.eq.0.or.icy2.eq.0)goto 111
1995    
1996                            if(cl_used(icy1).ne.0)goto 111
1997                            if(cl_used(icy2).ne.0)goto 111
1998    
1999                            
2000  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2001  *     track parameters on Y VIEW  *     track parameters on Y VIEW
2002  *     (2 couples needed)  *     (2 couples needed)
# Line 2183  c     $                       (icx2,icy2 Line 2006  c     $                       (icx2,icy2
2006       $                          '** warning ** number of identified '//       $                          '** warning ** number of identified '//
2007       $                          'doublets exceeds vector dimention '       $                          'doublets exceeds vector dimention '
2008       $                          ,'( ',ndblt_max,' )'       $                          ,'( ',ndblt_max,' )'
2009  c                           good2=.false.  c     good2=.false.
2010  c                           goto 880 !fill ntp and go to next event  c     goto 880 !fill ntp and go to next event
2011                             do iv=1,12                             do iv=1,12
2012  c                              mask_view(iv) = 3  c     mask_view(iv) = 3
2013                                mask_view(iv) = mask_view(iv)+ 2**2                                mask_view(iv) = mask_view(iv)+ 2**2
2014                             enddo                             enddo
2015                             iflag=1                             iflag=1
2016                             return                             return
2017                          endif                          endif
2018                            
2019                            
2020    ccc                        print*,'<doublet> ',icp1,icp2
2021    
2022                          ndblt = ndblt + 1                          ndblt = ndblt + 1
2023  *     store doublet info  *     store doublet info
2024                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)
# Line 2200  c                              mask_view Line 2027  c                              mask_view
2027                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)
2028  *     y0 (cm)  *     y0 (cm)
2029                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1
2030                                                      
2031  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2032  ****  reject non phisical couples                    ****  ****  reject non phisical couples                    ****
2033  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2034                            if(SECOND_SEARCH)goto 111
2035                          if(                          if(
2036       $                       abs(alfayz2(ndblt)).gt.alfyz2_max       $                       abs(alfayz2(ndblt)).gt.alfyz2_max
2037       $                       .or.       $                       .or.
2038       $                       abs(alfayz1(ndblt)).gt.alfyz1_max       $                       abs(alfayz1(ndblt)).gt.alfyz1_max
2039       $                       )ndblt = ndblt-1       $                       )ndblt = ndblt-1
2040                                                    
2041  c$$$      if(iev.eq.33)then                          
2042  c$$$      print*,'********* ',ndblt,' -- ',icp1,icp2,is1,is2   111                    continue
 c$$$     $        ,' || ',icx1,icy1,icx2,icy2  
 c$$$     $        ,' || ',xm1,ym1,xm2,ym2  
 c$$$     $        ,' || ',alfayz2(ndblt),alfayz1(ndblt)  
 c$$$      endif  
 c$$$  
2043  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2044  *     track parameters on Y VIEW - end  *     track parameters on Y VIEW - end
2045  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2046    
2047    
2048                            if(icx1.ne.0)then
2049                               if(cl_used(icx1).ne.0)goto 31
2050                            endif
2051                            if(icx2.ne.0)then
2052                               if(cl_used(icx2).ne.0)goto 31
2053                            endif
2054    
2055                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2056    
2057                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2058    c$$$                           print*,'(3) ip ',ip3
2059    c$$$     $                          ,mask_view(nviewx(ip3))
2060    c$$$     $                          ,mask_view(nviewy(ip3))                          
2061                             if(  mask_view(nviewx(ip3)).ne.0 .or.                             if(  mask_view(nviewx(ip3)).ne.0 .or.
2062       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2063                             do is3=1,2 !loop on sensors - COPPIA 3                             do is3=1,2 !loop on sensors - COPPIA 3
# Line 2232  c$$$ Line 2065  c$$$
2065                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
2066                                   icx3=clx(ip3,icp3)                                   icx3=clx(ip3,icp3)
2067                                   icy3=cly(ip3,icp3)                                   icy3=cly(ip3,icp3)
2068    
2069    c$$$                                 print*,'(3) ip ',ip3,' icp ',icp3
2070    
2071    *     ---------------------------------------------------
2072    *     all three couples must have a x-cluster
2073    *     (condition necessary when in RECOVER_SINGLETS mode)
2074    *     ---------------------------------------------------
2075                                     if(
2076         $                                icx1.eq.0.or.
2077         $                                icx2.eq.0.or.
2078         $                                icx3.eq.0.or.
2079         $                                .false.)goto 29
2080                                    
2081                                     if(cl_used(icx1).ne.0)goto 29
2082                                     if(cl_used(icx2).ne.0)goto 29
2083                                     if(cl_used(icx3).ne.0)goto 29
2084    
2085  c                                 call xyz_PAM  c                                 call xyz_PAM
2086  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2087  c                                 call xyz_PAM  c                                 call xyz_PAM
# Line 2242  c     $                               (i Line 2092  c     $                               (i
2092                                   xm3=xPAM                                   xm3=xPAM
2093                                   ym3=yPAM                                   ym3=yPAM
2094                                   zm3=zPAM                                   zm3=zPAM
2095    
2096    
2097  *     find the circle passing through the three points  *     find the circle passing through the three points
2098  c$$$                                 call tricircle(3,xp,zp,angp,resp,chi                                   iflag_t = DEBUG
 c$$$     $                                ,xc,zc,radius,iflag)  
                                  iflag = DEBUG  
2099                                   call tricircle(3,xp,zp,angp,resp,chi                                   call tricircle(3,xp,zp,angp,resp,chi
2100       $                                ,xc,zc,radius,iflag)       $                                ,xc,zc,radius,iflag_t)
 c     print*,xc,zc,radius  
2101  *     the circle must intersect the reference plane  *     the circle must intersect the reference plane
2102                                   if(  cc                                 if(iflag.ne.0)goto 29
2103  c     $                                 (xc.le.-1.*xclimit.or.                                   if(iflag_t.ne.0)then
2104  c     $                                 xc.ge.xclimit).and.  *     if tricircle fails, evaluate a straight line
2105       $                                radius**2.ge.(ZINI-zc)**2.and.                                      if(DEBUG.eq.1)
2106       $                                iflag.eq.0.and.       $                                   print*,'TRICIRCLE failure'
2107       $                                .true.)then       $                                   ,' >>> straight line'
2108                                                                        radius=0.
2109                                        xc=0.
2110                                        yc=0.
2111                                        
2112                                        SZZ=0.                  
2113                                        SZX=0.
2114                                        SSX=0.
2115                                        SZ=0.
2116                                        S1=0.
2117                                        X0=0.
2118                                        Ax=0.
2119                                        BX=0.
2120                                        DO I=1,3
2121                                           XX = XP(I)
2122                                           SZZ=SZZ+ZP(I)*ZP(I)
2123                                           SZX=SZX+ZP(I)*XX
2124                                           SSX=SSX+XX
2125                                           SZ=SZ+ZP(I)
2126                                           S1=S1+1.                                    
2127                                        ENDDO
2128                                        DET=SZZ*S1-SZ*SZ
2129                                        AX=(SZX*S1-SZ*SSX)/DET
2130                                        BX=(SZZ*SSX-SZX*SZ)/DET
2131                                        X0  = AX*ZINI+BX
2132                                        
2133                                     endif
2134    
2135                                     if(  .not.SECOND_SEARCH.and.
2136         $                                radius**2.lt.(ZINI-zc)**2)goto 29
2137                                                                      
2138  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2139  *     track parameters on X VIEW  *     track parameters on X VIEW
2140  *     (3 couples needed)  *     (3 couples needed)
2141  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2142                                   if(ntrpt.eq.ntrpt_max)then                                   if(ntrpt.eq.ntrpt_max)then
2143                                      if(verbose.eq.1)print*,                                      if(verbose.eq.1)print*,
2144       $                     '** warning ** number of identified '//       $                                   '** warning **'//
2145       $                     'triplets exceeds vector dimention '       $                                   ' number of identified '//
2146       $                    ,'( ',ntrpt_max,' )'       $                                   'triplets exceeds'//
2147  c                                    good2=.false.       $                                   ' vector dimention '
2148  c                                    goto 880 !fill ntp and go to next event       $                                   ,'( ',ntrpt_max,' )'
2149    c     good2=.false.
2150    c     goto 880 !fill ntp and go to next event
2151                                      do iv=1,nviews                                      do iv=1,nviews
2152  c                                       mask_view(iv) = 4  c     mask_view(iv) = 4
2153                                         mask_view(iv)=mask_view(iv)+ 2**3                                         mask_view(iv) =
2154         $                                      mask_view(iv)+ 2**3
2155                                      enddo                                      enddo
2156                                      iflag=1                                      iflag=1
2157                                      return                                      return
2158                                   endif                                   endif
2159    
2160    ccc                                 print*,'<triplet> ',icp1,icp2,icp3
2161                                    
2162                                   ntrpt = ntrpt +1                                   ntrpt = ntrpt +1
2163  *     store triplet info  *     store triplet info
2164                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)
2165                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)
2166                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)
2167                                                                    
2168                                   if(xc.lt.0)then                                   if(radius.ne.0.and.xc.lt.0)then
2169  *************POSITIVE DEFLECTION  *************POSITIVE DEFLECTION
2170                alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)
2171                alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2172                alfaxz3(ntrpt) = 1/radius               alfaxz3(ntrpt) = 1/radius
2173                                   else                                  else if(radius.ne.0.and.xc.ge.0)then
2174  *************NEGATIVE DEFLECTION  *************NEGATIVE DEFLECTION
2175                alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)
2176                alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2177                alfaxz3(ntrpt) = -1/radius               alfaxz3(ntrpt) = -1/radius
2178                                   endif                                  else if(radius.eq.0)then
2179                                    *************straight fit
2180                 alfaxz1(ntrpt) = X0
2181                 alfaxz2(ntrpt) = AX
2182                 alfaxz3(ntrpt) = 0.
2183                                    endif
2184    
2185    c$$$                                print*,'alfaxz1 ', alfaxz1(ntrpt)
2186    c$$$                                print*,'alfaxz2 ', alfaxz2(ntrpt)
2187    c$$$                                print*,'alfaxz3 ', alfaxz3(ntrpt)
2188                                        
2189  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2190  ****  reject non phisical triplets                   ****  ****  reject non phisical triplets                   ****
2191  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2192                                   if(                                  if(SECOND_SEARCH)goto 29
2193       $                                abs(alfaxz2(ntrpt)).gt.alfxz2_max                                  if(
2194       $                                .or.       $                               abs(alfaxz2(ntrpt)).gt.
2195       $                                abs(alfaxz1(ntrpt)).gt.alfxz1_max       $                               alfxz2_max
2196       $                                )ntrpt = ntrpt-1       $                               .or.
2197                                         $                               abs(alfaxz1(ntrpt)).gt.
2198                                         $                               alfxz1_max
2199  c     print*,alfaxz1(ntrpt),alfaxz2(ntrpt),alfaxz3(ntrpt)       $                               )ntrpt = ntrpt-1
2200                                                                    
2201  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2202  *     track parameters on X VIEW - end  *     track parameters on X VIEW - end
2203  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2204                                endif                                
2205     29                           continue
2206                             enddo !end loop on COPPIA 3                             enddo !end loop on COPPIA 3
2207                          enddo   !end loop on sensors - COPPIA 3                          enddo   !end loop on sensors - COPPIA 3
2208   30                     continue   30                     continue
2209                       enddo      !end loop on planes  - COPPIA 3                       enddo      !end loop on planes  - COPPIA 3
2210   31                  continue  
2211                         31                  continue                    
2212   1                enddo         !end loop on COPPIA 2   1                enddo         !end loop on COPPIA 2
2213                 enddo            !end loop on sensors - COPPIA 2                 enddo            !end loop on sensors - COPPIA 2
2214   20            continue   20            continue
2215              enddo               !end loop on planes  - COPPIA 2              enddo               !end loop on planes  - COPPIA 2
2216                
2217     11         continue
2218           enddo                  !end loop on COPPIA1           enddo                  !end loop on COPPIA1
2219        enddo                     !end loop on sensors - COPPIA 1        enddo                     !end loop on sensors - COPPIA 1
2220   10   continue   10   continue
# Line 2390  c      include 'momanhough_init.f' Line 2286  c      include 'momanhough_init.f'
2286        do idb1=1,ndblt           !loop (1) on DOUBLETS        do idb1=1,ndblt           !loop (1) on DOUBLETS
2287           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
2288                            
 c     print*,'--------------'  
 c     print*,'** ',idb1,' **'  
               
2289           do icp=1,ncp_tot           do icp=1,ncp_tot
2290              cp_useds1(icp)=0    !init              cp_useds1(icp)=0    !init
2291              cp_useds2(icp)=0    !init              cp_useds2(icp)=0    !init
# Line 2431  ccccc if(db_used(idbref).eq.1)goto 1188 Line 2324  ccccc if(db_used(idbref).eq.1)goto 1188
2324       $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2                     $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2              
2325                 distance = sqrt(distance)                 distance = sqrt(distance)
2326                                
 c$$$      if(iev.eq.33)then  
 c$$$      if(distance.lt.100)  
 c$$$     $ print*,'********* ',idb1,idbref,idb2,distance  
 c$$$      if(distance.lt.100)  
 c$$$     $ print*,'********* ',alfayz1(idbref),alfayz1(idb2)  
 c$$$     $                    ,alfayz2(idbref),alfayz2(idb2)  
 c$$$      endif  
2327                 if(distance.lt.cutdistyz)then                 if(distance.lt.cutdistyz)then
2328    
 c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  
2329                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1
2330                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1
2331                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1
# Line 2456  c     print*,idb1,idb2,distance,' cloud Line 2341  c     print*,idb1,idb2,distance,' cloud
2341    
2342                    temp1 = temp1 + alfayz1(idb2)                    temp1 = temp1 + alfayz1(idb2)
2343                    temp2 = temp2 + alfayz2(idb2)                    temp2 = temp2 + alfayz2(idb2)
 c     print*,'*   idbref,idb2 ',idbref,idb2  
2344                 endif                               endif              
2345                                
2346   1118          continue   1118          continue
# Line 2479  c     print*,'*   idbref,idb2 ',idbref,i Line 2363  c     print*,'*   idbref,idb2 ',idbref,i
2363           enddo           enddo
2364           ncpused=0           ncpused=0
2365           do icp=1,ncp_tot           do icp=1,ncp_tot
2366              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2367         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2368         $           .true.)then
2369                 ncpused=ncpused+1                 ncpused=ncpused+1
2370                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2371                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2489  c     print*,'*   idbref,idb2 ',idbref,i Line 2375  c     print*,'*   idbref,idb2 ',idbref,i
2375           do ip=1,nplanes           do ip=1,nplanes
2376              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2377           enddo           enddo
2378  c     print*,'>>>> ',ncpused,npt,nplused          
 c         if(ncpused.lt.ncpyz_min)goto 2228 !next doublet  
          if(npt.lt.nptyz_min)goto 2228 !next doublet  
2379           if(nplused.lt.nplyz_min)goto 2228 !next doublet           if(nplused.lt.nplyz_min)goto 2228 !next doublet
2380                    
2381  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2523  c               mask_view(iv) = 5 Line 2407  c               mask_view(iv) = 5
2407  c     ptcloud_yz_nt(nclouds_yz)=npt  c     ptcloud_yz_nt(nclouds_yz)=npt
2408           do ipt=1,npt           do ipt=1,npt
2409              db_cloud(npt_tot+ipt) = db_all(ipt)              db_cloud(npt_tot+ipt) = db_all(ipt)
 c     print*,'>> ',ipt,db_all(ipt)  
2410           enddo             enddo  
2411           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2412           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2413              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2414              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)
2415              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)
# Line 2536  c     print*,'>> ',ipt,db_all(ipt) Line 2418  c     print*,'>> ',ipt,db_all(ipt)
2418              print*,'cpcloud_yz '              print*,'cpcloud_yz '
2419       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)
2420              print*,'hit_plane  ',(hit_plane(ip),ip=1,nplanes)              print*,'hit_plane  ',(hit_plane(ip),ip=1,nplanes)
 c$$$            print*,'nt-uple: ptcloud_yz(',nclouds_yz,') = '  
 c$$$     $           ,ptcloud_yz(nclouds_yz)  
 c$$$            print*,'nt-uple: db_cloud(...) = '  
 c$$$     $           ,(db_cloud(iii),iii=npt_tot-npt+1,npt_tot)  
2421           endif           endif
2422  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2423  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2554  c$$$     $           ,(db_cloud(iii),iii Line 2432  c$$$     $           ,(db_cloud(iii),iii
2432        endif                            endif                    
2433                
2434        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2435           print*,'Y-Z total clouds ',nclouds_yz           print*,'Y-Z total clouds ',nclouds_yz
          print*,' '  
2436        endif        endif
2437                
2438                
# Line 2619  c      include 'momanhough_init.f' Line 2495  c      include 'momanhough_init.f'
2495   91   continue                     91   continue                  
2496        do itr1=1,ntrpt           !loop (1) on TRIPLETS        do itr1=1,ntrpt           !loop (1) on TRIPLETS
2497           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
 c     print*,'--------------'  
 c     print*,'** ',itr1,' **'  
2498                    
2499           do icp=1,ncp_tot           do icp=1,ncp_tot
2500              cp_useds1(icp)=0              cp_useds1(icp)=0
# Line 2654  c         tr_temp(1)=itr1 Line 2528  c         tr_temp(1)=itr1
2528              do itr2=1,ntrpt     !loop (2) on TRIPLETS              do itr2=1,ntrpt     !loop (2) on TRIPLETS
2529                 if(itr2.eq.itr1)goto 11188       !next triplet                 if(itr2.eq.itr1)goto 11188       !next triplet
2530                 if(tr_used(itr2).eq.1)goto 11188 !next triplet                               if(tr_used(itr2).eq.1)goto 11188 !next triplet              
2531    
2532    
2533  *     triplet distance in parameter space  *     triplet distance in parameter space
2534  *     solo i due parametri spaziali per il momemnto  *     solo i due parametri spaziali per il momemnto
2535                 distance=                 distance=
2536       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2
2537       $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2                     $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2              
2538                 distance = sqrt(distance)                 distance = sqrt(distance)
2539                  
2540    
2541  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
2542  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE
2543  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
# Line 2673  c         tr_temp(1)=itr1 Line 2550  c         tr_temp(1)=itr1
2550       $              .true.)istrimage=1       $              .true.)istrimage=1
2551    
2552                 if(distance.lt.cutdistxz.or.istrimage.eq.1)then                 if(distance.lt.cutdistxz.or.istrimage.eq.1)then
 c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  
2553                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2554                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
2555                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1
# Line 2692  c     print*,idb1,idb2,distance,' cloud Line 2568  c     print*,idb1,idb2,distance,' cloud
2568                    temp1 = temp1 + alfaxz1(itr2)                    temp1 = temp1 + alfaxz1(itr2)
2569                    temp2 = temp2 + alfaxz2(itr2)                    temp2 = temp2 + alfaxz2(itr2)
2570                    temp3 = temp3 + alfaxz3(itr2)                    temp3 = temp3 + alfaxz3(itr2)
 c     print*,'*   itrref,itr2 ',itrref,itr2,distance  
2571                 endif                               endif              
2572                                
2573  11188          continue  11188          continue
# Line 2713  c     print*,'*   itrref,itr2 ',itrref,i Line 2588  c     print*,'*   itrref,itr2 ',itrref,i
2588  *     1bis)  *     1bis)
2589  *     2) it is not already stored  *     2) it is not already stored
2590  *     ------------------------------------------  *     ------------------------------------------
 c     print*,'check cp_used'  
2591           do ip=1,nplanes           do ip=1,nplanes
2592              hit_plane(ip)=0              hit_plane(ip)=0
2593           enddo           enddo
2594           ncpused=0           ncpused=0
2595           do icp=1,ncp_tot           do icp=1,ncp_tot
2596              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2597         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2598         $           .true.)then
2599                 ncpused=ncpused+1                 ncpused=ncpused+1
2600                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2601                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2729  c     print*,'check cp_used' Line 2605  c     print*,'check cp_used'
2605           do ip=1,nplanes           do ip=1,nplanes
2606              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2607           enddo           enddo
 c         if(ncpused.lt.ncpxz_min)goto 22288 !next triplet  
          if(npt.lt.nptxz_min)goto 22288     !next triplet  
2608           if(nplused.lt.nplxz_min)goto 22288 !next triplet           if(nplused.lt.nplxz_min)goto 22288 !next triplet
2609                    
2610  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2764  c               mask_view(iv) = 6 Line 2638  c               mask_view(iv) = 6
2638           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2639                    
2640           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2641              print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'                            print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'              
2642              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)
2643              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)
# Line 2774  c               mask_view(iv) = 6 Line 2647  c               mask_view(iv) = 6
2647              print*,'cpcloud_xz '              print*,'cpcloud_xz '
2648       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)
2649              print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)              print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)
 c$$$            print*,'nt-uple: ptcloud_xz(',nclouds_xz,') = '  
 c$$$     $           ,ptcloud_xz(nclouds_xz)  
 c$$$            print*,'nt-uple: tr_cloud(...) = '  
 c$$$     $           ,(tr_cloud(iii),iii=npt_tot-npt+1,npt_tot)  
2650           endif           endif
2651  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2652  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2791  c$$$     $           ,(tr_cloud(iii),iii Line 2660  c$$$     $           ,(tr_cloud(iii),iii
2660         endif                             endif                    
2661                
2662        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2663           print*,'X-Z total clouds ',nclouds_xz           print*,'X-Z total clouds ',nclouds_xz
          print*,' '  
2664        endif        endif
2665                
2666                
# Line 2849  c$$$     $           ,(tr_cloud(iii),iii Line 2716  c$$$     $           ,(tr_cloud(iii),iii
2716    
2717        ntracks=0                 !counter of track candidates        ntracks=0                 !counter of track candidates
2718                
2719        do iyz=1,nclouds_yz       !loop on YZ couds        do iyz=1,nclouds_yz       !loop on YZ clouds
2720           do ixz=1,nclouds_xz    !loop on XZ couds           do ixz=1,nclouds_xz    !loop on XZ clouds
2721                            
2722  *     --------------------------------------------------  *     --------------------------------------------------
2723  *     check of consistency of the clouds  *     check of consistency of the clouds
# Line 2859  c$$$     $           ,(tr_cloud(iii),iii Line 2726  c$$$     $           ,(tr_cloud(iii),iii
2726  *     of the two clouds  *     of the two clouds
2727  *     --------------------------------------------------  *     --------------------------------------------------
2728              do ip=1,nplanes              do ip=1,nplanes
2729                 hit_plane(ip)=0                 hit_plane(ip)=0  !n.matching couples (REAL couples, not SINGLETS)
2730                 ncp_match(ip)=0                 ncp_match(ip)=0  !n.matching couples per plane
2731                 do icpp=1,ncouplemax                 do icpp=1,ncouplemax
2732                    cp_match(ip,icpp)=0 !init couple list                    cp_match(ip,icpp)=0 !init couple list
2733                 enddo                 enddo
2734              enddo              enddo
2735              ncp_ok=0              ncp_ok=0            !count n.matching-couples
2736                ncpx_ok=0           !count n.matching-couples with x cluster
2737                ncpy_ok=0           !count n.matching-couples with y cluster
2738    
2739    
2740              do icp=1,ncp_tot    !loop over couples              do icp=1,ncp_tot    !loop over couples
2741  *     get info on  
2742                 cpintersec(icp)=min(                 if(.not.RECOVER_SINGLETS)then
2743       $              cpcloud_yz(iyz,icp),  *     ------------------------------------------------------
2744       $              cpcloud_xz(ixz,icp))  *     if NOT in RECOVER_SINGLETS mode, take the intersection
2745                 if(  *     between xz yz clouds
2746       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.  *     ------------------------------------------------------
2747       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.                    cpintersec(icp)=min(
2748       $              .false.)cpintersec(icp)=0       $                 cpcloud_yz(iyz,icp),
2749         $                 cpcloud_xz(ixz,icp))
2750  *     cpintersec is >0 if yz and xz clouds contain the same image of couple icp  *     cpintersec is >0 if yz and xz clouds contain the same image of couple icp
2751    *     ------------------------------------------------------
2752    *     discard the couple if the sensor is in conflict
2753    *     ------------------------------------------------------
2754                      if(
2755         $       (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2756         $       (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2757         $                 .false.)cpintersec(icp)=0
2758                   else
2759    *     ------------------------------------------------------
2760    *     if RECOVER_SINGLETS take the union
2761    *     (otherwise the fake couples formed by singlets would be
2762    *     discarded)    
2763    *     ------------------------------------------------------
2764                      cpintersec(icp)=max(
2765         $                 cpcloud_yz(iyz,icp),
2766         $                 cpcloud_xz(ixz,icp))
2767    c$$$                  if(cpcloud_yz(iyz,icp).gt.0)
2768    c$$$     $                 cpintersec(icp)=cpcloud_yz(iyz,icp)
2769    *     cpintersec is >0 if either yz or xz cloud contains the couple icp
2770                   endif
2771    
2772    c$$$               print*,icp,ip_cp(icp),' -- ',cpintersec(icp)
2773    
2774                 if(cpintersec(icp).ne.0)then                 if(cpintersec(icp).ne.0)then
                   ncp_ok=ncp_ok+1    
2775                                        
2776                    ip=ip_cp(icp)                    ip=ip_cp(icp)
2777                    hit_plane(ip)=1                    hit_plane(ip)=1
2778    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).gt.0)
2779    c$$$     $                 ncp_ok=ncp_ok+1  
2780    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).eq.0)
2781    c$$$     $                 ncpx_ok=ncpx_ok+1
2782    c$$$                  if(clx(ip,icp).eq.0.and.cly(ip,icp).gt.0)
2783    c$$$     $                 ncpy_ok=ncpy_ok+1
2784    
2785                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2786         $                 cpcloud_xz(ixz,icp).gt.0)
2787         $                 ncp_ok=ncp_ok+1  
2788                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2789         $                 cpcloud_xz(ixz,icp).eq.0)
2790         $                 ncpy_ok=ncpy_ok+1  
2791                      if(  cpcloud_yz(iyz,icp).eq.0.and.
2792         $                 cpcloud_xz(ixz,icp).gt.0)
2793         $                 ncpx_ok=ncpx_ok+1  
2794    
2795                    if(cpintersec(icp).eq.1)then                    if(cpintersec(icp).eq.1)then
2796  *     1) only the couple image in sensor 1 matches  *     1) only the couple image in sensor 1 matches
2797                       id=-icp                       id=-icp
# Line 2907  c$$$     $           ,(tr_cloud(iii),iii Line 2818  c$$$     $           ,(tr_cloud(iii),iii
2818              do ip=1,nplanes              do ip=1,nplanes
2819                 nplused=nplused+ hit_plane(ip)                 nplused=nplused+ hit_plane(ip)
2820              enddo              enddo
2821                                        
2822                            if(nplused.lt.3)goto 888 !next combination
2823    ccc            if(nplused.lt.nplxz_min)goto 888 !next combination
2824    ccc            if(nplused.lt.nplyz_min)goto 888 !next combination
2825    *     -----------------------------------------------------------
2826    *     if in RECOVER_SINGLET mode, the two clouds must have
2827    *     at least ONE intersecting real couple
2828    *     -----------------------------------------------------------
2829                if(ncp_ok.lt.1)goto 888 !next combination
2830    
2831              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
2832                 print*,'Combination ',iyz,ixz                 print*,'////////////////////////////'
2833       $              ,' db ',ptcloud_yz(iyz)                 print*,'Cloud combination (Y,X): ',iyz,ixz
2834       $              ,' tr ',ptcloud_xz(ixz)                 print*,' db ',ptcloud_yz(iyz)
2835       $              ,'  -----> # matching couples ',ncp_ok                 print*,' tr ',ptcloud_xz(ixz)
2836                   print*,'  -----> # matching couples ',ncp_ok
2837                   print*,'  -----> # fake couples (X)',ncpx_ok
2838                   print*,'  -----> # fake couples (Y)',ncpy_ok
2839                   do icp=1,ncp_tot
2840                      print*,'cp ',icp,' >'
2841         $                 ,' x ',cpcloud_xz(ixz,icp)
2842         $                 ,' y ',cpcloud_yz(iyz,icp)
2843         $                 ,' ==> ',cpintersec(icp)
2844                   enddo
2845              endif              endif
   
 c            if(nplused.lt.nplxz_min)goto 888 !next combination  
             if(nplused.lt.nplyz_min)goto 888 !next combination  
             if(ncp_ok.lt.ncpok)goto 888 !next combination  
   
 c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'  
 c$$$  print*,'Configurazione cluster XZ'  
 c$$$  print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))  
 c$$$  print*,'2 -- ',(clx(2,i),i=1,ncp_plane(1))  
 c$$$  print*,'3 -- ',(clx(3,i),i=1,ncp_plane(1))  
 c$$$  print*,'4 -- ',(clx(4,i),i=1,ncp_plane(1))  
 c$$$  print*,'5 -- ',(clx(5,i),i=1,ncp_plane(1))  
 c$$$  print*,'6 -- ',(clx(6,i),i=1,ncp_plane(1))  
 c$$$  print*,'Configurazione cluster YZ'  
 c$$$  print*,'1 -- ',(cly(1,i),i=1,ncp_plane(1))  
 c$$$  print*,'2 -- ',(cly(2,i),i=1,ncp_plane(1))  
 c$$$  print*,'3 -- ',(cly(3,i),i=1,ncp_plane(1))  
 c$$$  print*,'4 -- ',(cly(4,i),i=1,ncp_plane(1))  
 c$$$  print*,'5 -- ',(cly(5,i),i=1,ncp_plane(1))  
 c$$$  print*,'6 -- ',(cly(6,i),i=1,ncp_plane(1))  
 c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'  
               
 *     -------> INITIAL GUESS <-------  
 cccc       SBAGLIATO  
 c$$$            AL_INI(1) = dreal(alfaxz1_av(ixz))  
 c$$$            AL_INI(2) = dreal(alfayz1_av(iyz))  
 c$$$            AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))  
 c$$$     $           /dreal(alfaxz2_av(ixz)))  
 c$$$            tath      = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))  
 c$$$            AL_INI(3) = tath/sqrt(1+tath**2)  
 c$$$            AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.  
 cccc       GIUSTO (ma si sua guess())  
 c$$$            AL_INI(1) = dreal(alfaxz1_av(ixz))  
 c$$$            AL_INI(2) = dreal(alfayz1_av(iyz))  
 c$$$            tath      = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))  
 c$$$            AL_INI(3) = tath/sqrt(1+tath**2)  
 c$$$            IF(alfaxz2_av(ixz).NE.0)THEN  
 c$$$            AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))  
 c$$$     $           /dreal(alfaxz2_av(ixz)))  
 c$$$            ELSE  
 c$$$               AL_INI(4) = acos(-1.)/2  
 c$$$               IF(alfayz2_av(iyz).LT.0)AL_INI(4) = AL_INI(4)+acos(-1.)  
 c$$$            ENDIF  
 c$$$            IF(alfaxz2_av(ixz).LT.0)AL_INI(4)= acos(-1.)+ AL_INI(4)  
 c$$$            AL_INI(4) = -acos(-1.) + AL_INI(4) !from incidence direction to tracking rs  
 c$$$              
 c$$$            AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.  
 c$$$              
 c$$$            if(AL_INI(5).gt.defmax)goto 888 !next cloud  
2846                                                    
2847              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
                print*,'track candidate', ntracks+1  
2848                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2849                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2850                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
# Line 2999  c$$$            if(AL_INI(5).gt.defmax)g Line 2877  c$$$            if(AL_INI(5).gt.defmax)g
2877                                hit_plane(6)=icp6                                hit_plane(6)=icp6
2878                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
2879                                                                
2880                                  if(DEBUG.eq.1)
2881         $                             print*,'combination: '
2882         $                             ,cp_match(6,icp1)
2883         $                             ,cp_match(5,icp2)
2884         $                             ,cp_match(4,icp3)
2885         $                             ,cp_match(3,icp4)
2886         $                             ,cp_match(2,icp5)
2887         $                             ,cp_match(1,icp6)
2888    
2889    
2890  *                             ---------------------------------------  *                             ---------------------------------------
2891  *                             check if this group of couples has been  *                             check if this group of couples has been
2892  *                             already fitted      *                             already fitted    
# Line 3047  c     $                                 Line 2935  c     $                                
2935       $                                   PFAdef,PFAdef,0.,0.,0.,0.)       $                                   PFAdef,PFAdef,0.,0.,0.,0.)
2936  *                                   *************************  *                                   *************************
2937  *                                   -----------------------------  *                                   -----------------------------
2938                                      xgood(nplanes-ip+1)=1.                                      if(icx.gt.0.and.icy.gt.0)then
2939                                      ygood(nplanes-ip+1)=1.                                         xgood(nplanes-ip+1)=1.
2940                                      xm(nplanes-ip+1)=xPAM                                         ygood(nplanes-ip+1)=1.
2941                                      ym(nplanes-ip+1)=yPAM                                         xm(nplanes-ip+1)=xPAM
2942                                      zm(nplanes-ip+1)=zPAM                                         ym(nplanes-ip+1)=yPAM
2943                                      resx(nplanes-ip+1)=resxPAM                                         zm(nplanes-ip+1)=zPAM
2944                                      resy(nplanes-ip+1)=resyPAM                                         resx(nplanes-ip+1)=resxPAM                                      
2945                                           resy(nplanes-ip+1)=resyPAM
2946                                           if(DEBUG.EQ.1)print*,'(X,Y)'
2947         $                                      ,nplanes-ip+1,xPAM,yPAM
2948                                        else
2949                                           xm_A(nplanes-ip+1) = xPAM_A
2950                                           ym_A(nplanes-ip+1) = yPAM_A
2951                                           xm_B(nplanes-ip+1) = xPAM_B
2952                                           ym_B(nplanes-ip+1) = yPAM_B
2953                                           zm(nplanes-ip+1)
2954         $                                      = (zPAM_A+zPAM_B)/2.
2955                                           resx(nplanes-ip+1) = resxPAM                                      
2956                                           resy(nplanes-ip+1) = resyPAM
2957                                           if(icx.eq.0.and.icy.gt.0)then
2958                                              xgood(nplanes-ip+1)=0.
2959                                              ygood(nplanes-ip+1)=1.
2960                                              resx(nplanes-ip+1) = 1000.
2961                                              if(DEBUG.EQ.1)print*,'(  Y)'
2962         $                                         ,nplanes-ip+1,xPAM,yPAM
2963                                           elseif(icx.gt.0.and.icy.eq.0)then
2964                                              xgood(nplanes-ip+1)=1.
2965                                              ygood(nplanes-ip+1)=0.
2966                                              if(DEBUG.EQ.1)print*,'(X  )'
2967         $                                         ,nplanes-ip+1,xPAM,yPAM
2968                                              resy(nplanes-ip+1) = 1000.
2969                                           else
2970                                              print*,'both icx=0 and icy=0'
2971         $                                         ,' ==> IMPOSSIBLE!!'
2972                                           endif
2973                                        endif
2974  *                                   -----------------------------  *                                   -----------------------------
2975                                   endif                                   endif
2976                                enddo !end loop on planes                                enddo !end loop on planes
# Line 3139  c                                    mas Line 3056  c                                    mas
3056       $                                   cp_match(ip,hit_plane(ip))       $                                   cp_match(ip,hit_plane(ip))
3057                                      SENSOR_STORE(nplanes-ip+1,ntracks)                                      SENSOR_STORE(nplanes-ip+1,ntracks)
3058       $                              = is_cp(cp_match(ip,hit_plane(ip)))       $                              = is_cp(cp_match(ip,hit_plane(ip)))
3059                                      LADDER_STORE(nplanes-ip+1,ntracks)                                      
3060       $                                   = LADDER(                                      icl=
3061       $                                   clx(ip,icp_cp(       $                                   clx(ip,icp_cp(
3062       $                                   cp_match(ip,hit_plane(ip)       $                                   cp_match(ip,hit_plane(ip)
3063       $                                   ))));       $                                   )));
3064                                        if(icl.eq.0)
3065         $                                   icl=
3066         $                                   cly(ip,icp_cp(
3067         $                                   cp_match(ip,hit_plane(ip)
3068         $                                   )));
3069    
3070                                        LADDER_STORE(nplanes-ip+1,ntracks)
3071         $                                   = LADDER(icl);
3072                                   else                                   else
3073                                      CP_STORE(nplanes-ip+1,ntracks)=0                                      CP_STORE(nplanes-ip+1,ntracks)=0
3074                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0
# Line 3177  c                                    mas Line 3102  c                                    mas
3102                
3103        if(ntracks.eq.0)then        if(ntracks.eq.0)then
3104           iflag=1           iflag=1
3105           return  cc         return
3106        endif        endif
3107                
 c$$$      if(DEBUG.EQ.1)then  
 c$$$         print*,'****** TRACK CANDIDATES ***********'  
 c$$$         print*,'#         R. chi2        RIG'  
 c$$$         do i=1,ntracks  
 c$$$            print*,i,' --- ',rchi2_store(i),' --- '  
 c$$$     $           ,1./abs(AL_STORE(5,i))  
 c$$$         enddo  
 c$$$         print*,'***********************************'  
 c$$$      endif  
3108        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
3109          print*,'****** TRACK CANDIDATES *****************'          print*,'****** TRACK CANDIDATES *****************'
3110          print*,'#         R. chi2        RIG         ndof'          print*,'#         R. chi2        RIG         ndof'
# Line 3250  c$$$      endif Line 3166  c$$$      endif
3166        call track_init        call track_init
3167        do ip=1,nplanes           !loop on planes        do ip=1,nplanes           !loop on planes
3168    
3169             if(DEBUG.EQ.1)print*,' ........... plane ',ip,' ........... '
3170    
3171           xP=XV_STORE(nplanes-ip+1,ibest)           xP=XV_STORE(nplanes-ip+1,ibest)
3172           yP=YV_STORE(nplanes-ip+1,ibest)           yP=YV_STORE(nplanes-ip+1,ibest)
3173           zP=ZV_STORE(nplanes-ip+1,ibest)           zP=ZV_STORE(nplanes-ip+1,ibest)
# Line 3266  c$$$         bxyz(3)=0 Line 3184  c$$$         bxyz(3)=0
3184  *     using improved PFAs  *     using improved PFAs
3185  *     -------------------------------------------------  *     -------------------------------------------------
3186  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3187           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.  c$$$         if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
3188    c$$$     $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3189    c$$$            
3190    c$$$            id=CP_STORE(nplanes-ip+1,ibest)
3191    c$$$            
3192    c$$$            is=is_cp(id)
3193    c$$$            icp=icp_cp(id)
3194    c$$$            if(ip_cp(id).ne.ip)
3195    c$$$     $           print*,'OKKIO!!'
3196    c$$$     $           ,'id ',id,is,icp
3197    c$$$     $           ,ip_cp(id),ip
3198    c$$$            icx=clx(ip,icp)
3199    c$$$            icy=cly(ip,icp)
3200    c$$$c            call xyz_PAM(icx,icy,is,
3201    c$$$c     $           PFA,PFA,
3202    c$$$c     $           AXV_STORE(nplanes-ip+1,ibest),
3203    c$$$c     $           AYV_STORE(nplanes-ip+1,ibest))
3204    c$$$            call xyz_PAM(icx,icy,is,
3205    c$$$     $           PFA,PFA,
3206    c$$$     $           AXV_STORE(nplanes-ip+1,ibest),
3207    c$$$     $           AYV_STORE(nplanes-ip+1,ibest),
3208    c$$$     $           bxyz(1),
3209    c$$$     $           bxyz(2)
3210    c$$$     $           )
3211    c$$$
3212    c$$$            xm(nplanes-ip+1) = xPAM
3213    c$$$            ym(nplanes-ip+1) = yPAM
3214    c$$$            zm(nplanes-ip+1) = zPAM
3215    c$$$            xgood(nplanes-ip+1) = 1
3216    c$$$            ygood(nplanes-ip+1) = 1
3217    c$$$            resx(nplanes-ip+1) = resxPAM
3218    c$$$            resy(nplanes-ip+1) = resyPAM
3219    c$$$
3220    c$$$            dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3221    c$$$            dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3222             if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..or.
3223       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3224                            
3225              id=CP_STORE(nplanes-ip+1,ibest)              id=CP_STORE(nplanes-ip+1,ibest)
# Line 3291  c     $           AYV_STORE(nplanes-ip+1 Line 3244  c     $           AYV_STORE(nplanes-ip+1
3244       $           bxyz(2)       $           bxyz(2)
3245       $           )       $           )
3246    
3247              xm(nplanes-ip+1) = xPAM              if(icx.gt.0.and.icy.gt.0)then
3248              ym(nplanes-ip+1) = yPAM                 xm(nplanes-ip+1) = xPAM
3249              zm(nplanes-ip+1) = zPAM                 ym(nplanes-ip+1) = yPAM
3250              xgood(nplanes-ip+1) = 1                 zm(nplanes-ip+1) = zPAM
3251              ygood(nplanes-ip+1) = 1                 xm_A(nplanes-ip+1) = 0.
3252              resx(nplanes-ip+1) = resxPAM                 ym_A(nplanes-ip+1) = 0.
3253              resy(nplanes-ip+1) = resyPAM                 xm_B(nplanes-ip+1) = 0.
3254                   ym_B(nplanes-ip+1) = 0.
3255              dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))                 xgood(nplanes-ip+1) = 1
3256              dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))                 ygood(nplanes-ip+1) = 1
3257                   resx(nplanes-ip+1) = resxPAM
3258                   resy(nplanes-ip+1) = resyPAM
3259                   dedxtrk_x(nplanes-ip+1)=
3260         $              sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3261                   dedxtrk_y(nplanes-ip+1)=
3262         $              sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3263                else
3264                   xm(nplanes-ip+1) = 0.
3265                   ym(nplanes-ip+1) = 0.
3266                   zm(nplanes-ip+1) = (zPAM_A+zPAM_B)/2.
3267                   xm_A(nplanes-ip+1) = xPAM_A
3268                   ym_A(nplanes-ip+1) = yPAM_A
3269                   xm_B(nplanes-ip+1) = xPAM_B
3270                   ym_B(nplanes-ip+1) = yPAM_B
3271                   xgood(nplanes-ip+1) = 0
3272                   ygood(nplanes-ip+1) = 0
3273                   resx(nplanes-ip+1) = 1000.!resxPAM
3274                   resy(nplanes-ip+1) = 1000.!resyPAM
3275                   dedxtrk_x(nplanes-ip+1)= 0
3276                   dedxtrk_y(nplanes-ip+1)= 0
3277                   if(icx.gt.0)then
3278                      xgood(nplanes-ip+1) = 1
3279                      resx(nplanes-ip+1) = resxPAM
3280                      dedxtrk_x(nplanes-ip+1)=
3281         $                 sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3282                   elseif(icy.gt.0)then
3283                      ygood(nplanes-ip+1) = 1
3284                      resy(nplanes-ip+1) = resyPAM
3285                      dedxtrk_y(nplanes-ip+1)=
3286         $                 sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3287                   endif
3288                endif
3289                            
3290  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3291  *     -------------------------------------------------  *     -------------------------------------------------
# Line 3312  c     $           AYV_STORE(nplanes-ip+1 Line 3297  c     $           AYV_STORE(nplanes-ip+1
3297                                
3298              xgood(nplanes-ip+1)=0              xgood(nplanes-ip+1)=0
3299              ygood(nplanes-ip+1)=0              ygood(nplanes-ip+1)=0
3300    
3301                CP_STORE(nplanes-ip+1,ibest)=0 !re-init
3302                CLS_STORE(nplanes-ip+1,ibest)=0
3303    
3304                                
3305  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3306  *     determine which ladder and sensor are intersected by the track  *     determine which ladder and sensor are intersected by the track
# Line 3334  c     $           AYV_STORE(nplanes-ip+1 Line 3323  c     $           AYV_STORE(nplanes-ip+1
3323  *     ===========================================  *     ===========================================
3324  *     STEP 1 >>>>>>>  try to include a new couple  *     STEP 1 >>>>>>>  try to include a new couple
3325  *     ===========================================  *     ===========================================
3326  c            if(DEBUG.EQ.1)print*,'>>>> try to include a new couple'              distmin=100000000.
             distmin=1000000.  
3327              xmm = 0.              xmm = 0.
3328              ymm = 0.              ymm = 0.
3329              zmm = 0.              zmm = 0.
# Line 3348  c            if(DEBUG.EQ.1)print*,'>>>> Line 3336  c            if(DEBUG.EQ.1)print*,'>>>>
3336              do icp=1,ncp_plane(ip) !loop on couples on plane icp              do icp=1,ncp_plane(ip) !loop on couples on plane icp
3337                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3338                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3339                   if(icx.eq.0.or.icy.eq.0)goto 1188!if fake couple, jump to next
3340                 if(LADDER(icx).ne.nldt.or. !If the ladder number does not match                 if(LADDER(icx).ne.nldt.or. !If the ladder number does not match
3341  c     $              cl_used(icx).eq.1.or. !or the X cluster is already used  c     $              cl_used(icx).eq.1.or. !or the X cluster is already used
3342  c     $              cl_used(icy).eq.1.or. !or the Y cluster is already used  c     $              cl_used(icy).eq.1.or. !or the Y cluster is already used
3343       $              cl_used(icx).ne.0.or. !or the X cluster is already used !(3)       $              cl_used(icx).ne.0.or. !or the X cluster is already used
3344       $              cl_used(icy).ne.0.or. !or the Y cluster is already used !(3)       $              cl_used(icy).ne.0.or. !or the Y cluster is already used
3345       $              .false.)goto 1188 !then jump to next couple.       $              .false.)goto 1188 !then jump to next couple.
3346  *            *          
3347                 call xyz_PAM(icx,icy,ist,                 call xyz_PAM(icx,icy,ist,
# Line 3366  c     $              cl_used(icy).eq.1.o Line 3355  c     $              cl_used(icy).eq.1.o
3355                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3356  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3357                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3358                 if(DEBUG.EQ.1)print*,'( couple ',id                 if(DEBUG.EQ.1)
3359         $              print*,'( couple ',id
3360       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3361                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3362                    xmm = xPAM                    xmm = xPAM
# Line 3378  c               distance = distance / RC Line 3368  c               distance = distance / RC
3368                    idm = id                                      idm = id                  
3369                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3370                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3371  c     QUIQUI --> non devo moltiplicare per clinc?!?!?!                    clincnewc=10*sqrt(rymm**2+rxmm**2
3372                    clincnewc=10*sqrt(rymm**2+rxmm**2 !QUIQUI       $                 +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2)))
      $                 +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2))) !QUIQUI  
3373                 endif                 endif
3374   1188          continue   1188          continue
3375              enddo               !end loop on couples on plane icp              enddo               !end loop on couples on plane icp
3376  c            if(distmin.le.clinc)then     !QUIQUI                            if(distmin.le.clincnewc)then    
             if(distmin.le.clincnewc)then     !QUIQUI                
3377  *              -----------------------------------  *              -----------------------------------
3378                 xm(nplanes-ip+1) = xmm !<<<                 xm(nplanes-ip+1) = xmm !<<<
3379                 ym(nplanes-ip+1) = ymm !<<<                 ym(nplanes-ip+1) = ymm !<<<
# Line 3399  c            if(distmin.le.clinc)then   Line 3387  c            if(distmin.le.clinc)then  
3387  *              -----------------------------------  *              -----------------------------------
3388                 CP_STORE(nplanes-ip+1,ibest)=idm                       CP_STORE(nplanes-ip+1,ibest)=idm      
3389                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm
3390       $              ,' (dist.= ',distmin,', cut ',clinc,' )'       $              ,' (dist.= ',distmin,', cut ',clincnewc,' )'
3391                 goto 133         !next plane                 goto 133         !next plane
3392              endif              endif
3393  *     ================================================  *     ================================================
3394  *     STEP 2 >>>>>>>  try to include a single cluster  *     STEP 2 >>>>>>>  try to include a single cluster
3395  *                     either from a couple or single  *                     either from a couple or single
3396  *     ================================================  *     ================================================
 c            if(DEBUG.EQ.1)print*,'>>>> try to include a new cluster'  
3397              distmin=1000000.              distmin=1000000.
3398              xmm_A = 0.          !---------------------------              xmm_A = 0.          !---------------------------
3399              ymm_A = 0.          ! init variables that              ymm_A = 0.          ! init variables that
# Line 3425  c            if(DEBUG.EQ.1)print*,'>>>> Line 3412  c            if(DEBUG.EQ.1)print*,'>>>>
3412              do icp=1,ncp_plane(ip) !loop on cluster inside couples              do icp=1,ncp_plane(ip) !loop on cluster inside couples
3413                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3414                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3415                   if(icx.eq.0.or.icy.eq.0)goto 11882!if fake couple, jump to next
3416                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3417                 if(LADDER(icx).ne.nldt)goto 11882 !if the ladder number does not match                 if(LADDER(icx).ne.nldt)goto 11882 !if the ladder number does not match
3418  *                                                !jump to the next couple  *                                                !jump to the next couple
# Line 3443  c     $              AXV_STORE(nplanes-i Line 3431  c     $              AXV_STORE(nplanes-i
3431       $              )                     $              )              
3432                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3433  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3434                 if(DEBUG.EQ.1)print*,'( cl-X ',icx                 if(DEBUG.EQ.1)
3435         $              print*,'( cl-X ',icx
3436       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3437                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3438                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3476  c     $              0.,AYV_STORE(nplane Line 3465  c     $              0.,AYV_STORE(nplane
3465       $              )       $              )
3466                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3467  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3468                 if(DEBUG.EQ.1)print*,'( cl-Y ',icy                 if(DEBUG.EQ.1)
3469         $              print*,'( cl-Y ',icy
3470       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3471                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3472                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3496  c                 dedxmm = sgnl(icy)  !( Line 3486  c                 dedxmm = sgnl(icy)  !(
3486  11882          continue  11882          continue
3487              enddo               !end loop on cluster inside couples              enddo               !end loop on cluster inside couples
3488  *----- single clusters -----------------------------------------------    *----- single clusters -----------------------------------------------  
 c            print*,'## ncls(',ip,') ',ncls(ip)  
3489              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
3490                 icl=cls(ip,ic)                 icl=cls(ip,ic)
 c               if(cl_used(icl).eq.1.or.     !if the cluster is already used  
3491                 if(cl_used(icl).ne.0.or.     !if the cluster is already used !(3)                 if(cl_used(icl).ne.0.or.     !if the cluster is already used !(3)
3492       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match
3493       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
# Line 3521  c               if(cl_used(icl).eq.1.or. Line 3509  c               if(cl_used(icl).eq.1.or.
3509    
3510                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3511  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3512                 if(DEBUG.EQ.1)print*,'( cl-s ',icl                 if(DEBUG.EQ.1)
3513         $              print*,'( cl-s ',icl
3514       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3515                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
 c                  if(DEBUG.EQ.1)print*,'YES'  
3516                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3517                    ymm_A = yPAM_A                    ymm_A = yPAM_A
3518                    zmm_A = zPAM_A                    zmm_A = zPAM_A
# Line 3545  c                  if(DEBUG.EQ.1)print*, Line 3533  c                  if(DEBUG.EQ.1)print*,
3533                 endif                                   endif                  
3534  18882          continue  18882          continue
3535              enddo               !end loop on single clusters              enddo               !end loop on single clusters
 c            print*,'## distmin ', distmin,' clinc ',clinc  
3536    
 c     QUIQUI------------  
 c     anche qui: non ci vuole clinc???  
3537              if(iclm.ne.0)then              if(iclm.ne.0)then
3538                 if(mod(VIEW(iclm),2).eq.0)then                 if(mod(VIEW(iclm),2).eq.0)then
3539                    clincnew=                    clincnew=
# Line 3559  c     anche qui: non ci vuole clinc??? Line 3544  c     anche qui: non ci vuole clinc???
3544       $                 10*       $                 10*
3545       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))
3546                 endif                 endif
3547  c     QUIQUI------------  
3548                                 if(distmin.le.clincnew)then  
                if(distmin.le.clincnew)then   !QUIQUI  
 c     if(distmin.le.clinc)then          !QUIQUI            
3549                                        
3550                    CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<                        CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<    
3551  *     ----------------------------  *     ----------------------------
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3552                    if(mod(VIEW(iclm),2).eq.0)then                    if(mod(VIEW(iclm),2).eq.0)then
3553                       XGOOD(nplanes-ip+1)=1.                       XGOOD(nplanes-ip+1)=1.
3554                       resx(nplanes-ip+1)=rxmm                       resx(nplanes-ip+1)=rxmm
3555                       if(DEBUG.EQ.1)print*,'%%%% included X-cl ',iclm                       if(DEBUG.EQ.1)
3556         $                    print*,'%%%% included X-cl ',iclm
3557       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3558       $                    ,', dist.= ',distmin       $                    ,', dist.= ',distmin
3559       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3560                    else                    else
3561                       YGOOD(nplanes-ip+1)=1.                       YGOOD(nplanes-ip+1)=1.
3562                       resy(nplanes-ip+1)=rymm                       resy(nplanes-ip+1)=rymm
3563                       if(DEBUG.EQ.1)print*,'%%%% included Y-cl ',iclm                       if(DEBUG.EQ.1)
3564         $                    print*,'%%%% included Y-cl ',iclm
3565       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3566       $                    ,', dist.= ', distmin       $                    ,', dist.= ', distmin
3567       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3568                    endif                    endif
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3569  *     ----------------------------  *     ----------------------------
3570                    xm_A(nplanes-ip+1) = xmm_A                    xm_A(nplanes-ip+1) = xmm_A
3571                    ym_A(nplanes-ip+1) = ymm_A                    ym_A(nplanes-ip+1) = ymm_A
# Line 3603  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3586  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3586        return        return
3587        end        end
3588    
3589    
3590  ***************************************************  ***************************************************
3591  *                                                 *  *                                                 *
3592  *                                                 *  *                                                 *
# Line 3612  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3596  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3596  *                                                 *  *                                                 *
3597  **************************************************  **************************************************
3598  *  *
       subroutine clean_XYclouds(ibest,iflag)  
   
       include 'commontracker.f'  
       include 'level1.f'  
       include 'common_momanhough.f'  
       include 'level2.f'        
   
       if(DEBUG.EQ.1)print*,'clean_XYclouds:'  
   
       do ip=1,nplanes           !loop on planes  
   
          id=CP_STORE(nplanes-ip+1,ibest)  
          icl=CLS_STORE(nplanes-ip+1,ibest)  
          if(id.ne.0.or.icl.ne.0)then                
             if(id.ne.0)then  
                iclx=clx(ip,icp_cp(id))  
                icly=cly(ip,icp_cp(id))  
 c$$$               cl_used(iclx)=ntrk  !tag used clusters  
 c$$$               cl_used(icly)=ntrk  !tag used clusters  
             elseif(icl.ne.0)then  
 c$$$               cl_used(icl)=ntrk   !tag used clusters  
             endif  
               
 *     -----------------------------  
 *     remove the couple from clouds  
 *     remove also vitual couples containing the  
 *     selected clusters  
 *     -----------------------------  
             do icp=1,ncp_plane(ip)  
                if(  
      $              clx(ip,icp).eq.iclx  
      $              .or.  
      $              clx(ip,icp).eq.icl  
      $              .or.  
      $              cly(ip,icp).eq.icly  
      $              .or.  
      $              cly(ip,icp).eq.icl  
      $              )then  
                   id=id_cp(ip,icp,1)  
                   if(DEBUG.EQ.1)then  
                      print*,ip,' <<< cp ',id  
      $                    ,' ( cl-x '  
      $                    ,clx(ip,icp)  
      $                    ,' cl-y '  
      $                    ,cly(ip,icp),' ) --> removed'  
                   endif  
 *     -----------------------------  
 *     remove the couple from clouds  
                   do iyz=1,nclouds_yz  
                      if(cpcloud_yz(iyz,abs(id)).ne.0)then  
                         ptcloud_yz(iyz)=ptcloud_yz(iyz)-1  
                         cpcloud_yz(iyz,abs(id))=0  
                      endif  
                   enddo  
                   do ixz=1,nclouds_xz  
                      if(cpcloud_xz(ixz,abs(id)).ne.0)then  
                         ptcloud_xz(ixz)=ptcloud_xz(ixz)-1  
                         cpcloud_xz(ixz,abs(id))=0  
                      endif  
                   enddo                      
 *     -----------------------------  
                endif  
             enddo  
               
          endif                
       enddo                     !end loop on planes  
         
       return  
       end  
   
   
   
3599    
3600    
3601    
# Line 3732  c$$$               cl_used(icl)=ntrk   ! Line 3644  c$$$               cl_used(icl)=ntrk   !
3644              DEDX_Y(IP,IT) = 0              DEDX_Y(IP,IT) = 0
3645              CLTRX(IP,IT) = 0              CLTRX(IP,IT) = 0
3646              CLTRY(IP,IT) = 0              CLTRY(IP,IT) = 0
3647                multmaxx(ip,it) = 0
3648                seedx(ip,it)    = 0
3649                xpu(ip,it)      = 0
3650                multmaxy(ip,it) = 0
3651                seedy(ip,it)    = 0
3652                ypu(ip,it)      = 0
3653           enddo           enddo
3654           do ipa=1,5           do ipa=1,5
3655              AL_nt(IPA,IT) = 0              AL_nt(IPA,IT) = 0
# Line 3751  c$$$               cl_used(icl)=ntrk   ! Line 3669  c$$$               cl_used(icl)=ntrk   !
3669          ys(1,ip)=0          ys(1,ip)=0
3670          ys(2,ip)=0          ys(2,ip)=0
3671          sgnlys(ip)=0          sgnlys(ip)=0
3672            sxbad(ip)=0
3673            sybad(ip)=0
3674            multmaxsx(ip)=0
3675            multmaxsy(ip)=0
3676        enddo        enddo
3677        end        end
3678    
# Line 3873  c$$$               cl_used(icl)=ntrk   ! Line 3795  c$$$               cl_used(icl)=ntrk   !
3795        integer ssensor,sladder        integer ssensor,sladder
3796        pig=acos(-1.)        pig=acos(-1.)
3797    
3798    
3799    
3800  *     -------------------------------------  *     -------------------------------------
3801        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3802        nstep_nt(ntr)       = nstep        nstep_nt(ntr)       = nstep
# Line 3920  c$$$               cl_used(icl)=ntrk   ! Line 3844  c$$$               cl_used(icl)=ntrk   !
3844           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)
3845           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)             dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)  
3846        
3847    
3848    ccc         print*,ip,'dedx >>> ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3849    
3850           ax   = axv_nt(ip,ntr)           ax   = axv_nt(ip,ntr)
3851           ay   = ayv_nt(ip,ntr)           ay   = ayv_nt(ip,ntr)
3852           bfx  = BX_STORE(ip,IDCAND)           bfx  = BX_STORE(ip,IDCAND)
3853           bfy  = BY_STORE(ip,IDCAND)           bfy  = BY_STORE(ip,IDCAND)
3854           if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)  c$$$         if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)
3855           if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)  c$$$         if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)
3856           tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001  c$$$         tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001
3857           angx     = 180.*atan(tgtemp)/acos(-1.)  c$$$         angx     = 180.*atan(tgtemp)/acos(-1.)
3858           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001          c$$$         tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001        
3859           angy    = 180.*atan(tgtemp)/acos(-1.)  c$$$         angy    = 180.*atan(tgtemp)/acos(-1.)
3860    
3861             angx = effectiveangle(ax,2*ip,bfy)
3862             angy = effectiveangle(ay,2*ip-1,bfx)
3863            
3864                    
 c         print*,'* ',ip,bfx,bfy,angx,angy  
3865    
3866           id  = CP_STORE(ip,IDCAND) ! couple id           id  = CP_STORE(ip,IDCAND) ! couple id
3867           icl = CLS_STORE(ip,IDCAND)           icl = CLS_STORE(ip,IDCAND)
# Line 3947  c           >>> is a couple Line 3877  c           >>> is a couple
3877              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3878              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3879    
3880              cl_used(cltrx(ip,ntr)) = 1     !tag used clusters                        if(clx(nplanes-ip+1,icp_cp(id)).gt.0)then
3881              cl_used(cltry(ip,ntr)) = 1     !tag used clusters            
3882                   cl_used(cltrx(ip,ntr)) = 1 !tag used clusters          
3883    
3884                   xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))              
3885    
3886                   if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3887         $              dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3888                  
3889                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3890         $              +10000*mult(cltrx(ip,ntr))
3891                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3892         $              /clsigma(indmax(cltrx(ip,ntr)))
3893                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3894                   xpu(ip,ntr)      = corr
3895    
3896                endif
3897                if(cly(nplanes-ip+1,icp_cp(id)).gt.0)then
3898    
3899  c$$$            nnnnx = npfastrips(clx(nplanes-ip+1,icp_cp(id)),PFA,angx)                 cl_used(cltry(ip,ntr)) = 1 !tag used clusters          
 c$$$            nnnny = npfastrips(cly(nplanes-ip+1,icp_cp(id)),PFA,angy)              
 c$$$            xbad(ip,ntr)= nbadstrips(nnnnx,clx(nplanes-ip+1,icp_cp(id)))  
 c$$$            ybad(ip,ntr)= nbadstrips(nnnny,cly(nplanes-ip+1,icp_cp(id)))  
             xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))  
             ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))  
3900    
3901                   ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))
3902    
3903              if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)                 if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3904       $           dedx_x(ip,ntr)=-dedx_x(ip,ntr)       $              dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3905              if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)                
3906       $           dedx_y(ip,ntr)=-dedx_y(ip,ntr)                 multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3907         $              +10000*mult(cltry(ip,ntr))
3908                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3909         $              /clsigma(indmax(cltry(ip,ntr)))
3910                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3911                   ypu(ip,ntr)      = corr
3912                endif
3913    
3914           elseif(icl.ne.0)then           elseif(icl.ne.0)then
3915    
# Line 3969  c$$$            ybad(ip,ntr)= nbadstrips Line 3917  c$$$            ybad(ip,ntr)= nbadstrips
3917    
3918              if(mod(VIEW(icl),2).eq.0)then              if(mod(VIEW(icl),2).eq.0)then
3919                 cltrx(ip,ntr)=icl                 cltrx(ip,ntr)=icl
 c$$$               nnnnn = npfastrips(icl,PFA,angx)  
 c$$$               xbad(ip,ntr) = nbadstrips(nnnnn,icl)  
3920                 xbad(ip,ntr) = nbadstrips(4,icl)                 xbad(ip,ntr) = nbadstrips(4,icl)
3921    
3922                 if(nsatstrips(icl).gt.0)dedx_x(ip,ntr)=-dedx_x(ip,ntr)                 if(nsatstrips(icl).gt.0)dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3923    
3924                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3925         $                         +10000*mult(cltrx(ip,ntr))
3926                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3927         $           /clsigma(indmax(cltrx(ip,ntr)))
3928                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3929                   xpu(ip,ntr)      = corr
3930    
3931              elseif(mod(VIEW(icl),2).eq.1)then              elseif(mod(VIEW(icl),2).eq.1)then
3932                 cltry(ip,ntr)=icl                 cltry(ip,ntr)=icl
 c$$$               nnnnn = npfastrips(icl,PFA,angy)  
 c$$$               ybad(ip,ntr) = nbadstrips(nnnnn,icl)  
3933                 ybad(ip,ntr) = nbadstrips(4,icl)                 ybad(ip,ntr) = nbadstrips(4,icl)
3934    
3935                 if(nsatstrips(icl).gt.0)dedx_y(ip,ntr)=-dedx_y(ip,ntr)                 if(nsatstrips(icl).gt.0)dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3936    
3937                   multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3938         $                         +10000*mult(cltry(ip,ntr))
3939                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3940         $           /clsigma(indmax(cltry(ip,ntr)))
3941                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3942                   ypu(ip,ntr)      = corr
3943                  
3944              endif              endif
3945    
3946           endif                     endif          
# Line 3992  c$$$               ybad(ip,ntr) = nbadst Line 3953  c$$$               ybad(ip,ntr) = nbadst
3953           do ip=1,6           do ip=1,6
3954              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)
3955           enddo           enddo
3956             print*,'dedx: '
3957             do ip=1,6
3958                print*,'> ',ip,' -- ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3959             enddo
3960        endif        endif
3961    
 c$$$      print*,(xgood(i),i=1,6)  
 c$$$      print*,(ygood(i),i=1,6)  
 c$$$      print*,(ls(i,ntr),i=1,6)  
 c$$$      print*,(dedx_x(i,ntr),i=1,6)  
 c$$$      print*,(dedx_y(i,ntr),i=1,6)  
 c$$$      print*,'-----------------------'  
   
3962        end        end
3963    
3964        subroutine fill_level2_siglets        subroutine fill_level2_siglets
# Line 4036  c         if( mask_view(iv).ne.0 )good2( Line 3994  c         if( mask_view(iv).ne.0 )good2(
3994           ip=nplanes-npl(VIEW(icl))+1                       ip=nplanes-npl(VIEW(icl))+1            
3995                    
3996           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
3997    
3998              if(mod(VIEW(icl),2).eq.0)then !=== X views              if(mod(VIEW(icl),2).eq.0)then !=== X views
3999    
4000                 nclsx = nclsx + 1                 nclsx = nclsx + 1
4001                 planex(nclsx) = ip                 planex(nclsx) = ip
4002                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4003                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)
4004                 clsx(nclsx)   = icl                 clsx(nclsx)   = icl
4005                   sxbad(nclsx)  = nbadstrips(1,icl)
4006                   multmaxsx(nclsx) = maxs(icl)+10000*mult(icl)
4007                  
4008    
4009                 do is=1,2                 do is=1,2
4010  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4011  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
4012                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)
4013                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2
4014                 enddo                 enddo
 c$$$               print*,'nclsx         ',nclsx  
 c$$$               print*,'planex(nclsx) ',planex(nclsx)  
 c$$$               print*,'sgnlxs(nclsx) ',sgnlxs(nclsx)  
 c$$$               print*,'xs(1,nclsx)   ',xs(1,nclsx)  
 c$$$               print*,'xs(2,nclsx)   ',xs(2,nclsx)  
4015              else                          !=== Y views              else                          !=== Y views
4016                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4017                 planey(nclsy) = ip                 planey(nclsy) = ip
4018                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4019                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)
4020                 clsy(nclsy)   = icl                 clsy(nclsy)   = icl
4021                   sybad(nclsy)  = nbadstrips(1,icl)
4022                   multmaxsy(nclsy) = maxs(icl)+10000*mult(icl)
4023    
4024    
4025                 do is=1,2                 do is=1,2
4026  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4027  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
4028                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)
4029                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2
4030                 enddo                 enddo
 c$$$               print*,'nclsy         ',nclsy  
 c$$$               print*,'planey(nclsy) ',planey(nclsy)  
 c$$$               print*,'sgnlys(nclsy) ',sgnlys(nclsy)  
 c$$$               print*,'ys(1,nclsy)   ',ys(1,nclsy)  
 c$$$               print*,'ys(2,nclsy)   ',ys(2,nclsy)  
4031              endif              endif
4032           endif           endif
4033    
# Line 4082  c$$$               print*,'ys(2,nclsy)   Line 4040  c$$$               print*,'ys(2,nclsy)  
4040  *     associati ad una traccia, e permettere di salvare  *     associati ad una traccia, e permettere di salvare
4041  *     solo questi nell'albero di uscita  *     solo questi nell'albero di uscita
4042  *     --------------------------------------------------  *     --------------------------------------------------
4043                            
   
 c$$$         print*,' cl ',icl,' --> ',cl_used(icl)  
 c$$$  
 c$$$         if( cl_used(icl).ne.0 )then  
 c$$$            if(  
 c$$$     $           mod(VIEW(icl),2).eq.0.and.  
 c$$$     $           cltrx(ip,whichtrack(icl)).ne.icl )  
 c$$$     $           print*,'**WARNING** cltrx(',ip,',',whichtrack(icl)  
 c$$$     $           ,')=',cltrx(ip,whichtrack(icl)),'.ne.',icl  
 c$$$            if(  
 c$$$     $           mod(VIEW(icl),2).eq.1.and.  
 c$$$     $           cltry(ip,whichtrack(icl)).ne.icl )  
 c$$$     $           print*,'**WARNING** cltry(',ip,',',whichtrack(icl)  
 c$$$     $           ,')=',cltry(ip,whichtrack(icl)),'.ne.',icl  
 c$$$         endif  
           
   
4044        enddo        enddo
4045        end        end
4046    

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

  ViewVC Help
Powered by ViewVC 1.1.23