/[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.29 by pam-fi, Tue Aug 21 15:21:52 2007 UTC revision 1.40 by mocchiut, Tue Aug 4 14:01:35 2009 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  c11111    continue               !<<<<<<< come here when performing a new search
275             continue                  !<<<<<<< come here when performing a new search
276    
277             if(nclouds_xz.eq.0)goto 880 !go to next event    
278             if(nclouds_yz.eq.0)goto 880 !go to next event    
279    
280  c         iflag=0  c         iflag=0
281           call clouds_to_ctrack(iflag)           call clouds_to_ctrack(iflag)
282           if(iflag.eq.1)then     !no candidate tracks found           if(iflag.eq.1)then     !no candidate tracks found
283              goto 880            !fill ntp and go to next event                goto 880            !fill ntp and go to next event  
284           endif           endif
285             if(ntracks.eq.0)goto 880 !go to next event    
286    
287           FIMAGE=.false.         !processing best track (not track image)           FIMAGE=.false.         !processing best track (not track image)
288           ibest=0                !best track among candidates           ibest=0                !best track among candidates
# Line 295  c$$$         if(ibest.eq.0)goto 880 !>> Line 326  c$$$         if(ibest.eq.0)goto 880 !>>
326             endif             endif
327           enddo           enddo
328    
 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  
329    
330           if(ibest.eq.0)goto 880 !>> no good candidates           if(ibest.eq.0)goto 880 !>> no good candidates
331  *-------------------------------------------------------------------------------      *-------------------------------------------------------------------------------    
# Line 350  c$$$         enddo Line 363  c$$$         enddo
363           do i=1,5           do i=1,5
364              AL_GUESS(i)=AL(i)              AL_GUESS(i)=AL(i)
365           enddo           enddo
 c         print*,'## guess: ',al  
366    
367           do i=1,5           do i=1,5
368              AL(i)=dble(AL_STORE(i,icand))                          AL(i)=dble(AL_STORE(i,icand))            
# Line 365  c         if(DEBUG.EQ.1)iprint=1 Line 377  c         if(DEBUG.EQ.1)iprint=1
377           if(VERBOSE.EQ.1)iprint=1           if(VERBOSE.EQ.1)iprint=1
378           if(DEBUG.EQ.1)iprint=2           if(DEBUG.EQ.1)iprint=2
379           call mini2(jstep,ifail,iprint)           call mini2(jstep,ifail,iprint)
380           if(ifail.ne.0) then  cc         if(ifail.ne.0) then
381             if(ifail.ne.0.or.CHI2.ne.CHI2) then !new
382                if(CHI2.ne.CHI2)CHI2=-9999. !new
383              if(VERBOSE.EQ.1)then              if(VERBOSE.EQ.1)then
384                 print *,                 print *,
385       $              '*** MINIMIZATION FAILURE *** (after refinement) '       $              '*** MINIMIZATION FAILURE *** (after refinement) '
386       $              ,iev       $              ,iev
   
 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*,'----------------------------------------------'  
387              endif              endif
 c            chi2=-chi2  
388           endif           endif
389                    
390           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
# Line 424  c         rchi2=chi2/dble(ndof) Line 430  c         rchi2=chi2/dble(ndof)
430              if(WARNING.EQ.1)print*,'** WARNING ** sensor=0'              if(WARNING.EQ.1)print*,'** WARNING ** sensor=0'
431              goto 122            !jump              goto 122            !jump
432           endif           endif
 c         print*,'is1 ',is1  
433           do ip=1,NPLANES           do ip=1,NPLANES
434              is2 = SENSOR_STORE(ip,icand) !sensor              is2 = SENSOR_STORE(ip,icand) !sensor
 c            print*,'is2 ',is2,' ip ',ip  
435              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
436              if(              if(
437       $           (is1.ne.is2.and.is2.ne.0)       $           (is1.ne.is2.and.is2.ne.0)
438       $           )goto 122      !jump (this track cannot have an image)       $           )goto 122      !jump (this track cannot have an image)
439           enddo           enddo
440           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  
441  *     ---------------------------------------------------------------  *     ---------------------------------------------------------------
442  *     take the candidate with the greatest number of matching couples  *     take the candidate with the greatest number of matching couples
443  *     if more than one satisfies the requirement,  *     if more than one satisfies the requirement,
# Line 486  c$$$         enddo Line 469  c$$$         enddo
469                                            
470                    endif                    endif
471                 endif                 endif
 c$$$               print*,' track ',i,' CP ',CP_STORE(nplanes-ip+1,i)  
 c$$$     $              ,CP_STORE(nplanes-ip+1,icand),ncp  
472              enddo              enddo
473   117        continue   117        continue
474              trackimage(i)=ncp   !number of matching couples              trackimage(i)=ncp   !number of matching couples
# Line 501  c$$$     $              ,CP_STORE(nplane Line 482  c$$$     $              ,CP_STORE(nplane
482           do i=1,ntracks           do i=1,ntracks
483              if( ncpmax.ne.0.and.trackimage(i).eq.ncpmax )ngood=ngood+1              if( ncpmax.ne.0.and.trackimage(i).eq.ncpmax )ngood=ngood+1
484           enddo           enddo
485             if(DEBUG.eq.1)print*,' n.image-candidates : ',ngood
486  *     if there are, choose the best one  *     if there are, choose the best one
487           if(ngood.gt.1)then           if(ngood.gt.0)then
488  *     -------------------------------------------------------  *     -------------------------------------------------------
489  *     order track-candidates according to:  *     order track-candidates according to:
490  *     1st) decreasing n.points  *     1st) decreasing n.points
# Line 532  c$$$     $              ,CP_STORE(nplane Line 514  c$$$     $              ,CP_STORE(nplane
514                    endif                    endif
515                 endif                 endif
516              enddo              enddo
517    
518                if(DEBUG.EQ.1)then
519                   print*,'Track candidate ',iimage
520         $              ,' >>> TRACK IMAGE >>> of'
521         $              ,ibest
522                endif
523                            
524           endif           endif
525    
          if(DEBUG.EQ.1)print*,'Track candidate ',iimage  
      $        ,' >>> TRACK IMAGE >>> of'  
      $        ,ibest  
526    
527   122     continue   122     continue
528    
# Line 550  c$$$     $              ,CP_STORE(nplane Line 535  c$$$     $              ,CP_STORE(nplane
535       $        .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
536           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
537           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)  
538    
539           if(ntrk.eq.NTRKMAX)then           if(ntrk.eq.NTRKMAX)then
540              if(verbose.eq.1)              if(verbose.eq.1)
# Line 567  cc            good2=.false. Line 550  cc            good2=.false.
550              goto 1212           !>>> fit image-track              goto 1212           !>>> fit image-track
551           endif           endif
552    
 *     --- 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  
 *     **********************************************  
   
   
553    
554   880     return   880     return
555        end        end
# Line 688  c     $        rchi2best.lt.15..and. Line 639  c     $        rchi2best.lt.15..and.
639    
640        real stripx,stripy        real stripx,stripy
641    
642          double precision xi,yi,zi
643          double precision xi_A,yi_A,zi_A
644          double precision xi_B,yi_B,zi_B
645        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
646        double precision xrt_A,yrt_A,zrt_A        double precision xrt_A,yrt_A,zrt_A
647        double precision xrt_B,yrt_B,zrt_B        double precision xrt_B,yrt_B,zrt_B
# Line 696  c     $        rchi2best.lt.15..and. Line 650  c     $        rchi2best.lt.15..and.
650        parameter (ndivx=30)        parameter (ndivx=30)
651    
652    
 c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy  
653                
654        resxPAM = 0        resxPAM = 0
655        resyPAM = 0        resyPAM = 0
656    
657        xPAM = 0.        xPAM = 0.D0
658        yPAM = 0.        yPAM = 0.D0
659        zPAM = 0.        zPAM = 0.D0
660        xPAM_A = 0.        xPAM_A = 0.D0
661        yPAM_A = 0.        yPAM_A = 0.D0
662        zPAM_A = 0.        zPAM_A = 0.D0
663        xPAM_B = 0.        xPAM_B = 0.D0
664        yPAM_B = 0.        yPAM_B = 0.D0
665        zPAM_B = 0.        zPAM_B = 0.D0
 c      print*,'## xyz_PAM: ',icx,icy,sensor,PFAx,PFAy,angx,angy  
666    
667        if(sensor.lt.1.or.sensor.gt.2)then        if(sensor.lt.1.or.sensor.gt.2)then
668           print*,'xyz_PAM   ***ERROR*** wrong input '           print*,'xyz_PAM   ***ERROR*** wrong input '
# Line 727  c      print*,'## xyz_PAM: ',icx,icy,sen Line 679  c      print*,'## xyz_PAM: ',icx,icy,sen
679           viewx   = VIEW(icx)           viewx   = VIEW(icx)
680           nldx    = nld(MAXS(icx),VIEW(icx))           nldx    = nld(MAXS(icx),VIEW(icx))
681           nplx    = npl(VIEW(icx))           nplx    = npl(VIEW(icx))
682           resxPAM = RESXAV  c         resxPAM = RESXAV
683           stripx  = float(MAXS(icx))           stripx  = float(MAXS(icx))
684    
685           if(           if(
# Line 747  c      print*,'## xyz_PAM: ',icx,icy,sen Line 699  c      print*,'## xyz_PAM: ',icx,icy,sen
699  *        --------------------------  *        --------------------------
700  *        magnetic-field corrections  *        magnetic-field corrections
701  *        --------------------------  *        --------------------------
702           angtemp  = ax           stripx  = stripx +  fieldcorr(viewx,bfy)      
703           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)  
704                    
705             call applypfa(PFAx,icx,angx,corr,res)
706           if(PFAx.eq.'COG1')then           stripx  = stripx + corr
707             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  
708    
709   10   endif   10   endif
   
710            
711  *     -----------------  *     -----------------
712  *     CLUSTER Y  *     CLUSTER Y
# Line 876  c$$$            print*,icx,' *** ',resxP Line 717  c$$$            print*,icx,' *** ',resxP
717           viewy = VIEW(icy)           viewy = VIEW(icy)
718           nldy = nld(MAXS(icy),VIEW(icy))           nldy = nld(MAXS(icy),VIEW(icy))
719           nply = npl(VIEW(icy))           nply = npl(VIEW(icy))
720           resyPAM = RESYAV  c         resyPAM = RESYAV
721           stripy = float(MAXS(icy))           stripy = float(MAXS(icy))
722    
723           if(           if(
# Line 900  c$$$            print*,icx,' *** ',resxP Line 741  c$$$            print*,icx,' *** ',resxP
741              endif              endif
742              goto 100              goto 100
743           endif           endif
744    
745  *        --------------------------  *        --------------------------
746  *        magnetic-field corrections  *        magnetic-field corrections
747  *        --------------------------  *        --------------------------
748           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001                   stripy  = stripy +  fieldcorr(viewy,bfx)      
749           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  
 *        --------------------------  
750                    
751  c$$$         print*,'--- y-cl ---'           call applypfa(PFAy,icy,angy,corr,res)
752  c$$$         istart = INDSTART(ICY)           stripy  = stripy + corr
753  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  
   
754    
755   20   endif   20   endif
756    
 c$$$      print*,'## stripx,stripy ',stripx,stripy  
757    
758  c===========================================================  c===========================================================
759  C     COUPLE  C     COUPLE
# Line 1024  c--------------------------------------- Line 770  c---------------------------------------
770       $              ' WARNING: false X strip: strip ',stripx       $              ' WARNING: false X strip: strip ',stripx
771              endif              endif
772           endif           endif
773           xi = acoordsi(stripx,viewx)           xi = dcoordsi(stripx,viewx)
774           yi = acoordsi(stripy,viewy)           yi = dcoordsi(stripy,viewy)
775           zi = 0.           zi = 0.D0
776                    
   
777  c------------------------------------------------------------------------  c------------------------------------------------------------------------
778  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
779  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 1062  c--------------------------------------- Line 807  c---------------------------------------
807           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
808           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
809    
810           xPAM_A = 0.           xPAM_A = 0.D0
811           yPAM_A = 0.           yPAM_A = 0.D0
812           zPAM_A = 0.           zPAM_A = 0.D0
813    
814           xPAM_B = 0.           xPAM_B = 0.D0
815           yPAM_B = 0.           yPAM_B = 0.D0
816           zPAM_B = 0.           zPAM_B = 0.D0
817    
818        elseif(        elseif(
819       $        (icx.ne.0.and.icy.eq.0).or.       $        (icx.ne.0.and.icy.eq.0).or.
# Line 1088  C======================================= Line 833  C=======================================
833              nldx = nldy              nldx = nldy
834              viewx = viewy + 1              viewx = viewy + 1
835    
836              yi   = acoordsi(stripy,viewy)              xi = dcoordsi(0.5*(nstrips+1),viewx) !sensor center
837                yi = dcoordsi(stripy,viewy)
838                zi = 0.D0
839    
840              xi_A = edgeY_d - SiDimX/2              xi_A = edgeY_d - SiDimX/2
841              yi_A = yi              yi_A = yi
# Line 1098  C======================================= Line 845  C=======================================
845              yi_B = yi              yi_B = yi
846              zi_B = 0.              zi_B = 0.
847    
 c            print*,'Y-cl ',icy,stripy,' --> ',yi  
 c            print*,xi_A,' <--> ',xi_B  
848                            
849           elseif(icx.ne.0)then           elseif(icx.ne.0)then
850  c===========================================================  c===========================================================
# Line 1110  C======================================= Line 855  C=======================================
855              nldy = nldx              nldy = nldx
856              viewy = viewx - 1              viewy = viewx - 1
857    
 c            print*,'X-singlet ',icx,nplx,nldx,viewx,stripx  
 c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  
858              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
859       $           .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...
860                 if(DEBUG.EQ.1) then                 if(DEBUG.EQ.1) then
# Line 1119  c            if((stripx.le.3).or.(stripx Line 862  c            if((stripx.le.3).or.(stripx
862       $                 ' WARNING: false X strip: strip ',stripx       $                 ' WARNING: false X strip: strip ',stripx
863                 endif                 endif
864              endif              endif
865              xi   = acoordsi(stripx,viewx)  
866                xi = dcoordsi(stripx,viewx)
867                yi = dcoordsi(0.5*(nstrips+1),viewy) !sensor center
868                zi = 0.D0
869    
870              xi_A = xi              xi_A = xi
871              yi_A = edgeX_d - SiDimY/2              yi_A = edgeX_d - SiDimY/2
# Line 1135  c            if((stripx.le.3).or.(stripx Line 881  c            if((stripx.le.3).or.(stripx
881                 yi_B = yi                 yi_B = yi
882              endif              endif
883    
 c            print*,'X-cl ',icx,stripx,' --> ',xi  
 c            print*,yi_A,' <--> ',yi_B  
884    
885           else           else
886              if(DEBUG.EQ.1) then              if(DEBUG.EQ.1) then
# Line 1182  c     N.B. I convert angles from microra Line 926  c     N.B. I convert angles from microra
926       $        + zi_B       $        + zi_B
927       $        + dz(nplx,nldx,sensor)       $        + dz(nplx,nldx,sensor)
928    
929    
930    
931             xrt = xi
932         $        - omega(nplx,nldx,sensor)*yi
933         $        + gamma(nplx,nldx,sensor)*zi
934         $        + dx(nplx,nldx,sensor)
935            
936             yrt = omega(nplx,nldx,sensor)*xi
937         $        + yi
938         $        - beta(nplx,nldx,sensor)*zi
939         $        + dy(nplx,nldx,sensor)
940            
941             zrt = -gamma(nplx,nldx,sensor)*xi
942         $        + beta(nplx,nldx,sensor)*yi
943         $        + zi
944         $        + dz(nplx,nldx,sensor)
945    
946    
947                    
948  c      xrt = xi  c      xrt = xi
949  c      yrt = yi  c      yrt = yi
# Line 1192  c     (xPAM,yPAM,zPAM) = measured coordi Line 954  c     (xPAM,yPAM,zPAM) = measured coordi
954  c                        in PAMELA reference system  c                        in PAMELA reference system
955  c------------------------------------------------------------------------  c------------------------------------------------------------------------
956    
957           xPAM = 0.           xPAM = dcoord(xrt,viewx,nldx,sensor) / 1.d4
958           yPAM = 0.           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
959           zPAM = 0.           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
960    c$$$         xPAM = 0.D0
961    c$$$         yPAM = 0.D0
962    c$$$         zPAM = 0.D0
963    
964           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4
965           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4
# Line 1205  c--------------------------------------- Line 970  c---------------------------------------
970           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
971                    
972    
 c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'  
973    
974        else        else
975           if(DEBUG.EQ.1) then           if(DEBUG.EQ.1) then
# Line 1216  c         print*,'A-(',xPAM_A,yPAM_A,') Line 980  c         print*,'A-(',xPAM_A,yPAM_A,')
980        endif        endif
981                    
982    
 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  
983    
984   100  continue   100  continue
985        end        end
# Line 1256  c$$$      PFAy = 'COG4'!PFA Line 1017  c$$$      PFAy = 'COG4'!PFA
1017    
1018        if(icx.gt.nclstr1.or.icy.gt.nclstr1)then        if(icx.gt.nclstr1.or.icy.gt.nclstr1)then
1019              print*,'xyzpam: ***WARNING*** clusters ',icx,icy              print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1020       $           ,' does not exists (nclstr1=',nclstr1,')'       $           ,' do not exists (n.clusters=',nclstr1,')'
1021              icx = -1*icx              icx = -1*icx
1022              icy = -1*icy              icy = -1*icy
1023              return              return
# Line 1266  c$$$      PFAy = 'COG4'!PFA Line 1027  c$$$      PFAy = 'COG4'!PFA
1027        call idtoc(pfaid,PFAx)        call idtoc(pfaid,PFAx)
1028        call idtoc(pfaid,PFAy)        call idtoc(pfaid,PFAy)
1029    
 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  
1030                
1031        if(icx.ne.0.and.icy.ne.0)then        if(icx.ne.0.and.icy.ne.0)then
1032    
1033           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
1034           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  
1035                    
1036           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1037              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster ',icx
# Line 1303  c$$$     $        ,' does not belong to Line 1056  c$$$     $        ,' does not belong to
1056           xm(ip) = xPAM           xm(ip) = xPAM
1057           ym(ip) = yPAM           ym(ip) = yPAM
1058           zm(ip) = zPAM           zm(ip) = zPAM
1059           xm_A(ip) = 0.           xm_A(ip) = 0.D0
1060           ym_A(ip) = 0.           ym_A(ip) = 0.D0
1061           xm_B(ip) = 0.           xm_B(ip) = 0.D0
1062           ym_B(ip) = 0.           ym_B(ip) = 0.D0
1063    
1064  c         zv(ip) = zPAM  c         zv(ip) = zPAM
1065    
1066        elseif(icx.eq.0.and.icy.ne.0)then        elseif(icx.eq.0.and.icy.ne.0)then
1067    
1068           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  
1069           if( (nplanes-ipy+1).ne.ip )then           if( (nplanes-ipy+1).ne.ip )then
1070              print*,'xyzpam: ***WARNING*** cluster ',icy              print*,'xyzpam: ***WARNING*** cluster ',icy
1071       $           ,' does not belong to plane: ',ip       $           ,' does not belong to plane: ',ip
# Line 1330  c$$$     $        ,' does not belong to Line 1080  c$$$     $        ,' does not belong to
1080           resx(ip)  = 1000.           resx(ip)  = 1000.
1081           resy(ip)  = resyPAM           resy(ip)  = resyPAM
1082    
1083           xm(ip) = -100.  c$$$         xm(ip) = -100.
1084           ym(ip) = -100.  c$$$         ym(ip) = -100.
1085           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1086             xm(ip) = xPAM
1087             ym(ip) = yPAM
1088             zm(ip) = zPAM
1089           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1090           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1091           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1343  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1096  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1096        elseif(icx.ne.0.and.icy.eq.0)then        elseif(icx.ne.0.and.icy.eq.0)then
1097    
1098           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  
1099    
1100           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1101              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster ',icx
# Line 1361  c$$$     $        ,' does not belong to Line 1111  c$$$     $        ,' does not belong to
1111           resx(ip)  = resxPAM           resx(ip)  = resxPAM
1112           resy(ip)  = 1000.           resy(ip)  = 1000.
1113    
1114           xm(ip) = -100.  c$$$         xm(ip) = -100.
1115           ym(ip) = -100.  c$$$         ym(ip) = -100.
1116           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1117             xm(ip) = xPAM
1118             ym(ip) = yPAM
1119             zm(ip) = zPAM
1120           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1121           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1122           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1377  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1130  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1130           if(lad.ne.0)il=lad           if(lad.ne.0)il=lad
1131           is = 1           is = 1
1132           if(sensor.ne.0)is=sensor           if(sensor.ne.0)is=sensor
 c         print*,nplanes-ip+1,il,is  
1133    
1134           xgood(ip) = 0.           xgood(ip) = 0.
1135           ygood(ip) = 0.           ygood(ip) = 0.
# Line 1397  c         zv(ip) = z_mech_sensor(nplanes Line 1149  c         zv(ip) = z_mech_sensor(nplanes
1149        endif        endif
1150    
1151        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
 c         print*,'----------------------------- track coord'  
1152  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1153           write(*,22222)ip,zm(ip),xm(ip),ym(ip)           write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1154       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1155       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)
 c$$$         print*,'-----------------------------'  
1156        endif        endif
1157        end        end
1158    
# Line 1426  c$$$         print*,'------------------- Line 1176  c$$$         print*,'-------------------
1176  *      *    
1177  ********************************************************************************  ********************************************************************************
1178    
1179        real function distance_to(XPP,YPP)        real function distance_to(rXPP,rYPP)
1180    
1181        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
1182    
# Line 1435  c$$$         print*,'------------------- Line 1185  c$$$         print*,'-------------------
1185  *     ( i.e. distance/resolution )  *     ( i.e. distance/resolution )
1186  *     -----------------------------------  *     -----------------------------------
1187    
1188          real rXPP,rYPP
1189          double precision XPP,YPP
1190        double precision distance,RE        double precision distance,RE
1191        double precision BETA,ALFA,xmi,ymi        double precision BETA,ALFA,xmi,ymi
1192    
1193          XPP=DBLE(rXPP)
1194          YPP=DBLE(rYPP)
1195    
1196  *     ----------------------  *     ----------------------
1197        if (        if (
1198       +     xPAM.eq.0.and.  c$$$     +     xPAM.eq.0.and.
1199       +     yPAM.eq.0.and.  c$$$     +     yPAM.eq.0.and.
1200       +     zPAM.eq.0.and.  c$$$     +     zPAM.eq.0.and.
1201       +     xPAM_A.ne.0.and.       +     xPAM_A.ne.0.and.
1202       +     yPAM_A.ne.0.and.       +     yPAM_A.ne.0.and.
1203       +     zPAM_A.ne.0.and.       +     zPAM_A.ne.0.and.
# Line 1484  c$$$         print*,'------------------- Line 1239  c$$$         print*,'-------------------
1239  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1240           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1241    
 c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',re  
1242    
1243                    
1244  *     ----------------------  *     ----------------------
1245        elseif(        elseif(
1246       +     xPAM.ne.0.and.  c$$$     +     xPAM.ne.0.and.
1247       +     yPAM.ne.0.and.  c$$$     +     yPAM.ne.0.and.
1248       +     zPAM.ne.0.and.  c$$$     +     zPAM.ne.0.and.
1249       +     xPAM_A.eq.0.and.       +     xPAM_A.eq.0.and.
1250       +     yPAM_A.eq.0.and.       +     yPAM_A.eq.0.and.
1251       +     zPAM_A.eq.0.and.       +     zPAM_A.eq.0.and.
# Line 1514  c$$$     $        + Line 1266  c$$$     $        +
1266  c$$$     $        ((yPAM-YPP)/resyPAM)**2  c$$$     $        ((yPAM-YPP)/resyPAM)**2
1267           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1268    
 c$$$         print*,xPAM,yPAM,zPAM  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',resxPAM,resyPAM  
1269                    
1270        else        else
1271                    
 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  
1272        endif          endif  
1273    
1274        distance_to = sngl(distance)        distance_to = sngl(distance)
# Line 1564  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1308  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1308        data c1/1.,0.,0.,1./        data c1/1.,0.,0.,1./
1309        data c2/1.,-1.,-1.,1./        data c2/1.,-1.,-1.,1./
1310        data c3/1.,1.,0.,0./        data c3/1.,1.,0.,0./
1311        real*8 yvvv,xvvv        double precision yvvv,xvvv
1312        double precision xi,yi,zi        double precision xi,yi,zi
1313        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
1314        real AA,BB        real AA,BB
1315        real yvv(4),xvv(4)        double precision yvv(4),xvv(4)
1316    
1317  *     tollerance to consider the track inside the sensitive area  *     tollerance to consider the track inside the sensitive area
1318        real ptoll        real ptoll
1319        data ptoll/150./          !um        data ptoll/150./          !um
1320    
1321        external nviewx,nviewy,acoordsi,dcoord        external nviewx,nviewy,dcoordsi,dcoord
1322    
1323        nplpt = nplPAM            !plane        nplpt = nplPAM            !plane
1324        viewx = nviewx(nplpt)        viewx = nviewx(nplpt)
# Line 1589  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1333  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1333  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1334  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1335  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1336                 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)                 xi = dcoordsi(stripx,viewx)
1337       $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...                 yi = dcoordsi(stripy,viewy)
1338  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.  
1339  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1340  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
1341  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 1622  c--------------------------------------- Line 1360  c---------------------------------------
1360    
1361                 yvv(iv)=sngl(yvvv)                 yvv(iv)=sngl(yvvv)
1362                 xvv(iv)=sngl(xvvv)                 xvv(iv)=sngl(xvvv)
 c               print*,'LADDER ',il,' SENSOR ',is,' vertexes >> '  
 c     $              ,iv,xvv(iv),yvv(iv)  
1363              enddo               !end loop on sensor vertexes              enddo               !end loop on sensor vertexes
1364    
1365              dtot=0.              dtot=0.
# Line 1748  c      include 'common_analysis.f' Line 1484  c      include 'common_analysis.f'
1484        is_cp=0        is_cp=0
1485        if(id.lt.0)is_cp=1        if(id.lt.0)is_cp=1
1486        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 !!!'  
1487    
1488        return        return
1489        end        end
# Line 1847  c      include 'level1.f' Line 1582  c      include 'level1.f'
1582        integer iflag        integer iflag
1583    
1584        integer badseed,badclx,badcly        integer badseed,badclx,badcly
1585        
1586          iflag = iflag
1587        if(DEBUG.EQ.1)print*,'cl_to_couples:'        if(DEBUG.EQ.1)print*,'cl_to_couples:'
1588    
1589    cc      if(RECOVER_SINGLETS.and..not.SECOND_SEARCH)goto 80
1590    
1591  *     init variables  *     init variables
       ncp_tot=0  
1592        do ip=1,nplanes        do ip=1,nplanes
1593           do ico=1,ncouplemax           do ico=1,ncouplemax
1594              clx(ip,ico)=0              clx(ip,ico)=0
# Line 1864  c      include 'level1.f' Line 1601  c      include 'level1.f'
1601           ncls(ip)=0           ncls(ip)=0
1602        enddo        enddo
1603        do icl=1,nclstrmax_level2        do icl=1,nclstrmax_level2
1604           cl_single(icl) = 1           cl_single(icl) = 1     !all are single
1605           cl_good(icl)   = 0           cl_good(icl)   = 0     !all are bad
1606        enddo        enddo
1607        do iv=1,nviews        do iv=1,nviews
1608           ncl_view(iv)  = 0           ncl_view(iv)  = 0
# Line 1893  c            mask_view(iv) = 1 Line 1630  c            mask_view(iv) = 1
1630        do icx=1,nclstr1          !loop on cluster (X)        do icx=1,nclstr1          !loop on cluster (X)
1631           if(mod(VIEW(icx),2).eq.1)goto 10           if(mod(VIEW(icx),2).eq.1)goto 10
1632                    
1633             if(cl_used(icx).ne.0)goto 10
1634    
1635  *     ----------------------------------------------------  *     ----------------------------------------------------
1636  *     jump masked views (X VIEW)  *     jump masked views (X VIEW)
1637  *     ----------------------------------------------------  *     ----------------------------------------------------
# Line 1900  c            mask_view(iv) = 1 Line 1639  c            mask_view(iv) = 1
1639  *     ----------------------------------------------------  *     ----------------------------------------------------
1640  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1641  *     ----------------------------------------------------  *     ----------------------------------------------------
1642           if(sgnl(icx).lt.dedx_x_min)then           if(sgnl(icx)/mip(VIEW(icx),LADDER(icx)).lt.dedx_x_min)then
1643              cl_single(icx)=0              cl_single(icx)=0
1644              goto 10              goto 10
1645           endif           endif
# Line 1941  c     endif Line 1680  c     endif
1680                    
1681           do icy=1,nclstr1       !loop on cluster (Y)           do icy=1,nclstr1       !loop on cluster (Y)
1682              if(mod(VIEW(icy),2).eq.0)goto 20              if(mod(VIEW(icy),2).eq.0)goto 20
1683    
1684                if(cl_used(icx).ne.0)goto 20
1685                            
1686  *     ----------------------------------------------------  *     ----------------------------------------------------
1687  *     jump masked views (Y VIEW)  *     jump masked views (Y VIEW)
# Line 1950  c     endif Line 1691  c     endif
1691  *     ----------------------------------------------------  *     ----------------------------------------------------
1692  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1693  *     ----------------------------------------------------  *     ----------------------------------------------------
1694              if(sgnl(icy).lt.dedx_y_min)then              if(sgnl(icy)/mip(VIEW(icy),LADDER(icy)) .lt.dedx_y_min)then
1695                 cl_single(icy)=0                 cl_single(icy)=0
1696                 goto 20                 goto 20
1697              endif              endif
# Line 2028  c                  cut = chcut * sch(npl Line 1769  c                  cut = chcut * sch(npl
1769       $                 ,'( ',ncouplemax,' ) --> masked!'       $                 ,'( ',ncouplemax,' ) --> masked!'
1770  c                  mask_view(nviewx(nplx)) = 2  c                  mask_view(nviewx(nplx)) = 2
1771  c                  mask_view(nviewy(nply)) = 2  c                  mask_view(nviewy(nply)) = 2
1772                    mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1                   mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1
1773                    mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1                   mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1
1774                    goto 10                    goto 10
1775                 endif                 endif
1776                                
# Line 2049  c                  mask_view(nviewy(nply Line 1790  c                  mask_view(nviewy(nply
1790   10      continue   10      continue
1791        enddo                     !end loop on clusters(X)        enddo                     !end loop on clusters(X)
1792                
         
1793        do icl=1,nclstr1        do icl=1,nclstr1
1794           if(cl_single(icl).eq.1)then           if(cl_single(icl).eq.1)then
1795              ip=npl(VIEW(icl))              ip=npl(VIEW(icl))
# Line 2057  c                  mask_view(nviewy(nply Line 1797  c                  mask_view(nviewy(nply
1797              cls(ip,ncls(ip))=icl              cls(ip,ncls(ip))=icl
1798           endif           endif
1799        enddo        enddo
1800    
1801    c 80   continue
1802          continue
1803                
1804                
1805        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
1806           print*,'clusters  ',nclstr1           print*,'clusters  ',nclstr1
1807           print*,'good    ',(cl_good(i),i=1,nclstr1)           print*,'good    ',(cl_good(i),i=1,nclstr1)
1808             print*,'used    ',(cl_used(i),i=1,nclstr1)
1809           print*,'singlets',(cl_single(i),i=1,nclstr1)           print*,'singlets',(cl_single(i),i=1,nclstr1)
1810           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1811        endif        endif
1812    
1813      
1814          if(.not.RECOVER_SINGLETS)goto 81
1815    
1816    *     ////////////////////////////////////////////////
1817    *     PATCH to recover events with less than 3 couples
1818    *     ////////////////////////////////////////////////    
1819    *     loop over singlet and create "fake" couples
1820    *     (with clx=0 or cly=0)
1821    *    
1822    
1823          if(DEBUG.EQ.1)
1824         $     print*,'>>> Recover singlets '
1825         $     ,'(creates fake couples) <<<'
1826          do icl=1,nclstr1
1827             if(
1828         $        cl_single(icl).eq.1.and.
1829         $        cl_used(icl).eq.0.and.
1830         $        .true.)then
1831    *     ----------------------------------------------------
1832    *     jump masked views
1833    *     ----------------------------------------------------
1834                if( mask_view(VIEW(icl)).ne.0 ) goto 21
1835                if(mod(VIEW(icl),2).eq.0)then !=== X views
1836    *     ----------------------------------------------------
1837    *     cut on charge (X VIEW)
1838    *     ----------------------------------------------------
1839                   if(sgnl(icl).lt.dedx_x_min) goto 21
1840                  
1841                   nplx=npl(VIEW(icl))
1842    *     ------------------> (FAKE) COUPLE <-----------------
1843                   ncp_plane(nplx) = ncp_plane(nplx) + 1
1844                   clx(nplx,ncp_plane(nplx))=icl
1845                   cly(nplx,ncp_plane(nplx))=0
1846    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1847    *     ----------------------------------------------------
1848                  
1849                else                !=== Y views
1850    *     ----------------------------------------------------
1851    *     cut on charge (Y VIEW)
1852    *     ----------------------------------------------------
1853                   if(sgnl(icl).lt.dedx_y_min) goto 21
1854                  
1855                   nply=npl(VIEW(icl))
1856    *     ------------------> (FAKE) COUPLE <-----------------
1857                   ncp_plane(nply) = ncp_plane(nply) + 1
1858                   clx(nply,ncp_plane(nply))=0
1859                   cly(nply,ncp_plane(nply))=icl
1860    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1861    *     ----------------------------------------------------
1862                  
1863                endif
1864             endif                  !end "single" condition
1865     21      continue
1866          enddo                     !end loop over clusters
1867    
1868          if(DEBUG.EQ.1)
1869         $     print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1870    
1871    
1872     81   continue
1873                
1874        do ip=1,6        ncp_tot=0
1875          do ip=1,NPLANES
1876           ncp_tot = ncp_tot + ncp_plane(ip)           ncp_tot = ncp_tot + ncp_plane(ip)
1877        enddo        enddo
1878          if(DEBUG.EQ.1)
1879         $     print*,'n.couple tot:      ',ncp_tot
1880                
1881        return        return
1882        end        end
# Line 2131  c      double precision xm3,ym3,zm3 Line 1939  c      double precision xm3,ym3,zm3
1939  *     --------------------------------------------  *     --------------------------------------------
1940        do ip=1,nplanes        do ip=1,nplanes
1941           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  
1942              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7
1943              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7
1944           endif           endif
# Line 2143  c            mask_view(nviewy(ip)) = 8 Line 1949  c            mask_view(nviewy(ip)) = 8
1949        ntrpt=0                   !number of triplets        ntrpt=0                   !number of triplets
1950                
1951        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1
1952    c$$$         print*,'(1) ip ',ip1
1953    c$$$     $        ,mask_view(nviewx(ip1))
1954    c$$$     $        ,mask_view(nviewy(ip1))        
1955           if(  mask_view(nviewx(ip1)).ne.0 .or.           if(  mask_view(nviewx(ip1)).ne.0 .or.
1956       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
1957           do is1=1,2             !loop on sensors - COPPIA 1                       do is1=1,2             !loop on sensors - COPPIA 1            
1958              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
1959                 icx1=clx(ip1,icp1)                 icx1=clx(ip1,icp1)
1960                 icy1=cly(ip1,icp1)                 icy1=cly(ip1,icp1)
1961                  
1962    c$$$               print*,'(1) ip ',ip1,' icp ',icp1
1963    
1964  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
1965  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
1966                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
1967                 xm1=xPAM                 xm1=xPAM
1968                 ym1=yPAM                 ym1=yPAM
1969                 zm1=zPAM                                   zm1=zPAM                  
 c     print*,'***',is1,xm1,ym1,zm1  
1970    
1971                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
1972    c$$$                  print*,'(2) ip ',ip2
1973    c$$$     $                 ,mask_view(nviewx(ip2))
1974    c$$$     $                 ,mask_view(nviewy(ip2))
1975                    if(  mask_view(nviewx(ip2)).ne.0 .or.                    if(  mask_view(nviewx(ip2)).ne.0 .or.
1976       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
1977                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                                        do is2=1,2    !loop on sensors -ndblt COPPIA 2                    
1978                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
1979                          icx2=clx(ip2,icp2)                          icx2=clx(ip2,icp2)
1980                          icy2=cly(ip2,icp2)                          icy2=cly(ip2,icp2)
1981    
1982    c$$$                        print*,'(2) ip ',ip2,' icp ',icp2
1983    
1984  c                        call xyz_PAM  c                        call xyz_PAM
1985  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
1986  c                        call xyz_PAM  c                        call xyz_PAM
# Line 2173  c     $                       (icx2,icy2 Line 1990  c     $                       (icx2,icy2
1990                          xm2=xPAM                          xm2=xPAM
1991                          ym2=yPAM                          ym2=yPAM
1992                          zm2=zPAM                          zm2=zPAM
1993                                                    
1994    *                       ---------------------------------------------------
1995    *                       both couples must have a y-cluster
1996    *                       (condition necessary when in RECOVER_SINGLETS mode)
1997    *                       ---------------------------------------------------
1998                            if(icy1.eq.0.or.icy2.eq.0)goto 111
1999    
2000                            if(cl_used(icy1).ne.0)goto 111
2001                            if(cl_used(icy2).ne.0)goto 111
2002    
2003                            
2004  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2005  *     track parameters on Y VIEW  *     track parameters on Y VIEW
2006  *     (2 couples needed)  *     (2 couples needed)
# Line 2183  c     $                       (icx2,icy2 Line 2010  c     $                       (icx2,icy2
2010       $                          '** warning ** number of identified '//       $                          '** warning ** number of identified '//
2011       $                          'doublets exceeds vector dimention '       $                          'doublets exceeds vector dimention '
2012       $                          ,'( ',ndblt_max,' )'       $                          ,'( ',ndblt_max,' )'
2013  c                           good2=.false.  c     good2=.false.
2014  c                           goto 880 !fill ntp and go to next event  c     goto 880 !fill ntp and go to next event
2015                             do iv=1,12                             do iv=1,12
2016  c                              mask_view(iv) = 3  c     mask_view(iv) = 3
2017                                mask_view(iv) = mask_view(iv)+ 2**2                                mask_view(iv) = mask_view(iv)+ 2**2
2018                             enddo                             enddo
2019                             iflag=1                             iflag=1
2020                             return                             return
2021                          endif                          endif
2022                            
2023                            
2024    ccc                        print*,'<doublet> ',icp1,icp2
2025    
2026                          ndblt = ndblt + 1                          ndblt = ndblt + 1
2027  *     store doublet info  *     store doublet info
2028                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)
# Line 2200  c                              mask_view Line 2031  c                              mask_view
2031                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)
2032  *     y0 (cm)  *     y0 (cm)
2033                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1
2034                                                      
2035  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2036  ****  reject non phisical couples                    ****  ****  reject non phisical couples                    ****
2037  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2038                            if(SECOND_SEARCH)goto 111
2039                          if(                          if(
2040       $                       abs(alfayz2(ndblt)).gt.alfyz2_max       $                       abs(alfayz2(ndblt)).gt.alfyz2_max
2041       $                       .or.       $                       .or.
2042       $                       abs(alfayz1(ndblt)).gt.alfyz1_max       $                       abs(alfayz1(ndblt)).gt.alfyz1_max
2043       $                       )ndblt = ndblt-1       $                       )ndblt = ndblt-1
2044                                                    
2045  c$$$      if(iev.eq.33)then                          
2046  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$$$  
2047  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2048  *     track parameters on Y VIEW - end  *     track parameters on Y VIEW - end
2049  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2050    
2051    
2052                            if(icx1.ne.0)then
2053                               if(cl_used(icx1).ne.0)goto 31
2054                            endif
2055                            if(icx2.ne.0)then
2056                               if(cl_used(icx2).ne.0)goto 31
2057                            endif
2058    
2059                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2060    
2061                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2062    c$$$                           print*,'(3) ip ',ip3
2063    c$$$     $                          ,mask_view(nviewx(ip3))
2064    c$$$     $                          ,mask_view(nviewy(ip3))                          
2065                             if(  mask_view(nviewx(ip3)).ne.0 .or.                             if(  mask_view(nviewx(ip3)).ne.0 .or.
2066       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2067                             do is3=1,2 !loop on sensors - COPPIA 3                             do is3=1,2 !loop on sensors - COPPIA 3
# Line 2232  c$$$ Line 2069  c$$$
2069                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
2070                                   icx3=clx(ip3,icp3)                                   icx3=clx(ip3,icp3)
2071                                   icy3=cly(ip3,icp3)                                   icy3=cly(ip3,icp3)
2072    
2073    c$$$                                 print*,'(3) ip ',ip3,' icp ',icp3
2074    
2075    *     ---------------------------------------------------
2076    *     all three couples must have a x-cluster
2077    *     (condition necessary when in RECOVER_SINGLETS mode)
2078    *     ---------------------------------------------------
2079                                     if(
2080         $                                icx1.eq.0.or.
2081         $                                icx2.eq.0.or.
2082         $                                icx3.eq.0.or.
2083         $                                .false.)goto 29
2084                                    
2085                                     if(cl_used(icx1).ne.0)goto 29
2086                                     if(cl_used(icx2).ne.0)goto 29
2087                                     if(cl_used(icx3).ne.0)goto 29
2088    
2089  c                                 call xyz_PAM  c                                 call xyz_PAM
2090  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2091  c                                 call xyz_PAM  c                                 call xyz_PAM
# Line 2242  c     $                               (i Line 2096  c     $                               (i
2096                                   xm3=xPAM                                   xm3=xPAM
2097                                   ym3=yPAM                                   ym3=yPAM
2098                                   zm3=zPAM                                   zm3=zPAM
2099    
2100    
2101  *     find the circle passing through the three points  *     find the circle passing through the three points
2102                                     iflag_t = DEBUG
2103                                   call tricircle(3,xp,zp,angp,resp,chi                                   call tricircle(3,xp,zp,angp,resp,chi
2104       $                                ,xc,zc,radius,iflag)       $                                ,xc,zc,radius,iflag_t)
 c     print*,xc,zc,radius  
2105  *     the circle must intersect the reference plane  *     the circle must intersect the reference plane
2106                                   if(  cc                                 if(iflag.ne.0)goto 29
2107  c     $                                 (xc.le.-1.*xclimit.or.                                   if(iflag_t.ne.0)then
2108  c     $                                 xc.ge.xclimit).and.  *     if tricircle fails, evaluate a straight line
2109       $                                radius**2.ge.(ZINI-zc)**2.and.                                      if(DEBUG.eq.1)
2110       $                                iflag.eq.0.and.       $                                   print*,'TRICIRCLE failure'
2111       $                                .true.)then       $                                   ,' >>> straight line'
2112                                                                        radius=0.
2113                                        xc=0.
2114                                        yc=0.
2115                                        
2116                                        SZZ=0.                  
2117                                        SZX=0.
2118                                        SSX=0.
2119                                        SZ=0.
2120                                        S1=0.
2121                                        X0=0.
2122                                        Ax=0.
2123                                        BX=0.
2124                                        DO I=1,3
2125                                           XX = XP(I)
2126                                           SZZ=SZZ+ZP(I)*ZP(I)
2127                                           SZX=SZX+ZP(I)*XX
2128                                           SSX=SSX+XX
2129                                           SZ=SZ+ZP(I)
2130                                           S1=S1+1.
2131                                        ENDDO
2132                                        DET=SZZ*S1-SZ*SZ
2133                                        AX=(SZX*S1-SZ*SSX)/DET
2134                                        BX=(SZZ*SSX-SZX*SZ)/DET
2135                                        X0  = AX*ZINI+BX
2136                                        
2137                                     endif
2138    
2139                                     if(  .not.SECOND_SEARCH.and.
2140         $                                radius**2.lt.(ZINI-zc)**2)goto 29
2141                                                                      
2142  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2143  *     track parameters on X VIEW  *     track parameters on X VIEW
2144  *     (3 couples needed)  *     (3 couples needed)
2145  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2146                                   if(ntrpt.eq.ntrpt_max)then                                   if(ntrpt.eq.ntrpt_max)then
2147                                      if(verbose.eq.1)print*,                                      if(verbose.eq.1)print*,
2148       $                     '** warning ** number of identified '//       $                                   '** warning **'//
2149       $                     'triplets exceeds vector dimention '       $                                   ' number of identified '//
2150       $                    ,'( ',ntrpt_max,' )'       $                                   'triplets exceeds'//
2151  c                                    good2=.false.       $                                   ' vector dimention '
2152  c                                    goto 880 !fill ntp and go to next event       $                                   ,'( ',ntrpt_max,' )'
2153    c     good2=.false.
2154    c     goto 880 !fill ntp and go to next event
2155                                      do iv=1,nviews                                      do iv=1,nviews
2156  c                                       mask_view(iv) = 4  c     mask_view(iv) = 4
2157                                         mask_view(iv)=mask_view(iv)+ 2**3                                         mask_view(iv) =
2158         $                                      mask_view(iv)+ 2**3
2159                                      enddo                                      enddo
2160                                      iflag=1                                      iflag=1
2161                                      return                                      return
2162                                   endif                                   endif
2163    
2164    ccc                                 print*,'<triplet> ',icp1,icp2,icp3
2165                                    
2166                                   ntrpt = ntrpt +1                                   ntrpt = ntrpt +1
2167  *     store triplet info  *     store triplet info
2168                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)
2169                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)
2170                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)
2171                                                                    
2172                                   if(xc.lt.0)then                                   if(radius.ne.0.and.xc.lt.0)then
2173  *************POSITIVE DEFLECTION  *************POSITIVE DEFLECTION
2174                alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)
2175                alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2176                alfaxz3(ntrpt) = 1/radius               alfaxz3(ntrpt) = 1/radius
2177                                   else                                  else if(radius.ne.0.and.xc.ge.0)then
2178  *************NEGATIVE DEFLECTION  *************NEGATIVE DEFLECTION
2179                alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)
2180                alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2181                alfaxz3(ntrpt) = -1/radius               alfaxz3(ntrpt) = -1/radius
2182                                   endif                                  else if(radius.eq.0)then
2183                                    *************straight fit
2184                 alfaxz1(ntrpt) = X0
2185                 alfaxz2(ntrpt) = AX
2186                 alfaxz3(ntrpt) = 0.
2187                                    endif
2188    
2189    c$$$                                print*,'alfaxz1 ', alfaxz1(ntrpt)
2190    c$$$                                print*,'alfaxz2 ', alfaxz2(ntrpt)
2191    c$$$                                print*,'alfaxz3 ', alfaxz3(ntrpt)
2192                                        
2193  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2194  ****  reject non phisical triplets                   ****  ****  reject non phisical triplets                   ****
2195  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2196                                   if(                                  if(SECOND_SEARCH)goto 29
2197       $                                abs(alfaxz2(ntrpt)).gt.alfxz2_max                                  if(
2198       $                                .or.       $                               abs(alfaxz2(ntrpt)).gt.
2199       $                                abs(alfaxz1(ntrpt)).gt.alfxz1_max       $                               alfxz2_max
2200       $                                )ntrpt = ntrpt-1       $                               .or.
2201                                         $                               abs(alfaxz1(ntrpt)).gt.
2202                                         $                               alfxz1_max
2203  c     print*,alfaxz1(ntrpt),alfaxz2(ntrpt),alfaxz3(ntrpt)       $                               )ntrpt = ntrpt-1
2204                                                                    
2205  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2206  *     track parameters on X VIEW - end  *     track parameters on X VIEW - end
2207  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2208                                endif                                
2209     29                           continue
2210                             enddo !end loop on COPPIA 3                             enddo !end loop on COPPIA 3
2211                          enddo   !end loop on sensors - COPPIA 3                          enddo   !end loop on sensors - COPPIA 3
2212   30                     continue   30                     continue
2213                       enddo      !end loop on planes  - COPPIA 3                       enddo      !end loop on planes  - COPPIA 3
2214   31                  continue  
2215                         31                  continue                    
2216   1                enddo         !end loop on COPPIA 2  c 1                enddo         !end loop on COPPIA 2
2217                     enddo         !end loop on COPPIA 2
2218                 enddo            !end loop on sensors - COPPIA 2                 enddo            !end loop on sensors - COPPIA 2
2219   20            continue   20            continue
2220              enddo               !end loop on planes  - COPPIA 2              enddo               !end loop on planes  - COPPIA 2
2221                
2222    c 11         continue
2223              continue
2224           enddo                  !end loop on COPPIA1           enddo                  !end loop on COPPIA1
2225        enddo                     !end loop on sensors - COPPIA 1        enddo                     !end loop on sensors - COPPIA 1
2226   10   continue   10   continue
# Line 2387  c      include 'momanhough_init.f' Line 2292  c      include 'momanhough_init.f'
2292        do idb1=1,ndblt           !loop (1) on DOUBLETS        do idb1=1,ndblt           !loop (1) on DOUBLETS
2293           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
2294                            
 c     print*,'--------------'  
 c     print*,'** ',idb1,' **'  
               
2295           do icp=1,ncp_tot           do icp=1,ncp_tot
2296              cp_useds1(icp)=0    !init              cp_useds1(icp)=0    !init
2297              cp_useds2(icp)=0    !init              cp_useds2(icp)=0    !init
# Line 2425  ccccc if(db_used(idbref).eq.1)goto 1188 Line 2327  ccccc if(db_used(idbref).eq.1)goto 1188
2327  *     doublet distance in parameter space  *     doublet distance in parameter space
2328                 distance=                 distance=
2329       $              ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2       $              ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2
2330       $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2                     $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2
2331                 distance = sqrt(distance)                 distance = sqrt(distance)
2332                                
 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  
2333                 if(distance.lt.cutdistyz)then                 if(distance.lt.cutdistyz)then
2334    
 c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  
2335                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1
2336                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1
2337                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1
# Line 2453  c     print*,idb1,idb2,distance,' cloud Line 2347  c     print*,idb1,idb2,distance,' cloud
2347    
2348                    temp1 = temp1 + alfayz1(idb2)                    temp1 = temp1 + alfayz1(idb2)
2349                    temp2 = temp2 + alfayz2(idb2)                    temp2 = temp2 + alfayz2(idb2)
 c     print*,'*   idbref,idb2 ',idbref,idb2  
2350                 endif                               endif              
2351                                
2352   1118          continue   1118          continue
2353              enddo               !end loop (2) on DOUBLETS              enddo               !end loop (2) on DOUBLETS
2354                            
2355   1188       continue  c 1188       continue
2356                continue
2357           enddo                  !end loop on... bo?           enddo                  !end loop on... bo?
2358                    
2359           nptloop=npv           nptloop=npv
# Line 2476  c     print*,'*   idbref,idb2 ',idbref,i Line 2370  c     print*,'*   idbref,idb2 ',idbref,i
2370           enddo           enddo
2371           ncpused=0           ncpused=0
2372           do icp=1,ncp_tot           do icp=1,ncp_tot
2373              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2374         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2375         $           .true.)then
2376                 ncpused=ncpused+1                 ncpused=ncpused+1
2377                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2378                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2486  c     print*,'*   idbref,idb2 ',idbref,i Line 2382  c     print*,'*   idbref,idb2 ',idbref,i
2382           do ip=1,nplanes           do ip=1,nplanes
2383              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2384           enddo           enddo
2385  c     print*,'>>>> ',ncpused,npt,nplused          
 c         if(ncpused.lt.ncpyz_min)goto 2228 !next doublet  
          if(npt.lt.nptyz_min)goto 2228 !next doublet  
2386           if(nplused.lt.nplyz_min)goto 2228 !next doublet           if(nplused.lt.nplyz_min)goto 2228 !next doublet
2387                    
2388  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2520  c               mask_view(iv) = 5 Line 2414  c               mask_view(iv) = 5
2414  c     ptcloud_yz_nt(nclouds_yz)=npt  c     ptcloud_yz_nt(nclouds_yz)=npt
2415           do ipt=1,npt           do ipt=1,npt
2416              db_cloud(npt_tot+ipt) = db_all(ipt)              db_cloud(npt_tot+ipt) = db_all(ipt)
 c     print*,'>> ',ipt,db_all(ipt)  
2417           enddo             enddo  
2418           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2419           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2420              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2421              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)
2422              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)
# Line 2533  c     print*,'>> ',ipt,db_all(ipt) Line 2425  c     print*,'>> ',ipt,db_all(ipt)
2425              print*,'cpcloud_yz '              print*,'cpcloud_yz '
2426       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)
2427              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)  
2428           endif           endif
2429  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2430  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2551  c$$$     $           ,(db_cloud(iii),iii Line 2439  c$$$     $           ,(db_cloud(iii),iii
2439        endif                            endif                    
2440                
2441        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2442           print*,'Y-Z total clouds ',nclouds_yz           print*,'Y-Z total clouds ',nclouds_yz
          print*,' '  
2443        endif        endif
2444                
2445                
# Line 2616  c      include 'momanhough_init.f' Line 2502  c      include 'momanhough_init.f'
2502   91   continue                     91   continue                  
2503        do itr1=1,ntrpt           !loop (1) on TRIPLETS        do itr1=1,ntrpt           !loop (1) on TRIPLETS
2504           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,' **'  
2505                    
2506           do icp=1,ncp_tot           do icp=1,ncp_tot
2507              cp_useds1(icp)=0              cp_useds1(icp)=0
# Line 2651  c         tr_temp(1)=itr1 Line 2535  c         tr_temp(1)=itr1
2535              do itr2=1,ntrpt     !loop (2) on TRIPLETS              do itr2=1,ntrpt     !loop (2) on TRIPLETS
2536                 if(itr2.eq.itr1)goto 11188       !next triplet                 if(itr2.eq.itr1)goto 11188       !next triplet
2537                 if(tr_used(itr2).eq.1)goto 11188 !next triplet                               if(tr_used(itr2).eq.1)goto 11188 !next triplet              
2538    
2539    
2540  *     triplet distance in parameter space  *     triplet distance in parameter space
2541  *     solo i due parametri spaziali per il momemnto  *     solo i due parametri spaziali per il momemnto
2542                 distance=                 distance=
2543       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2
2544       $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2                     $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2
2545                 distance = sqrt(distance)                 distance = sqrt(distance)
2546                  
2547    
2548  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
2549  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE
2550  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
# Line 2670  c         tr_temp(1)=itr1 Line 2557  c         tr_temp(1)=itr1
2557       $              .true.)istrimage=1       $              .true.)istrimage=1
2558    
2559                 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  
2560                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2561                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
2562                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1
# Line 2689  c     print*,idb1,idb2,distance,' cloud Line 2575  c     print*,idb1,idb2,distance,' cloud
2575                    temp1 = temp1 + alfaxz1(itr2)                    temp1 = temp1 + alfaxz1(itr2)
2576                    temp2 = temp2 + alfaxz2(itr2)                    temp2 = temp2 + alfaxz2(itr2)
2577                    temp3 = temp3 + alfaxz3(itr2)                    temp3 = temp3 + alfaxz3(itr2)
 c     print*,'*   itrref,itr2 ',itrref,itr2,distance  
2578                 endif                               endif              
2579                                
2580  11188          continue  11188          continue
2581              enddo               !end loop (2) on TRIPLETS              enddo               !end loop (2) on TRIPLETS
2582                                                
2583  11888       continue  c11888       continue
2584                continue
2585           enddo                  !end loop on... bo?               enddo                  !end loop on... bo?    
2586                    
2587           nptloop=npv           nptloop=npv
# Line 2710  c     print*,'*   itrref,itr2 ',itrref,i Line 2596  c     print*,'*   itrref,itr2 ',itrref,i
2596  *     1bis)  *     1bis)
2597  *     2) it is not already stored  *     2) it is not already stored
2598  *     ------------------------------------------  *     ------------------------------------------
 c     print*,'check cp_used'  
2599           do ip=1,nplanes           do ip=1,nplanes
2600              hit_plane(ip)=0              hit_plane(ip)=0
2601           enddo           enddo
2602           ncpused=0           ncpused=0
2603           do icp=1,ncp_tot           do icp=1,ncp_tot
2604              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2605         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2606         $           .true.)then
2607                 ncpused=ncpused+1                 ncpused=ncpused+1
2608                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2609                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2726  c     print*,'check cp_used' Line 2613  c     print*,'check cp_used'
2613           do ip=1,nplanes           do ip=1,nplanes
2614              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2615           enddo           enddo
 c         if(ncpused.lt.ncpxz_min)goto 22288 !next triplet  
          if(npt.lt.nptxz_min)goto 22288     !next triplet  
2616           if(nplused.lt.nplxz_min)goto 22288 !next triplet           if(nplused.lt.nplxz_min)goto 22288 !next triplet
2617                    
2618  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2761  c               mask_view(iv) = 6 Line 2646  c               mask_view(iv) = 6
2646           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2647                    
2648           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
2649              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'              print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'
             print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'                
2650              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)
2651              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)
2652              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)
# Line 2771  c               mask_view(iv) = 6 Line 2655  c               mask_view(iv) = 6
2655              print*,'cpcloud_xz '              print*,'cpcloud_xz '
2656       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)
2657              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)  
2658           endif           endif
2659  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2660  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2788  c$$$     $           ,(tr_cloud(iii),iii Line 2668  c$$$     $           ,(tr_cloud(iii),iii
2668         endif                             endif                    
2669                
2670        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2671           print*,'X-Z total clouds ',nclouds_xz           print*,'X-Z total clouds ',nclouds_xz
          print*,' '  
2672        endif        endif
2673                
2674                
# Line 2846  c$$$     $           ,(tr_cloud(iii),iii Line 2724  c$$$     $           ,(tr_cloud(iii),iii
2724    
2725        ntracks=0                 !counter of track candidates        ntracks=0                 !counter of track candidates
2726                
2727        do iyz=1,nclouds_yz       !loop on YZ couds        do iyz=1,nclouds_yz       !loop on YZ clouds
2728           do ixz=1,nclouds_xz    !loop on XZ couds           do ixz=1,nclouds_xz    !loop on XZ clouds
2729                            
2730  *     --------------------------------------------------  *     --------------------------------------------------
2731  *     check of consistency of the clouds  *     check of consistency of the clouds
# Line 2856  c$$$     $           ,(tr_cloud(iii),iii Line 2734  c$$$     $           ,(tr_cloud(iii),iii
2734  *     of the two clouds  *     of the two clouds
2735  *     --------------------------------------------------  *     --------------------------------------------------
2736              do ip=1,nplanes              do ip=1,nplanes
2737                 hit_plane(ip)=0                 hit_plane(ip)=0  !n.matching couples (REAL couples, not SINGLETS)
2738                 ncp_match(ip)=0                 ncp_match(ip)=0  !n.matching couples per plane
2739                 do icpp=1,ncouplemax                 do icpp=1,ncouplemax
2740                    cp_match(ip,icpp)=0 !init couple list                    cp_match(ip,icpp)=0 !init couple list
2741                 enddo                 enddo
2742              enddo              enddo
2743              ncp_ok=0              ncp_ok=0            !count n.matching-couples
2744                ncpx_ok=0           !count n.matching-couples with x cluster
2745                ncpy_ok=0           !count n.matching-couples with y cluster
2746    
2747    
2748              do icp=1,ncp_tot    !loop over couples              do icp=1,ncp_tot    !loop over couples
2749  *     get info on  
2750                 cpintersec(icp)=min(                 if(.not.RECOVER_SINGLETS)then
2751       $              cpcloud_yz(iyz,icp),  *     ------------------------------------------------------
2752       $              cpcloud_xz(ixz,icp))  *     if NOT in RECOVER_SINGLETS mode, take the intersection
2753                 if(  *     between xz yz clouds
2754       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.  *     ------------------------------------------------------
2755       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.                    cpintersec(icp)=min(
2756       $              .false.)cpintersec(icp)=0       $                 cpcloud_yz(iyz,icp),
2757         $                 cpcloud_xz(ixz,icp))
2758  *     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
2759    *     ------------------------------------------------------
2760    *     discard the couple if the sensor is in conflict
2761    *     ------------------------------------------------------
2762                      if(
2763         $       (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2764         $       (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2765         $                 .false.)cpintersec(icp)=0
2766                   else
2767    *     ------------------------------------------------------
2768    *     if RECOVER_SINGLETS take the union
2769    *     (otherwise the fake couples formed by singlets would be
2770    *     discarded)    
2771    *     ------------------------------------------------------
2772                      cpintersec(icp)=max(
2773         $                 cpcloud_yz(iyz,icp),
2774         $                 cpcloud_xz(ixz,icp))
2775    c$$$                  if(cpcloud_yz(iyz,icp).gt.0)
2776    c$$$     $                 cpintersec(icp)=cpcloud_yz(iyz,icp)
2777    *     cpintersec is >0 if either yz or xz cloud contains the couple icp
2778                   endif
2779    
2780    c$$$               print*,icp,ip_cp(icp),' -- ',cpintersec(icp)
2781    
2782                 if(cpintersec(icp).ne.0)then                 if(cpintersec(icp).ne.0)then
                   ncp_ok=ncp_ok+1    
2783                                        
2784                    ip=ip_cp(icp)                    ip=ip_cp(icp)
2785                    hit_plane(ip)=1                    hit_plane(ip)=1
2786    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).gt.0)
2787    c$$$     $                 ncp_ok=ncp_ok+1  
2788    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).eq.0)
2789    c$$$     $                 ncpx_ok=ncpx_ok+1
2790    c$$$                  if(clx(ip,icp).eq.0.and.cly(ip,icp).gt.0)
2791    c$$$     $                 ncpy_ok=ncpy_ok+1
2792    
2793                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2794         $                 cpcloud_xz(ixz,icp).gt.0)
2795         $                 ncp_ok=ncp_ok+1  
2796                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2797         $                 cpcloud_xz(ixz,icp).eq.0)
2798         $                 ncpy_ok=ncpy_ok+1  
2799                      if(  cpcloud_yz(iyz,icp).eq.0.and.
2800         $                 cpcloud_xz(ixz,icp).gt.0)
2801         $                 ncpx_ok=ncpx_ok+1  
2802    
2803                    if(cpintersec(icp).eq.1)then                    if(cpintersec(icp).eq.1)then
2804  *     1) only the couple image in sensor 1 matches  *     1) only the couple image in sensor 1 matches
2805                       id=-icp                       id=-icp
# Line 2904  c$$$     $           ,(tr_cloud(iii),iii Line 2826  c$$$     $           ,(tr_cloud(iii),iii
2826              do ip=1,nplanes              do ip=1,nplanes
2827                 nplused=nplused+ hit_plane(ip)                 nplused=nplused+ hit_plane(ip)
2828              enddo              enddo
2829                                        
2830                            if(nplused.lt.3)goto 888 !next combination
2831    ccc            if(nplused.lt.nplxz_min)goto 888 !next combination
2832    ccc            if(nplused.lt.nplyz_min)goto 888 !next combination
2833    *     -----------------------------------------------------------
2834    *     if in RECOVER_SINGLET mode, the two clouds must have
2835    *     at least ONE intersecting real couple
2836    *     -----------------------------------------------------------
2837                if(ncp_ok.lt.1)goto 888 !next combination
2838    
2839              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
2840                 print*,'Combination ',iyz,ixz                 print*,'////////////////////////////'
2841       $              ,' db ',ptcloud_yz(iyz)                 print*,'Cloud combination (Y,X): ',iyz,ixz
2842       $              ,' tr ',ptcloud_xz(ixz)                 print*,' db ',ptcloud_yz(iyz)
2843       $              ,'  -----> # matching couples ',ncp_ok                 print*,' tr ',ptcloud_xz(ixz)
2844                   print*,'  -----> # matching couples ',ncp_ok
2845                   print*,'  -----> # fake couples (X)',ncpx_ok
2846                   print*,'  -----> # fake couples (Y)',ncpy_ok
2847                   do icp=1,ncp_tot
2848                      print*,'cp ',icp,' >'
2849         $                 ,' x ',cpcloud_xz(ixz,icp)
2850         $                 ,' y ',cpcloud_yz(iyz,icp)
2851         $                 ,' ==> ',cpintersec(icp)
2852                   enddo
2853              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  
2854                                                    
2855              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
                print*,'track candidate', ntracks+1  
2856                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2857                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2858                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
# Line 2996  c$$$            if(AL_INI(5).gt.defmax)g Line 2885  c$$$            if(AL_INI(5).gt.defmax)g
2885                                hit_plane(6)=icp6                                hit_plane(6)=icp6
2886                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
2887                                                                
2888                                  if(DEBUG.eq.1)
2889         $                             print*,'combination: '
2890         $                             ,cp_match(6,icp1)
2891         $                             ,cp_match(5,icp2)
2892         $                             ,cp_match(4,icp3)
2893         $                             ,cp_match(3,icp4)
2894         $                             ,cp_match(2,icp5)
2895         $                             ,cp_match(1,icp6)
2896    
2897    
2898  *                             ---------------------------------------  *                             ---------------------------------------
2899  *                             check if this group of couples has been  *                             check if this group of couples has been
2900  *                             already fitted      *                             already fitted    
# Line 3044  c     $                                 Line 2943  c     $                                
2943       $                                   PFAdef,PFAdef,0.,0.,0.,0.)       $                                   PFAdef,PFAdef,0.,0.,0.,0.)
2944  *                                   *************************  *                                   *************************
2945  *                                   -----------------------------  *                                   -----------------------------
2946                                      xgood(nplanes-ip+1)=1.                                      if(icx.gt.0.and.icy.gt.0)then
2947                                      ygood(nplanes-ip+1)=1.                                         xgood(nplanes-ip+1)=1.
2948                                      xm(nplanes-ip+1)=xPAM                                         ygood(nplanes-ip+1)=1.
2949                                      ym(nplanes-ip+1)=yPAM                                         xm(nplanes-ip+1)=xPAM
2950                                      zm(nplanes-ip+1)=zPAM                                         ym(nplanes-ip+1)=yPAM
2951                                      resx(nplanes-ip+1)=resxPAM                                         zm(nplanes-ip+1)=zPAM
2952                                      resy(nplanes-ip+1)=resyPAM                                         resx(nplanes-ip+1)=resxPAM
2953                                           resy(nplanes-ip+1)=resyPAM
2954                                           if(DEBUG.EQ.1)print*,'(X,Y)'
2955         $                                      ,nplanes-ip+1,xPAM,yPAM
2956                                        else
2957                                           xm_A(nplanes-ip+1) = xPAM_A
2958                                           ym_A(nplanes-ip+1) = yPAM_A
2959                                           xm_B(nplanes-ip+1) = xPAM_B
2960                                           ym_B(nplanes-ip+1) = yPAM_B
2961                                           zm(nplanes-ip+1)
2962         $                                      = (zPAM_A+zPAM_B)/2.
2963                                           resx(nplanes-ip+1) = resxPAM
2964                                           resy(nplanes-ip+1) = resyPAM
2965                                           if(icx.eq.0.and.icy.gt.0)then
2966                                              xgood(nplanes-ip+1)=0.
2967                                              ygood(nplanes-ip+1)=1.
2968                                              resx(nplanes-ip+1) = 1000.
2969                                              if(DEBUG.EQ.1)print*,'(  Y)'
2970         $                                         ,nplanes-ip+1,xPAM,yPAM
2971                                           elseif(icx.gt.0.and.icy.eq.0)then
2972                                              xgood(nplanes-ip+1)=1.
2973                                              ygood(nplanes-ip+1)=0.
2974                                              if(DEBUG.EQ.1)print*,'(X  )'
2975         $                                         ,nplanes-ip+1,xPAM,yPAM
2976                                              resy(nplanes-ip+1) = 1000.
2977                                           else
2978                                              print*,'both icx=0 and icy=0'
2979         $                                         ,' ==> IMPOSSIBLE!!'
2980                                           endif
2981                                        endif
2982  *                                   -----------------------------  *                                   -----------------------------
2983                                   endif                                   endif
2984                                enddo !end loop on planes                                enddo !end loop on planes
# Line 3091  c                                 chi2=- Line 3019  c                                 chi2=-
3019  *     **********************************************************  *     **********************************************************
3020    
3021                                if(chi2.le.0.)goto 666                                              if(chi2.le.0.)goto 666              
3022                                  if(chi2.ge.1.e08)goto 666 !OPTIMIZATION
3023                                  if(chi2.ne.chi2)goto 666  !OPTIMIZATION
3024    
3025  *     --------------------------  *     --------------------------
3026  *     STORE candidate TRACK INFO  *     STORE candidate TRACK INFO
# Line 3117  c                                    mas Line 3047  c                                    mas
3047    
3048                                   XV_STORE(ip,ntracks)=sngl(xv(ip))                                   XV_STORE(ip,ntracks)=sngl(xv(ip))
3049                                   YV_STORE(ip,ntracks)=sngl(yv(ip))                                   YV_STORE(ip,ntracks)=sngl(yv(ip))
3050                                   ZV_STORE(ip,ntracks)=sngl(zv(ip))                                                                       ZV_STORE(ip,ntracks)=sngl(zv(ip))
3051                                   XM_STORE(ip,ntracks)=sngl(xm(ip))                                   XM_STORE(ip,ntracks)=sngl(xm(ip))
3052                                   YM_STORE(ip,ntracks)=sngl(ym(ip))                                   YM_STORE(ip,ntracks)=sngl(ym(ip))
3053                                   ZM_STORE(ip,ntracks)=sngl(zm(ip))                                   ZM_STORE(ip,ntracks)=sngl(zm(ip))
# Line 3136  c                                    mas Line 3066  c                                    mas
3066       $                                   cp_match(ip,hit_plane(ip))       $                                   cp_match(ip,hit_plane(ip))
3067                                      SENSOR_STORE(nplanes-ip+1,ntracks)                                      SENSOR_STORE(nplanes-ip+1,ntracks)
3068       $                              = is_cp(cp_match(ip,hit_plane(ip)))       $                              = is_cp(cp_match(ip,hit_plane(ip)))
3069                                      LADDER_STORE(nplanes-ip+1,ntracks)                                      
3070       $                                   = LADDER(                                      icl=
3071       $                                   clx(ip,icp_cp(       $                                   clx(ip,icp_cp(
3072       $                                   cp_match(ip,hit_plane(ip)       $                                   cp_match(ip,hit_plane(ip)
3073       $                                   ))));       $                                   )));
3074                                        if(icl.eq.0)
3075         $                                   icl=
3076         $                                   cly(ip,icp_cp(
3077         $                                   cp_match(ip,hit_plane(ip)
3078         $                                   )));
3079    
3080                                        LADDER_STORE(nplanes-ip+1,ntracks)
3081         $                                   = LADDER(icl);
3082                                   else                                   else
3083                                      CP_STORE(nplanes-ip+1,ntracks)=0                                      CP_STORE(nplanes-ip+1,ntracks)=0
3084                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0
# Line 3174  c                                    mas Line 3112  c                                    mas
3112                
3113        if(ntracks.eq.0)then        if(ntracks.eq.0)then
3114           iflag=1           iflag=1
3115           return  cc         return
3116        endif        endif
3117                
 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  
3118        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
3119          print*,'****** TRACK CANDIDATES *****************'          print*,'****** TRACK CANDIDATES *****************'
3120          print*,'#         R. chi2        RIG         ndof'          print*,'#         R. chi2        RIG         ndof'
# Line 3247  c$$$      endif Line 3176  c$$$      endif
3176        call track_init        call track_init
3177        do ip=1,nplanes           !loop on planes        do ip=1,nplanes           !loop on planes
3178    
3179             if(DEBUG.EQ.1)print*,' ........... plane ',ip,' ........... '
3180    
3181           xP=XV_STORE(nplanes-ip+1,ibest)           xP=XV_STORE(nplanes-ip+1,ibest)
3182           yP=YV_STORE(nplanes-ip+1,ibest)           yP=YV_STORE(nplanes-ip+1,ibest)
3183           zP=ZV_STORE(nplanes-ip+1,ibest)           zP=ZV_STORE(nplanes-ip+1,ibest)
# Line 3263  c$$$         bxyz(3)=0 Line 3194  c$$$         bxyz(3)=0
3194  *     using improved PFAs  *     using improved PFAs
3195  *     -------------------------------------------------  *     -------------------------------------------------
3196  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3197           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.  c$$$         if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
3198    c$$$     $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3199    c$$$            
3200    c$$$            id=CP_STORE(nplanes-ip+1,ibest)
3201    c$$$            
3202    c$$$            is=is_cp(id)
3203    c$$$            icp=icp_cp(id)
3204    c$$$            if(ip_cp(id).ne.ip)
3205    c$$$     $           print*,'OKKIO!!'
3206    c$$$     $           ,'id ',id,is,icp
3207    c$$$     $           ,ip_cp(id),ip
3208    c$$$            icx=clx(ip,icp)
3209    c$$$            icy=cly(ip,icp)
3210    c$$$c            call xyz_PAM(icx,icy,is,
3211    c$$$c     $           PFA,PFA,
3212    c$$$c     $           AXV_STORE(nplanes-ip+1,ibest),
3213    c$$$c     $           AYV_STORE(nplanes-ip+1,ibest))
3214    c$$$            call xyz_PAM(icx,icy,is,
3215    c$$$     $           PFA,PFA,
3216    c$$$     $           AXV_STORE(nplanes-ip+1,ibest),
3217    c$$$     $           AYV_STORE(nplanes-ip+1,ibest),
3218    c$$$     $           bxyz(1),
3219    c$$$     $           bxyz(2)
3220    c$$$     $           )
3221    c$$$
3222    c$$$            xm(nplanes-ip+1) = xPAM
3223    c$$$            ym(nplanes-ip+1) = yPAM
3224    c$$$            zm(nplanes-ip+1) = zPAM
3225    c$$$            xgood(nplanes-ip+1) = 1
3226    c$$$            ygood(nplanes-ip+1) = 1
3227    c$$$            resx(nplanes-ip+1) = resxPAM
3228    c$$$            resy(nplanes-ip+1) = resyPAM
3229    c$$$
3230    c$$$            dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3231    c$$$            dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3232             if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..or.
3233       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3234                            
3235              id=CP_STORE(nplanes-ip+1,ibest)              id=CP_STORE(nplanes-ip+1,ibest)
# Line 3288  c     $           AYV_STORE(nplanes-ip+1 Line 3254  c     $           AYV_STORE(nplanes-ip+1
3254       $           bxyz(2)       $           bxyz(2)
3255       $           )       $           )
3256    
3257              xm(nplanes-ip+1) = xPAM              if(icx.gt.0.and.icy.gt.0)then
3258              ym(nplanes-ip+1) = yPAM                 xm(nplanes-ip+1) = xPAM
3259              zm(nplanes-ip+1) = zPAM                 ym(nplanes-ip+1) = yPAM
3260              xgood(nplanes-ip+1) = 1                 zm(nplanes-ip+1) = zPAM
3261              ygood(nplanes-ip+1) = 1                 xm_A(nplanes-ip+1) = 0.
3262              resx(nplanes-ip+1) = resxPAM                 ym_A(nplanes-ip+1) = 0.
3263              resy(nplanes-ip+1) = resyPAM                 xm_B(nplanes-ip+1) = 0.
3264                   ym_B(nplanes-ip+1) = 0.
3265              dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))                 xgood(nplanes-ip+1) = 1
3266              dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))                 ygood(nplanes-ip+1) = 1
3267                   resx(nplanes-ip+1) = resxPAM
3268                   resy(nplanes-ip+1) = resyPAM
3269                   dedxtrk_x(nplanes-ip+1)=
3270         $              sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3271                   dedxtrk_y(nplanes-ip+1)=
3272         $              sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3273                else
3274                   xm(nplanes-ip+1) = 0.
3275                   ym(nplanes-ip+1) = 0.
3276                   zm(nplanes-ip+1) = (zPAM_A+zPAM_B)/2.
3277                   xm_A(nplanes-ip+1) = xPAM_A
3278                   ym_A(nplanes-ip+1) = yPAM_A
3279                   xm_B(nplanes-ip+1) = xPAM_B
3280                   ym_B(nplanes-ip+1) = yPAM_B
3281                   xgood(nplanes-ip+1) = 0
3282                   ygood(nplanes-ip+1) = 0
3283                   resx(nplanes-ip+1) = 1000.!resxPAM
3284                   resy(nplanes-ip+1) = 1000.!resyPAM
3285                   dedxtrk_x(nplanes-ip+1)= 0
3286                   dedxtrk_y(nplanes-ip+1)= 0
3287                   if(icx.gt.0)then
3288                      xgood(nplanes-ip+1) = 1
3289                      resx(nplanes-ip+1) = resxPAM
3290                      dedxtrk_x(nplanes-ip+1)=
3291         $                 sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3292                   elseif(icy.gt.0)then
3293                      ygood(nplanes-ip+1) = 1
3294                      resy(nplanes-ip+1) = resyPAM
3295                      dedxtrk_y(nplanes-ip+1)=
3296         $                 sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3297                   endif
3298                endif
3299                            
3300  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3301  *     -------------------------------------------------  *     -------------------------------------------------
# Line 3309  c     $           AYV_STORE(nplanes-ip+1 Line 3307  c     $           AYV_STORE(nplanes-ip+1
3307                                
3308              xgood(nplanes-ip+1)=0              xgood(nplanes-ip+1)=0
3309              ygood(nplanes-ip+1)=0              ygood(nplanes-ip+1)=0
3310    
3311                CP_STORE(nplanes-ip+1,ibest)=0 !re-init
3312                CLS_STORE(nplanes-ip+1,ibest)=0
3313    
3314                                
3315  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3316  *     determine which ladder and sensor are intersected by the track  *     determine which ladder and sensor are intersected by the track
# Line 3331  c     $           AYV_STORE(nplanes-ip+1 Line 3333  c     $           AYV_STORE(nplanes-ip+1
3333  *     ===========================================  *     ===========================================
3334  *     STEP 1 >>>>>>>  try to include a new couple  *     STEP 1 >>>>>>>  try to include a new couple
3335  *     ===========================================  *     ===========================================
3336  c            if(DEBUG.EQ.1)print*,'>>>> try to include a new couple'              distmin=100000000.
             distmin=1000000.  
3337              xmm = 0.              xmm = 0.
3338              ymm = 0.              ymm = 0.
3339              zmm = 0.              zmm = 0.
# Line 3345  c            if(DEBUG.EQ.1)print*,'>>>> Line 3346  c            if(DEBUG.EQ.1)print*,'>>>>
3346              do icp=1,ncp_plane(ip) !loop on couples on plane icp              do icp=1,ncp_plane(ip) !loop on couples on plane icp
3347                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3348                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3349                   if(icx.eq.0.or.icy.eq.0)goto 1188!if fake couple, jump to next
3350                 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
3351  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
3352  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
3353       $              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
3354       $              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
3355       $              .false.)goto 1188 !then jump to next couple.       $              .false.)goto 1188 !then jump to next couple.
3356  *            *          
3357                 call xyz_PAM(icx,icy,ist,                 call xyz_PAM(icx,icy,ist,
# Line 3363  c     $              cl_used(icy).eq.1.o Line 3365  c     $              cl_used(icy).eq.1.o
3365                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3366  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3367                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3368                 if(DEBUG.EQ.1)print*,'( couple ',id                 if(DEBUG.EQ.1)
3369         $              print*,'( couple ',id
3370       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3371                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3372                    xmm = xPAM                    xmm = xPAM
# Line 3375  c               distance = distance / RC Line 3378  c               distance = distance / RC
3378                    idm = id                                      idm = id                  
3379                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3380                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3381  c     QUIQUI --> non devo moltiplicare per clinc?!?!?!                    clincnewc=10*sqrt(rymm**2+rxmm**2
3382                    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  
3383                 endif                 endif
3384   1188          continue   1188          continue
3385              enddo               !end loop on couples on plane icp              enddo               !end loop on couples on plane icp
3386  c            if(distmin.le.clinc)then     !QUIQUI                            if(distmin.le.clincnewc)then    
             if(distmin.le.clincnewc)then     !QUIQUI                
3387  *              -----------------------------------  *              -----------------------------------
3388                 xm(nplanes-ip+1) = xmm !<<<                 xm(nplanes-ip+1) = xmm !<<<
3389                 ym(nplanes-ip+1) = ymm !<<<                 ym(nplanes-ip+1) = ymm !<<<
# Line 3396  c            if(distmin.le.clinc)then   Line 3397  c            if(distmin.le.clinc)then  
3397  *              -----------------------------------  *              -----------------------------------
3398                 CP_STORE(nplanes-ip+1,ibest)=idm                       CP_STORE(nplanes-ip+1,ibest)=idm      
3399                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm
3400       $              ,' (dist.= ',distmin,', cut ',clinc,' )'       $              ,' (dist.= ',distmin,', cut ',clincnewc,' )'
3401                 goto 133         !next plane                 goto 133         !next plane
3402              endif              endif
3403  *     ================================================  *     ================================================
3404  *     STEP 2 >>>>>>>  try to include a single cluster  *     STEP 2 >>>>>>>  try to include a single cluster
3405  *                     either from a couple or single  *                     either from a couple or single
3406  *     ================================================  *     ================================================
 c            if(DEBUG.EQ.1)print*,'>>>> try to include a new cluster'  
3407              distmin=1000000.              distmin=1000000.
3408              xmm_A = 0.          !---------------------------              xmm_A = 0.          !---------------------------
3409              ymm_A = 0.          ! init variables that              ymm_A = 0.          ! init variables that
# Line 3422  c            if(DEBUG.EQ.1)print*,'>>>> Line 3422  c            if(DEBUG.EQ.1)print*,'>>>>
3422              do icp=1,ncp_plane(ip) !loop on cluster inside couples              do icp=1,ncp_plane(ip) !loop on cluster inside couples
3423                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3424                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3425                   if(icx.eq.0.or.icy.eq.0)goto 11882!if fake couple, jump to next
3426                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3427                 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
3428  *                                                !jump to the next couple  *                                                !jump to the next couple
# Line 3440  c     $              AXV_STORE(nplanes-i Line 3441  c     $              AXV_STORE(nplanes-i
3441       $              )                     $              )              
3442                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3443  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3444                 if(DEBUG.EQ.1)print*,'( cl-X ',icx                 if(DEBUG.EQ.1)
3445         $              print*,'( cl-X ',icx
3446       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3447                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3448                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3473  c     $              0.,AYV_STORE(nplane Line 3475  c     $              0.,AYV_STORE(nplane
3475       $              )       $              )
3476                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3477  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3478                 if(DEBUG.EQ.1)print*,'( cl-Y ',icy                 if(DEBUG.EQ.1)
3479         $              print*,'( cl-Y ',icy
3480       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3481                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3482                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3493  c                 dedxmm = sgnl(icy)  !( Line 3496  c                 dedxmm = sgnl(icy)  !(
3496  11882          continue  11882          continue
3497              enddo               !end loop on cluster inside couples              enddo               !end loop on cluster inside couples
3498  *----- single clusters -----------------------------------------------    *----- single clusters -----------------------------------------------  
 c            print*,'## ncls(',ip,') ',ncls(ip)  
3499              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
3500                 icl=cls(ip,ic)                 icl=cls(ip,ic)
 c               if(cl_used(icl).eq.1.or.     !if the cluster is already used  
3501                 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)
3502       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match
3503       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
# Line 3518  c               if(cl_used(icl).eq.1.or. Line 3519  c               if(cl_used(icl).eq.1.or.
3519    
3520                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3521  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3522                 if(DEBUG.EQ.1)print*,'( cl-s ',icl                 if(DEBUG.EQ.1)
3523         $              print*,'( cl-s ',icl
3524       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3525                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
 c                  if(DEBUG.EQ.1)print*,'YES'  
3526                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3527                    ymm_A = yPAM_A                    ymm_A = yPAM_A
3528                    zmm_A = zPAM_A                    zmm_A = zPAM_A
# Line 3542  c                  if(DEBUG.EQ.1)print*, Line 3543  c                  if(DEBUG.EQ.1)print*,
3543                 endif                                   endif                  
3544  18882          continue  18882          continue
3545              enddo               !end loop on single clusters              enddo               !end loop on single clusters
 c            print*,'## distmin ', distmin,' clinc ',clinc  
3546    
 c     QUIQUI------------  
 c     anche qui: non ci vuole clinc???  
3547              if(iclm.ne.0)then              if(iclm.ne.0)then
3548                 if(mod(VIEW(iclm),2).eq.0)then                 if(mod(VIEW(iclm),2).eq.0)then
3549                    clincnew=                    clincnew=
# Line 3556  c     anche qui: non ci vuole clinc??? Line 3554  c     anche qui: non ci vuole clinc???
3554       $                 10*       $                 10*
3555       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))
3556                 endif                 endif
3557  c     QUIQUI------------  
3558                                 if(distmin.le.clincnew)then  
                if(distmin.le.clincnew)then   !QUIQUI  
 c     if(distmin.le.clinc)then          !QUIQUI            
3559                                        
3560                    CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<                        CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<    
3561  *     ----------------------------  *     ----------------------------
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3562                    if(mod(VIEW(iclm),2).eq.0)then                    if(mod(VIEW(iclm),2).eq.0)then
3563                       XGOOD(nplanes-ip+1)=1.                       XGOOD(nplanes-ip+1)=1.
3564                       resx(nplanes-ip+1)=rxmm                       resx(nplanes-ip+1)=rxmm
3565                       if(DEBUG.EQ.1)print*,'%%%% included X-cl ',iclm                       if(DEBUG.EQ.1)
3566         $                    print*,'%%%% included X-cl ',iclm
3567       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3568       $                    ,', dist.= ',distmin       $                    ,', dist.= ',distmin
3569       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3570                    else                    else
3571                       YGOOD(nplanes-ip+1)=1.                       YGOOD(nplanes-ip+1)=1.
3572                       resy(nplanes-ip+1)=rymm                       resy(nplanes-ip+1)=rymm
3573                       if(DEBUG.EQ.1)print*,'%%%% included Y-cl ',iclm                       if(DEBUG.EQ.1)
3574         $                    print*,'%%%% included Y-cl ',iclm
3575       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3576       $                    ,', dist.= ', distmin       $                    ,', dist.= ', distmin
3577       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3578                    endif                    endif
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3579  *     ----------------------------  *     ----------------------------
3580                    xm_A(nplanes-ip+1) = xmm_A                    xm_A(nplanes-ip+1) = xmm_A
3581                    ym_A(nplanes-ip+1) = ymm_A                    ym_A(nplanes-ip+1) = ymm_A
# Line 3600  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3596  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3596        return        return
3597        end        end
3598    
3599    
3600  ***************************************************  ***************************************************
3601  *                                                 *  *                                                 *
3602  *                                                 *  *                                                 *
# Line 3609  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3606  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3606  *                                                 *  *                                                 *
3607  **************************************************  **************************************************
3608  *  *
       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  
   
   
   
3609    
3610    
3611    
# Line 3729  c$$$               cl_used(icl)=ntrk   ! Line 3654  c$$$               cl_used(icl)=ntrk   !
3654              DEDX_Y(IP,IT) = 0              DEDX_Y(IP,IT) = 0
3655              CLTRX(IP,IT) = 0              CLTRX(IP,IT) = 0
3656              CLTRY(IP,IT) = 0              CLTRY(IP,IT) = 0
3657                multmaxx(ip,it) = 0
3658                seedx(ip,it)    = 0
3659                xpu(ip,it)      = 0
3660                multmaxy(ip,it) = 0
3661                seedy(ip,it)    = 0
3662                ypu(ip,it)      = 0
3663           enddo           enddo
3664           do ipa=1,5           do ipa=1,5
3665              AL_nt(IPA,IT) = 0              AL_nt(IPA,IT) = 0
# Line 3748  c$$$               cl_used(icl)=ntrk   ! Line 3679  c$$$               cl_used(icl)=ntrk   !
3679          ys(1,ip)=0          ys(1,ip)=0
3680          ys(2,ip)=0          ys(2,ip)=0
3681          sgnlys(ip)=0          sgnlys(ip)=0
3682            sxbad(ip)=0
3683            sybad(ip)=0
3684            multmaxsx(ip)=0
3685            multmaxsy(ip)=0
3686        enddo        enddo
3687        end        end
3688    
# Line 3870  c$$$               cl_used(icl)=ntrk   ! Line 3805  c$$$               cl_used(icl)=ntrk   !
3805        integer ssensor,sladder        integer ssensor,sladder
3806        pig=acos(-1.)        pig=acos(-1.)
3807    
3808    
3809    
3810  *     -------------------------------------  *     -------------------------------------
3811        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3812        nstep_nt(ntr)       = nstep        nstep_nt(ntr)       = nstep
# Line 3917  c$$$               cl_used(icl)=ntrk   ! Line 3854  c$$$               cl_used(icl)=ntrk   !
3854           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)
3855           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)             dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)  
3856        
3857    
3858    ccc         print*,ip,'dedx >>> ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3859    
3860           ax   = axv_nt(ip,ntr)           ax   = axv_nt(ip,ntr)
3861           ay   = ayv_nt(ip,ntr)           ay   = ayv_nt(ip,ntr)
3862           bfx  = BX_STORE(ip,IDCAND)           bfx  = BX_STORE(ip,IDCAND)
3863           bfy  = BY_STORE(ip,IDCAND)           bfy  = BY_STORE(ip,IDCAND)
3864           if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)  c$$$         if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)
3865           if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)  c$$$         if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)
3866           tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001  c$$$         tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001
3867           angx     = 180.*atan(tgtemp)/acos(-1.)  c$$$         angx     = 180.*atan(tgtemp)/acos(-1.)
3868           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001          c$$$         tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001        
3869           angy    = 180.*atan(tgtemp)/acos(-1.)  c$$$         angy    = 180.*atan(tgtemp)/acos(-1.)
3870    
3871             angx = effectiveangle(ax,2*ip,bfy)
3872             angy = effectiveangle(ay,2*ip-1,bfx)
3873            
3874                    
 c         print*,'* ',ip,bfx,bfy,angx,angy  
3875    
3876           id  = CP_STORE(ip,IDCAND) ! couple id           id  = CP_STORE(ip,IDCAND) ! couple id
3877           icl = CLS_STORE(ip,IDCAND)           icl = CLS_STORE(ip,IDCAND)
# Line 3944  c           >>> is a couple Line 3887  c           >>> is a couple
3887              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3888              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3889    
3890              cl_used(cltrx(ip,ntr)) = 1     !tag used clusters                        if(clx(nplanes-ip+1,icp_cp(id)).gt.0)then
3891              cl_used(cltry(ip,ntr)) = 1     !tag used clusters            
3892                   cl_used(cltrx(ip,ntr)) = 1 !tag used clusters          
3893    
3894                   xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))
3895    
3896                   if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3897         $              dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3898                  
3899                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3900         $              +10000*mult(cltrx(ip,ntr))
3901                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3902         $              /clsigma(indmax(cltrx(ip,ntr)))
3903                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3904                   xpu(ip,ntr)      = corr
3905    
3906                endif
3907                if(cly(nplanes-ip+1,icp_cp(id)).gt.0)then
3908    
3909  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)))  
3910    
3911                   ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))
3912    
3913              if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)                 if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3914       $           dedx_x(ip,ntr)=-dedx_x(ip,ntr)       $              dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3915              if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)                
3916       $           dedx_y(ip,ntr)=-dedx_y(ip,ntr)                 multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3917         $              +10000*mult(cltry(ip,ntr))
3918                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3919         $              /clsigma(indmax(cltry(ip,ntr)))
3920                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3921                   ypu(ip,ntr)      = corr
3922                endif
3923    
3924           elseif(icl.ne.0)then           elseif(icl.ne.0)then
3925    
# Line 3966  c$$$            ybad(ip,ntr)= nbadstrips Line 3927  c$$$            ybad(ip,ntr)= nbadstrips
3927    
3928              if(mod(VIEW(icl),2).eq.0)then              if(mod(VIEW(icl),2).eq.0)then
3929                 cltrx(ip,ntr)=icl                 cltrx(ip,ntr)=icl
 c$$$               nnnnn = npfastrips(icl,PFA,angx)  
 c$$$               xbad(ip,ntr) = nbadstrips(nnnnn,icl)  
3930                 xbad(ip,ntr) = nbadstrips(4,icl)                 xbad(ip,ntr) = nbadstrips(4,icl)
3931    
3932                 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)
3933    
3934                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3935         $                         +10000*mult(cltrx(ip,ntr))
3936                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3937         $           /clsigma(indmax(cltrx(ip,ntr)))
3938                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3939                   xpu(ip,ntr)      = corr
3940    
3941              elseif(mod(VIEW(icl),2).eq.1)then              elseif(mod(VIEW(icl),2).eq.1)then
3942                 cltry(ip,ntr)=icl                 cltry(ip,ntr)=icl
 c$$$               nnnnn = npfastrips(icl,PFA,angy)  
 c$$$               ybad(ip,ntr) = nbadstrips(nnnnn,icl)  
3943                 ybad(ip,ntr) = nbadstrips(4,icl)                 ybad(ip,ntr) = nbadstrips(4,icl)
3944    
3945                 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)
3946    
3947                   multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3948         $                         +10000*mult(cltry(ip,ntr))
3949                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3950         $           /clsigma(indmax(cltry(ip,ntr)))
3951                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3952                   ypu(ip,ntr)      = corr
3953                  
3954              endif              endif
3955    
3956           endif                     endif          
# Line 3989  c$$$               ybad(ip,ntr) = nbadst Line 3963  c$$$               ybad(ip,ntr) = nbadst
3963           do ip=1,6           do ip=1,6
3964              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)
3965           enddo           enddo
3966             print*,'dedx: '
3967             do ip=1,6
3968                print*,'> ',ip,' -- ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3969             enddo
3970        endif        endif
3971    
 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*,'-----------------------'  
   
3972        end        end
3973    
3974        subroutine fill_level2_siglets        subroutine fill_level2_siglets
# Line 4033  c         if( mask_view(iv).ne.0 )good2( Line 4004  c         if( mask_view(iv).ne.0 )good2(
4004           ip=nplanes-npl(VIEW(icl))+1                       ip=nplanes-npl(VIEW(icl))+1            
4005                    
4006           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
4007    
4008              if(mod(VIEW(icl),2).eq.0)then !=== X views              if(mod(VIEW(icl),2).eq.0)then !=== X views
4009    
4010                 nclsx = nclsx + 1                 nclsx = nclsx + 1
4011                 planex(nclsx) = ip                 planex(nclsx) = ip
4012                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4013                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)
4014                 clsx(nclsx)   = icl                 clsx(nclsx)   = icl
4015                   sxbad(nclsx)  = nbadstrips(1,icl)
4016                   multmaxsx(nclsx) = maxs(icl)+10000*mult(icl)
4017                  
4018    
4019                 do is=1,2                 do is=1,2
4020  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4021  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
4022                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)
4023                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2
4024                 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)  
4025              else                          !=== Y views              else                          !=== Y views
4026                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4027                 planey(nclsy) = ip                 planey(nclsy) = ip
4028                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4029                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)
4030                 clsy(nclsy)   = icl                 clsy(nclsy)   = icl
4031                   sybad(nclsy)  = nbadstrips(1,icl)
4032                   multmaxsy(nclsy) = maxs(icl)+10000*mult(icl)
4033    
4034    
4035                 do is=1,2                 do is=1,2
4036  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4037  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
4038                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)
4039                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2
4040                 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)  
4041              endif              endif
4042           endif           endif
4043    
# Line 4079  c$$$               print*,'ys(2,nclsy)   Line 4050  c$$$               print*,'ys(2,nclsy)  
4050  *     associati ad una traccia, e permettere di salvare  *     associati ad una traccia, e permettere di salvare
4051  *     solo questi nell'albero di uscita  *     solo questi nell'albero di uscita
4052  *     --------------------------------------------------  *     --------------------------------------------------
4053                            
   
 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  
           
   
4054        enddo        enddo
4055        end        end
4056    
# Line 4158  c$$$         endif Line 4112  c$$$         endif
4112                 alfayz2_av_nt(iyz)=alfayz2_av(iyz)                 alfayz2_av_nt(iyz)=alfayz2_av(iyz)
4113                 nnn=nnn+ptcloud_yz(iyz)                 nnn=nnn+ptcloud_yz(iyz)
4114              enddo              enddo
4115              do ipt=1,nnn              do ipt=1,min(ndblt_max_nt,nnn)
4116                 db_cloud_nt(ipt)=db_cloud(ipt)                 db_cloud_nt(ipt)=db_cloud(ipt)
4117               enddo               enddo
4118           endif           endif
# Line 4171  c$$$         endif Line 4125  c$$$         endif
4125                 alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)                 alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)
4126                 nnn=nnn+ptcloud_xz(ixz)                               nnn=nnn+ptcloud_xz(ixz)              
4127              enddo              enddo
4128              do ipt=1,nnn              do ipt=1,min(ntrpt_max_nt,nnn)
4129                tr_cloud_nt(ipt)=tr_cloud(ipt)                tr_cloud_nt(ipt)=tr_cloud(ipt)
4130               enddo               enddo
4131           endif           endif

Legend:
Removed from v.1.29  
changed lines
  Added in v.1.40

  ViewVC Help
Powered by ViewVC 1.1.23