/[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.32 by bongi, Tue Sep 4 15:44:49 2007 UTC revision 1.41 by mocchiut, Tue Aug 11 12:58:24 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    c11111    continue               !<<<<<<< come here when performing a new search
275             continue                  !<<<<<<< come here when performing a new search
276    
277  11111    continue               !<<<<<<< come here when performing a new search           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 272  c$$$         if(ibest.eq.0)goto 880 !>> Line 303  c$$$         if(ibest.eq.0)goto 880 !>>
303  *     1st) decreasing n.points  *     1st) decreasing n.points
304  *     2nd) increasing chi**2  *     2nd) increasing chi**2
305  *     -------------------------------------------------------  *     -------------------------------------------------------
306           rchi2best=1000000000.           rchi2best=1000000000.
307           ndofbest=0                       ndofbest=0            
308           do i=1,ntracks           do i=1,ntracks
309             ndof=0                           ndof=0              
# 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 699  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
# Line 713  c$$$      print*,icx,icy,sensor,PFAx,PFA Line 663  c$$$      print*,icx,icy,sensor,PFAx,PFA
663        xPAM_B = 0.D0        xPAM_B = 0.D0
664        yPAM_B = 0.D0        yPAM_B = 0.D0
665        zPAM_B = 0.D0        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 757  c         resxPAM = RESXAV Line 706  c         resxPAM = RESXAV
706           stripx  = stripx + corr           stripx  = stripx + corr
707           resxPAM = res           resxPAM = res
708    
709   10   endif   10   continue
710          endif
711            
712  *     -----------------  *     -----------------
713  *     CLUSTER Y  *     CLUSTER Y
# Line 803  c         resyPAM = RESYAV Line 753  c         resyPAM = RESYAV
753           stripy  = stripy + corr           stripy  = stripy + corr
754           resyPAM = res           resyPAM = res
755    
756   20   endif   20   continue
757          endif
758    
 c$$$      print*,'## stripx,stripy ',stripx,stripy  
759    
760  c===========================================================  c===========================================================
761  C     COUPLE  C     COUPLE
# Line 885  C======================================= Line 835  C=======================================
835              nldx = nldy              nldx = nldy
836              viewx = viewy + 1              viewx = viewy + 1
837    
838              yi   = dcoordsi(stripy,viewy)              xi = dcoordsi(0.5*(nstrips+1),viewx) !sensor center
839                yi = dcoordsi(stripy,viewy)
840                zi = 0.D0
841    
842              xi_A = edgeY_d - SiDimX/2              xi_A = edgeY_d - SiDimX/2
843              yi_A = yi              yi_A = yi
# Line 895  C======================================= Line 847  C=======================================
847              yi_B = yi              yi_B = yi
848              zi_B = 0.              zi_B = 0.
849    
 c            print*,'Y-cl ',icy,stripy,' --> ',yi  
 c            print*,xi_A,' <--> ',xi_B  
850                            
851           elseif(icx.ne.0)then           elseif(icx.ne.0)then
852  c===========================================================  c===========================================================
# Line 907  C======================================= Line 857  C=======================================
857              nldy = nldx              nldy = nldx
858              viewy = viewx - 1              viewy = viewx - 1
859    
 c            print*,'X-singlet ',icx,nplx,nldx,viewx,stripx  
 c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  
860              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
861       $           .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...
862                 if(DEBUG.EQ.1) then                 if(DEBUG.EQ.1) then
# Line 916  c            if((stripx.le.3).or.(stripx Line 864  c            if((stripx.le.3).or.(stripx
864       $                 ' WARNING: false X strip: strip ',stripx       $                 ' WARNING: false X strip: strip ',stripx
865                 endif                 endif
866              endif              endif
867              xi   = dcoordsi(stripx,viewx)  
868                xi = dcoordsi(stripx,viewx)
869                yi = dcoordsi(0.5*(nstrips+1),viewy) !sensor center
870                zi = 0.D0
871    
872              xi_A = xi              xi_A = xi
873              yi_A = edgeX_d - SiDimY/2              yi_A = edgeX_d - SiDimY/2
# Line 932  c            if((stripx.le.3).or.(stripx Line 883  c            if((stripx.le.3).or.(stripx
883                 yi_B = yi                 yi_B = yi
884              endif              endif
885    
 c            print*,'X-cl ',icx,stripx,' --> ',xi  
 c            print*,yi_A,' <--> ',yi_B  
886    
887           else           else
888              if(DEBUG.EQ.1) then              if(DEBUG.EQ.1) then
# Line 979  c     N.B. I convert angles from microra Line 928  c     N.B. I convert angles from microra
928       $        + zi_B       $        + zi_B
929       $        + dz(nplx,nldx,sensor)       $        + dz(nplx,nldx,sensor)
930    
931    
932    
933             xrt = xi
934         $        - omega(nplx,nldx,sensor)*yi
935         $        + gamma(nplx,nldx,sensor)*zi
936         $        + dx(nplx,nldx,sensor)
937            
938             yrt = omega(nplx,nldx,sensor)*xi
939         $        + yi
940         $        - beta(nplx,nldx,sensor)*zi
941         $        + dy(nplx,nldx,sensor)
942            
943             zrt = -gamma(nplx,nldx,sensor)*xi
944         $        + beta(nplx,nldx,sensor)*yi
945         $        + zi
946         $        + dz(nplx,nldx,sensor)
947    
948    
949                    
950  c      xrt = xi  c      xrt = xi
951  c      yrt = yi  c      yrt = yi
# Line 989  c     (xPAM,yPAM,zPAM) = measured coordi Line 956  c     (xPAM,yPAM,zPAM) = measured coordi
956  c                        in PAMELA reference system  c                        in PAMELA reference system
957  c------------------------------------------------------------------------  c------------------------------------------------------------------------
958    
959           xPAM = 0.D0           xPAM = dcoord(xrt,viewx,nldx,sensor) / 1.d4
960           yPAM = 0.D0           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
961           zPAM = 0.D0           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
962    c$$$         xPAM = 0.D0
963    c$$$         yPAM = 0.D0
964    c$$$         zPAM = 0.D0
965    
966           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4
967           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4
# Line 1002  c--------------------------------------- Line 972  c---------------------------------------
972           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
973                    
974    
 c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'  
975    
976        else        else
977           if(DEBUG.EQ.1) then           if(DEBUG.EQ.1) then
# Line 1013  c         print*,'A-(',xPAM_A,yPAM_A,') Line 982  c         print*,'A-(',xPAM_A,yPAM_A,')
982        endif        endif
983                    
984    
 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  
985    
986   100  continue   100  continue
987        end        end
# Line 1053  c$$$      PFAy = 'COG4'!PFA Line 1019  c$$$      PFAy = 'COG4'!PFA
1019    
1020        if(icx.gt.nclstr1.or.icy.gt.nclstr1)then        if(icx.gt.nclstr1.or.icy.gt.nclstr1)then
1021              print*,'xyzpam: ***WARNING*** clusters ',icx,icy              print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1022       $           ,' does not exists (nclstr1=',nclstr1,')'       $           ,' do not exists (n.clusters=',nclstr1,')'
1023              icx = -1*icx              icx = -1*icx
1024              icy = -1*icy              icy = -1*icy
1025              return              return
# Line 1063  c$$$      PFAy = 'COG4'!PFA Line 1029  c$$$      PFAy = 'COG4'!PFA
1029        call idtoc(pfaid,PFAx)        call idtoc(pfaid,PFAx)
1030        call idtoc(pfaid,PFAy)        call idtoc(pfaid,PFAy)
1031    
 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  
1032                
1033        if(icx.ne.0.and.icy.ne.0)then        if(icx.ne.0.and.icy.ne.0)then
1034    
1035           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
1036           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  
1037                    
1038           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1039              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster ',icx
# Line 1110  c         zv(ip) = zPAM Line 1068  c         zv(ip) = zPAM
1068        elseif(icx.eq.0.and.icy.ne.0)then        elseif(icx.eq.0.and.icy.ne.0)then
1069    
1070           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  
1071           if( (nplanes-ipy+1).ne.ip )then           if( (nplanes-ipy+1).ne.ip )then
1072              print*,'xyzpam: ***WARNING*** cluster ',icy              print*,'xyzpam: ***WARNING*** cluster ',icy
1073       $           ,' does not belong to plane: ',ip       $           ,' does not belong to plane: ',ip
# Line 1127  c$$$     $        ,' does not belong to Line 1082  c$$$     $        ,' does not belong to
1082           resx(ip)  = 1000.           resx(ip)  = 1000.
1083           resy(ip)  = resyPAM           resy(ip)  = resyPAM
1084    
1085           xm(ip) = -100.  c$$$         xm(ip) = -100.
1086           ym(ip) = -100.  c$$$         ym(ip) = -100.
1087           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1088             xm(ip) = xPAM
1089             ym(ip) = yPAM
1090             zm(ip) = zPAM
1091           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1092           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1093           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1140  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1098  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1098        elseif(icx.ne.0.and.icy.eq.0)then        elseif(icx.ne.0.and.icy.eq.0)then
1099    
1100           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  
1101    
1102           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1103              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster ',icx
# Line 1158  c$$$     $        ,' does not belong to Line 1113  c$$$     $        ,' does not belong to
1113           resx(ip)  = resxPAM           resx(ip)  = resxPAM
1114           resy(ip)  = 1000.           resy(ip)  = 1000.
1115    
1116           xm(ip) = -100.  c$$$         xm(ip) = -100.
1117           ym(ip) = -100.  c$$$         ym(ip) = -100.
1118           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1119             xm(ip) = xPAM
1120             ym(ip) = yPAM
1121             zm(ip) = zPAM
1122           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1123           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1124           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1174  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1132  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1132           if(lad.ne.0)il=lad           if(lad.ne.0)il=lad
1133           is = 1           is = 1
1134           if(sensor.ne.0)is=sensor           if(sensor.ne.0)is=sensor
 c         print*,nplanes-ip+1,il,is  
1135    
1136           xgood(ip) = 0.           xgood(ip) = 0.
1137           ygood(ip) = 0.           ygood(ip) = 0.
# Line 1194  c         zv(ip) = z_mech_sensor(nplanes Line 1151  c         zv(ip) = z_mech_sensor(nplanes
1151        endif        endif
1152    
1153        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
 c         print*,'----------------------------- track coord'  
1154  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1155           write(*,22222)ip,zm(ip),xm(ip),ym(ip)           write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1156       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1157       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)
 c$$$         print*,'-----------------------------'  
1158        endif        endif
1159        end        end
1160    
# Line 1242  c$$$         print*,'------------------- Line 1197  c$$$         print*,'-------------------
1197    
1198  *     ----------------------  *     ----------------------
1199        if (        if (
1200       +     xPAM.eq.0.and.  c$$$     +     xPAM.eq.0.and.
1201       +     yPAM.eq.0.and.  c$$$     +     yPAM.eq.0.and.
1202       +     zPAM.eq.0.and.  c$$$     +     zPAM.eq.0.and.
1203       +     xPAM_A.ne.0.and.       +     xPAM_A.ne.0.and.
1204       +     yPAM_A.ne.0.and.       +     yPAM_A.ne.0.and.
1205       +     zPAM_A.ne.0.and.       +     zPAM_A.ne.0.and.
# Line 1286  c$$$         print*,'------------------- Line 1241  c$$$         print*,'-------------------
1241  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1242           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1243    
 c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',re  
1244    
1245                    
1246  *     ----------------------  *     ----------------------
1247        elseif(        elseif(
1248       +     xPAM.ne.0.and.  c$$$     +     xPAM.ne.0.and.
1249       +     yPAM.ne.0.and.  c$$$     +     yPAM.ne.0.and.
1250       +     zPAM.ne.0.and.  c$$$     +     zPAM.ne.0.and.
1251       +     xPAM_A.eq.0.and.       +     xPAM_A.eq.0.and.
1252       +     yPAM_A.eq.0.and.       +     yPAM_A.eq.0.and.
1253       +     zPAM_A.eq.0.and.       +     zPAM_A.eq.0.and.
# Line 1316  c$$$     $        + Line 1268  c$$$     $        +
1268  c$$$     $        ((yPAM-YPP)/resyPAM)**2  c$$$     $        ((yPAM-YPP)/resyPAM)**2
1269           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1270    
 c$$$         print*,xPAM,yPAM,zPAM  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',resxPAM,resyPAM  
1271                    
1272        else        else
1273                    
 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  
1274        endif          endif  
1275    
1276        distance_to = sngl(distance)        distance_to = sngl(distance)
# Line 1391  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1335  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1335  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1336  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1337  c------------------------------------------------------------------------  c------------------------------------------------------------------------
 c               if(((mod(int(stripx+0.5)-1,1024)+1).le.3)  
 c     $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...  
 c     if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  
 c                  print*,'whichsensor: ',  
 c     $                ' WARNING: false X strip: strip ',stripx  
 c               endif  
1338                 xi = dcoordsi(stripx,viewx)                 xi = dcoordsi(stripx,viewx)
1339                 yi = dcoordsi(stripy,viewy)                 yi = dcoordsi(stripy,viewy)
1340                 zi = 0.D0                 zi = 0.D0
# Line 1424  c--------------------------------------- Line 1362  c---------------------------------------
1362    
1363                 yvv(iv)=sngl(yvvv)                 yvv(iv)=sngl(yvvv)
1364                 xvv(iv)=sngl(xvvv)                 xvv(iv)=sngl(xvvv)
 c               print*,'LADDER ',il,' SENSOR ',is,' vertexes >> '  
 c     $              ,iv,xvv(iv),yvv(iv)  
1365              enddo               !end loop on sensor vertexes              enddo               !end loop on sensor vertexes
1366    
1367              dtot=0.              dtot=0.
# Line 1550  c      include 'common_analysis.f' Line 1486  c      include 'common_analysis.f'
1486        is_cp=0        is_cp=0
1487        if(id.lt.0)is_cp=1        if(id.lt.0)is_cp=1
1488        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 !!!'  
1489    
1490        return        return
1491        end        end
# Line 1649  c      include 'level1.f' Line 1584  c      include 'level1.f'
1584        integer iflag        integer iflag
1585    
1586        integer badseed,badclx,badcly        integer badseed,badclx,badcly
1587        
1588          iflag = iflag
1589        if(DEBUG.EQ.1)print*,'cl_to_couples:'        if(DEBUG.EQ.1)print*,'cl_to_couples:'
1590    
1591    cc      if(RECOVER_SINGLETS.and..not.SECOND_SEARCH)goto 80
1592    
1593  *     init variables  *     init variables
       ncp_tot=0  
1594        do ip=1,nplanes        do ip=1,nplanes
1595           do ico=1,ncouplemax           do ico=1,ncouplemax
1596              clx(ip,ico)=0              clx(ip,ico)=0
# Line 1666  c      include 'level1.f' Line 1603  c      include 'level1.f'
1603           ncls(ip)=0           ncls(ip)=0
1604        enddo        enddo
1605        do icl=1,nclstrmax_level2        do icl=1,nclstrmax_level2
1606           cl_single(icl) = 1           cl_single(icl) = 1     !all are single
1607           cl_good(icl)   = 0           cl_good(icl)   = 0     !all are bad
1608        enddo        enddo
1609        do iv=1,nviews        do iv=1,nviews
1610           ncl_view(iv)  = 0           ncl_view(iv)  = 0
# Line 1695  c            mask_view(iv) = 1 Line 1632  c            mask_view(iv) = 1
1632        do icx=1,nclstr1          !loop on cluster (X)        do icx=1,nclstr1          !loop on cluster (X)
1633           if(mod(VIEW(icx),2).eq.1)goto 10           if(mod(VIEW(icx),2).eq.1)goto 10
1634                    
1635             if(cl_used(icx).ne.0)goto 10
1636    
1637  *     ----------------------------------------------------  *     ----------------------------------------------------
1638  *     jump masked views (X VIEW)  *     jump masked views (X VIEW)
1639  *     ----------------------------------------------------  *     ----------------------------------------------------
# Line 1702  c            mask_view(iv) = 1 Line 1641  c            mask_view(iv) = 1
1641  *     ----------------------------------------------------  *     ----------------------------------------------------
1642  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1643  *     ----------------------------------------------------  *     ----------------------------------------------------
1644           if(sgnl(icx).lt.dedx_x_min)then           if(sgnl(icx)/mip(VIEW(icx),LADDER(icx)).lt.dedx_x_min)then
1645              cl_single(icx)=0              cl_single(icx)=0
1646              goto 10              goto 10
1647           endif           endif
# Line 1743  c     endif Line 1682  c     endif
1682                    
1683           do icy=1,nclstr1       !loop on cluster (Y)           do icy=1,nclstr1       !loop on cluster (Y)
1684              if(mod(VIEW(icy),2).eq.0)goto 20              if(mod(VIEW(icy),2).eq.0)goto 20
1685    
1686                if(cl_used(icx).ne.0)goto 20
1687                            
1688  *     ----------------------------------------------------  *     ----------------------------------------------------
1689  *     jump masked views (Y VIEW)  *     jump masked views (Y VIEW)
# Line 1752  c     endif Line 1693  c     endif
1693  *     ----------------------------------------------------  *     ----------------------------------------------------
1694  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1695  *     ----------------------------------------------------  *     ----------------------------------------------------
1696              if(sgnl(icy).lt.dedx_y_min)then              if(sgnl(icy)/mip(VIEW(icy),LADDER(icy)) .lt.dedx_y_min)then
1697                 cl_single(icy)=0                 cl_single(icy)=0
1698                 goto 20                 goto 20
1699              endif              endif
# Line 1830  c                  cut = chcut * sch(npl Line 1771  c                  cut = chcut * sch(npl
1771       $                 ,'( ',ncouplemax,' ) --> masked!'       $                 ,'( ',ncouplemax,' ) --> masked!'
1772  c                  mask_view(nviewx(nplx)) = 2  c                  mask_view(nviewx(nplx)) = 2
1773  c                  mask_view(nviewy(nply)) = 2  c                  mask_view(nviewy(nply)) = 2
1774                    mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1                   mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1
1775                    mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1                   mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1
1776                    goto 10                    goto 10
1777                 endif                 endif
1778                                
# Line 1851  c                  mask_view(nviewy(nply Line 1792  c                  mask_view(nviewy(nply
1792   10      continue   10      continue
1793        enddo                     !end loop on clusters(X)        enddo                     !end loop on clusters(X)
1794                
         
1795        do icl=1,nclstr1        do icl=1,nclstr1
1796           if(cl_single(icl).eq.1)then           if(cl_single(icl).eq.1)then
1797              ip=npl(VIEW(icl))              ip=npl(VIEW(icl))
# Line 1859  c                  mask_view(nviewy(nply Line 1799  c                  mask_view(nviewy(nply
1799              cls(ip,ncls(ip))=icl              cls(ip,ncls(ip))=icl
1800           endif           endif
1801        enddo        enddo
1802    
1803    c 80   continue
1804          continue
1805                
1806                
1807        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
1808           print*,'clusters  ',nclstr1           print*,'clusters  ',nclstr1
1809           print*,'good    ',(cl_good(i),i=1,nclstr1)           print*,'good    ',(cl_good(i),i=1,nclstr1)
1810             print*,'used    ',(cl_used(i),i=1,nclstr1)
1811           print*,'singlets',(cl_single(i),i=1,nclstr1)           print*,'singlets',(cl_single(i),i=1,nclstr1)
1812           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1813        endif        endif
1814    
1815      
1816          if(.not.RECOVER_SINGLETS)goto 81
1817    
1818    *     ////////////////////////////////////////////////
1819    *     PATCH to recover events with less than 3 couples
1820    *     ////////////////////////////////////////////////    
1821    *     loop over singlet and create "fake" couples
1822    *     (with clx=0 or cly=0)
1823    *    
1824    
1825          if(DEBUG.EQ.1)
1826         $     print*,'>>> Recover singlets '
1827         $     ,'(creates fake couples) <<<'
1828          do icl=1,nclstr1
1829             if(
1830         $        cl_single(icl).eq.1.and.
1831         $        cl_used(icl).eq.0.and.
1832         $        .true.)then
1833    *     ----------------------------------------------------
1834    *     jump masked views
1835    *     ----------------------------------------------------
1836                if( mask_view(VIEW(icl)).ne.0 ) goto 21
1837                if(mod(VIEW(icl),2).eq.0)then !=== X views
1838    *     ----------------------------------------------------
1839    *     cut on charge (X VIEW)
1840    *     ----------------------------------------------------
1841                   if(sgnl(icl).lt.dedx_x_min) goto 21
1842                  
1843                   nplx=npl(VIEW(icl))
1844    *     ------------------> (FAKE) COUPLE <-----------------
1845                   ncp_plane(nplx) = ncp_plane(nplx) + 1
1846                   clx(nplx,ncp_plane(nplx))=icl
1847                   cly(nplx,ncp_plane(nplx))=0
1848    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1849    *     ----------------------------------------------------
1850                  
1851                else                !=== Y views
1852    *     ----------------------------------------------------
1853    *     cut on charge (Y VIEW)
1854    *     ----------------------------------------------------
1855                   if(sgnl(icl).lt.dedx_y_min) goto 21
1856                  
1857                   nply=npl(VIEW(icl))
1858    *     ------------------> (FAKE) COUPLE <-----------------
1859                   ncp_plane(nply) = ncp_plane(nply) + 1
1860                   clx(nply,ncp_plane(nply))=0
1861                   cly(nply,ncp_plane(nply))=icl
1862    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1863    *     ----------------------------------------------------
1864                  
1865                endif
1866             endif                  !end "single" condition
1867     21      continue
1868          enddo                     !end loop over clusters
1869    
1870          if(DEBUG.EQ.1)
1871         $     print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1872    
1873    
1874     81   continue
1875                
1876        do ip=1,6        ncp_tot=0
1877          do ip=1,NPLANES
1878           ncp_tot = ncp_tot + ncp_plane(ip)           ncp_tot = ncp_tot + ncp_plane(ip)
1879        enddo        enddo
1880          if(DEBUG.EQ.1)
1881         $     print*,'n.couple tot:      ',ncp_tot
1882                
1883        return        return
1884        end        end
# Line 1933  c      double precision xm3,ym3,zm3 Line 1941  c      double precision xm3,ym3,zm3
1941  *     --------------------------------------------  *     --------------------------------------------
1942        do ip=1,nplanes        do ip=1,nplanes
1943           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  
1944              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7
1945              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7
1946           endif           endif
# Line 1945  c            mask_view(nviewy(ip)) = 8 Line 1951  c            mask_view(nviewy(ip)) = 8
1951        ntrpt=0                   !number of triplets        ntrpt=0                   !number of triplets
1952                
1953        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1
1954    c$$$         print*,'(1) ip ',ip1
1955    c$$$     $        ,mask_view(nviewx(ip1))
1956    c$$$     $        ,mask_view(nviewy(ip1))        
1957           if(  mask_view(nviewx(ip1)).ne.0 .or.           if(  mask_view(nviewx(ip1)).ne.0 .or.
1958       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
1959           do is1=1,2             !loop on sensors - COPPIA 1                       do is1=1,2             !loop on sensors - COPPIA 1            
1960              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
1961                 icx1=clx(ip1,icp1)                 icx1=clx(ip1,icp1)
1962                 icy1=cly(ip1,icp1)                 icy1=cly(ip1,icp1)
1963                  
1964    c$$$               print*,'(1) ip ',ip1,' icp ',icp1
1965    
1966  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
1967  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
1968                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
1969                 xm1=xPAM                 xm1=xPAM
1970                 ym1=yPAM                 ym1=yPAM
1971                 zm1=zPAM                                   zm1=zPAM                  
 c     print*,'***',is1,xm1,ym1,zm1  
1972    
1973                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
1974    c$$$                  print*,'(2) ip ',ip2
1975    c$$$     $                 ,mask_view(nviewx(ip2))
1976    c$$$     $                 ,mask_view(nviewy(ip2))
1977                    if(  mask_view(nviewx(ip2)).ne.0 .or.                    if(  mask_view(nviewx(ip2)).ne.0 .or.
1978       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
1979                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                                        do is2=1,2    !loop on sensors -ndblt COPPIA 2                    
1980                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
1981                          icx2=clx(ip2,icp2)                          icx2=clx(ip2,icp2)
1982                          icy2=cly(ip2,icp2)                          icy2=cly(ip2,icp2)
1983    
1984    c$$$                        print*,'(2) ip ',ip2,' icp ',icp2
1985    
1986  c                        call xyz_PAM  c                        call xyz_PAM
1987  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
1988  c                        call xyz_PAM  c                        call xyz_PAM
# Line 1975  c     $                       (icx2,icy2 Line 1992  c     $                       (icx2,icy2
1992                          xm2=xPAM                          xm2=xPAM
1993                          ym2=yPAM                          ym2=yPAM
1994                          zm2=zPAM                          zm2=zPAM
1995                                                    
1996    *                       ---------------------------------------------------
1997    *                       both couples must have a y-cluster
1998    *                       (condition necessary when in RECOVER_SINGLETS mode)
1999    *                       ---------------------------------------------------
2000                            if(icy1.eq.0.or.icy2.eq.0)goto 111
2001    
2002                            if(cl_used(icy1).ne.0)goto 111
2003                            if(cl_used(icy2).ne.0)goto 111
2004    
2005                            
2006  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2007  *     track parameters on Y VIEW  *     track parameters on Y VIEW
2008  *     (2 couples needed)  *     (2 couples needed)
# Line 1985  c     $                       (icx2,icy2 Line 2012  c     $                       (icx2,icy2
2012       $                          '** warning ** number of identified '//       $                          '** warning ** number of identified '//
2013       $                          'doublets exceeds vector dimention '       $                          'doublets exceeds vector dimention '
2014       $                          ,'( ',ndblt_max,' )'       $                          ,'( ',ndblt_max,' )'
2015  c                           good2=.false.  c     good2=.false.
2016  c                           goto 880 !fill ntp and go to next event  c     goto 880 !fill ntp and go to next event
2017                             do iv=1,12                             do iv=1,12
2018  c                              mask_view(iv) = 3  c     mask_view(iv) = 3
2019                                mask_view(iv) = mask_view(iv)+ 2**2                                mask_view(iv) = mask_view(iv)+ 2**2
2020                             enddo                             enddo
2021                             iflag=1                             iflag=1
2022                             return                             return
2023                          endif                          endif
2024                            
2025                            
2026    ccc                        print*,'<doublet> ',icp1,icp2
2027    
2028                          ndblt = ndblt + 1                          ndblt = ndblt + 1
2029  *     store doublet info  *     store doublet info
2030                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)
# Line 2002  c                              mask_view Line 2033  c                              mask_view
2033                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)
2034  *     y0 (cm)  *     y0 (cm)
2035                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1
2036                                                      
2037  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2038  ****  reject non phisical couples                    ****  ****  reject non phisical couples                    ****
2039  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2040                            if(SECOND_SEARCH)goto 111
2041                          if(                          if(
2042       $                       abs(alfayz2(ndblt)).gt.alfyz2_max       $                       abs(alfayz2(ndblt)).gt.alfyz2_max
2043       $                       .or.       $                       .or.
2044       $                       abs(alfayz1(ndblt)).gt.alfyz1_max       $                       abs(alfayz1(ndblt)).gt.alfyz1_max
2045       $                       )ndblt = ndblt-1       $                       )ndblt = ndblt-1
2046                                                    
2047  c$$$      if(iev.eq.33)then                          
2048  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$$$  
2049  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2050  *     track parameters on Y VIEW - end  *     track parameters on Y VIEW - end
2051  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2052    
2053    
2054                            if(icx1.ne.0)then
2055                               if(cl_used(icx1).ne.0)goto 31
2056                            endif
2057                            if(icx2.ne.0)then
2058                               if(cl_used(icx2).ne.0)goto 31
2059                            endif
2060    
2061                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2062    
2063                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2064    c$$$                           print*,'(3) ip ',ip3
2065    c$$$     $                          ,mask_view(nviewx(ip3))
2066    c$$$     $                          ,mask_view(nviewy(ip3))                          
2067                             if(  mask_view(nviewx(ip3)).ne.0 .or.                             if(  mask_view(nviewx(ip3)).ne.0 .or.
2068       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2069                             do is3=1,2 !loop on sensors - COPPIA 3                             do is3=1,2 !loop on sensors - COPPIA 3
# Line 2034  c$$$ Line 2071  c$$$
2071                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
2072                                   icx3=clx(ip3,icp3)                                   icx3=clx(ip3,icp3)
2073                                   icy3=cly(ip3,icp3)                                   icy3=cly(ip3,icp3)
2074    
2075    c$$$                                 print*,'(3) ip ',ip3,' icp ',icp3
2076    
2077    *     ---------------------------------------------------
2078    *     all three couples must have a x-cluster
2079    *     (condition necessary when in RECOVER_SINGLETS mode)
2080    *     ---------------------------------------------------
2081                                     if(
2082         $                                icx1.eq.0.or.
2083         $                                icx2.eq.0.or.
2084         $                                icx3.eq.0.or.
2085         $                                .false.)goto 29
2086                                    
2087                                     if(cl_used(icx1).ne.0)goto 29
2088                                     if(cl_used(icx2).ne.0)goto 29
2089                                     if(cl_used(icx3).ne.0)goto 29
2090    
2091  c                                 call xyz_PAM  c                                 call xyz_PAM
2092  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2093  c                                 call xyz_PAM  c                                 call xyz_PAM
# Line 2044  c     $                               (i Line 2098  c     $                               (i
2098                                   xm3=xPAM                                   xm3=xPAM
2099                                   ym3=yPAM                                   ym3=yPAM
2100                                   zm3=zPAM                                   zm3=zPAM
2101    
2102    
2103  *     find the circle passing through the three points  *     find the circle passing through the three points
2104  c$$$                                 call tricircle(3,xp,zp,angp,resp,chi                                   iflag_t = DEBUG
 c$$$     $                                ,xc,zc,radius,iflag)  
                                  iflag = DEBUG  
2105                                   call tricircle(3,xp,zp,angp,resp,chi                                   call tricircle(3,xp,zp,angp,resp,chi
2106       $                                ,xc,zc,radius,iflag)       $                                ,xc,zc,radius,iflag_t)
 c     print*,xc,zc,radius  
2107  *     the circle must intersect the reference plane  *     the circle must intersect the reference plane
2108                                   if(  cc                                 if(iflag.ne.0)goto 29
2109  c     $                                 (xc.le.-1.*xclimit.or.                                   if(iflag_t.ne.0)then
2110  c     $                                 xc.ge.xclimit).and.  *     if tricircle fails, evaluate a straight line
2111       $                                radius**2.ge.(ZINI-zc)**2.and.                                      if(DEBUG.eq.1)
2112       $                                iflag.eq.0.and.       $                                   print*,'TRICIRCLE failure'
2113       $                                .true.)then       $                                   ,' >>> straight line'
2114                                                                        radius=0.
2115                                        xc=0.
2116                                        yc=0.
2117                                        
2118                                        SZZ=0.                  
2119                                        SZX=0.
2120                                        SSX=0.
2121                                        SZ=0.
2122                                        S1=0.
2123                                        X0=0.
2124                                        Ax=0.
2125                                        BX=0.
2126                                        DO I=1,3
2127                                           XX = XP(I)
2128                                           SZZ=SZZ+ZP(I)*ZP(I)
2129                                           SZX=SZX+ZP(I)*XX
2130                                           SSX=SSX+XX
2131                                           SZ=SZ+ZP(I)
2132                                           S1=S1+1.
2133                                        ENDDO
2134                                        DET=SZZ*S1-SZ*SZ
2135                                        AX=(SZX*S1-SZ*SSX)/DET
2136                                        BX=(SZZ*SSX-SZX*SZ)/DET
2137                                        X0  = AX*ZINI+BX
2138                                        
2139                                     endif
2140    
2141                                     if(  .not.SECOND_SEARCH.and.
2142         $                                radius**2.lt.(ZINI-zc)**2)goto 29
2143                                                                      
2144  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2145  *     track parameters on X VIEW  *     track parameters on X VIEW
2146  *     (3 couples needed)  *     (3 couples needed)
2147  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2148                                   if(ntrpt.eq.ntrpt_max)then                                   if(ntrpt.eq.ntrpt_max)then
2149                                      if(verbose.eq.1)print*,                                      if(verbose.eq.1)print*,
2150       $                     '** warning ** number of identified '//       $                                   '** warning **'//
2151       $                     'triplets exceeds vector dimention '       $                                   ' number of identified '//
2152       $                    ,'( ',ntrpt_max,' )'       $                                   'triplets exceeds'//
2153  c                                    good2=.false.       $                                   ' vector dimention '
2154  c                                    goto 880 !fill ntp and go to next event       $                                   ,'( ',ntrpt_max,' )'
2155    c     good2=.false.
2156    c     goto 880 !fill ntp and go to next event
2157                                      do iv=1,nviews                                      do iv=1,nviews
2158  c                                       mask_view(iv) = 4  c     mask_view(iv) = 4
2159                                         mask_view(iv)=mask_view(iv)+ 2**3                                         mask_view(iv) =
2160         $                                      mask_view(iv)+ 2**3
2161                                      enddo                                      enddo
2162                                      iflag=1                                      iflag=1
2163                                      return                                      return
2164                                   endif                                   endif
2165    
2166    ccc                                 print*,'<triplet> ',icp1,icp2,icp3
2167                                    
2168                                   ntrpt = ntrpt +1                                   ntrpt = ntrpt +1
2169  *     store triplet info  *     store triplet info
2170                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)
2171                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)
2172                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)
2173                                                                    
2174                                   if(xc.lt.0)then                                   if(radius.ne.0.and.xc.lt.0)then
2175  *************POSITIVE DEFLECTION  *************POSITIVE DEFLECTION
2176                alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)
2177                alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2178                alfaxz3(ntrpt) = 1/radius               alfaxz3(ntrpt) = 1/radius
2179                                   else                                  else if(radius.ne.0.and.xc.ge.0)then
2180  *************NEGATIVE DEFLECTION  *************NEGATIVE DEFLECTION
2181                alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)
2182                alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2183                alfaxz3(ntrpt) = -1/radius               alfaxz3(ntrpt) = -1/radius
2184                                   endif                                  else if(radius.eq.0)then
2185                                    *************straight fit
2186                 alfaxz1(ntrpt) = X0
2187                 alfaxz2(ntrpt) = AX
2188                 alfaxz3(ntrpt) = 0.
2189                                    endif
2190    
2191    c$$$                                print*,'alfaxz1 ', alfaxz1(ntrpt)
2192    c$$$                                print*,'alfaxz2 ', alfaxz2(ntrpt)
2193    c$$$                                print*,'alfaxz3 ', alfaxz3(ntrpt)
2194                                        
2195  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2196  ****  reject non phisical triplets                   ****  ****  reject non phisical triplets                   ****
2197  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2198                                   if(                                  if(SECOND_SEARCH)goto 29
2199       $                                abs(alfaxz2(ntrpt)).gt.alfxz2_max                                  if(
2200       $                                .or.       $                               abs(alfaxz2(ntrpt)).gt.
2201       $                                abs(alfaxz1(ntrpt)).gt.alfxz1_max       $                               alfxz2_max
2202       $                                )ntrpt = ntrpt-1       $                               .or.
2203                                         $                               abs(alfaxz1(ntrpt)).gt.
2204                                         $                               alfxz1_max
2205  c     print*,alfaxz1(ntrpt),alfaxz2(ntrpt),alfaxz3(ntrpt)       $                               )ntrpt = ntrpt-1
2206                                                                    
2207  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2208  *     track parameters on X VIEW - end  *     track parameters on X VIEW - end
2209  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2210                                endif                                
2211     29                           continue
2212                             enddo !end loop on COPPIA 3                             enddo !end loop on COPPIA 3
2213                          enddo   !end loop on sensors - COPPIA 3                          enddo   !end loop on sensors - COPPIA 3
2214   30                     continue   30                     continue
2215                       enddo      !end loop on planes  - COPPIA 3                       enddo      !end loop on planes  - COPPIA 3
2216   31                  continue  
2217                         31                  continue                    
2218   1                enddo         !end loop on COPPIA 2  c 1                enddo         !end loop on COPPIA 2
2219                     enddo         !end loop on COPPIA 2
2220                 enddo            !end loop on sensors - COPPIA 2                 enddo            !end loop on sensors - COPPIA 2
2221   20            continue   20            continue
2222              enddo               !end loop on planes  - COPPIA 2              enddo               !end loop on planes  - COPPIA 2
2223                
2224    c 11         continue
2225              continue
2226           enddo                  !end loop on COPPIA1           enddo                  !end loop on COPPIA1
2227        enddo                     !end loop on sensors - COPPIA 1        enddo                     !end loop on sensors - COPPIA 1
2228   10   continue   10   continue
# Line 2192  c      include 'momanhough_init.f' Line 2294  c      include 'momanhough_init.f'
2294        do idb1=1,ndblt           !loop (1) on DOUBLETS        do idb1=1,ndblt           !loop (1) on DOUBLETS
2295           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
2296                            
 c     print*,'--------------'  
 c     print*,'** ',idb1,' **'  
               
2297           do icp=1,ncp_tot           do icp=1,ncp_tot
2298              cp_useds1(icp)=0    !init              cp_useds1(icp)=0    !init
2299              cp_useds2(icp)=0    !init              cp_useds2(icp)=0    !init
# Line 2230  ccccc if(db_used(idbref).eq.1)goto 1188 Line 2329  ccccc if(db_used(idbref).eq.1)goto 1188
2329  *     doublet distance in parameter space  *     doublet distance in parameter space
2330                 distance=                 distance=
2331       $              ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2       $              ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2
2332       $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2                     $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2
2333                 distance = sqrt(distance)                 distance = sqrt(distance)
2334                                
 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  
2335                 if(distance.lt.cutdistyz)then                 if(distance.lt.cutdistyz)then
2336    
 c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  
2337                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1
2338                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1
2339                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1
# Line 2258  c     print*,idb1,idb2,distance,' cloud Line 2349  c     print*,idb1,idb2,distance,' cloud
2349    
2350                    temp1 = temp1 + alfayz1(idb2)                    temp1 = temp1 + alfayz1(idb2)
2351                    temp2 = temp2 + alfayz2(idb2)                    temp2 = temp2 + alfayz2(idb2)
 c     print*,'*   idbref,idb2 ',idbref,idb2  
2352                 endif                               endif              
2353                                
2354   1118          continue   1118          continue
2355              enddo               !end loop (2) on DOUBLETS              enddo               !end loop (2) on DOUBLETS
2356                            
2357   1188       continue  c 1188       continue
2358                continue
2359           enddo                  !end loop on... bo?           enddo                  !end loop on... bo?
2360                    
2361           nptloop=npv           nptloop=npv
# Line 2281  c     print*,'*   idbref,idb2 ',idbref,i Line 2372  c     print*,'*   idbref,idb2 ',idbref,i
2372           enddo           enddo
2373           ncpused=0           ncpused=0
2374           do icp=1,ncp_tot           do icp=1,ncp_tot
2375              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2376         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2377         $           .true.)then
2378                 ncpused=ncpused+1                 ncpused=ncpused+1
2379                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2380                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2291  c     print*,'*   idbref,idb2 ',idbref,i Line 2384  c     print*,'*   idbref,idb2 ',idbref,i
2384           do ip=1,nplanes           do ip=1,nplanes
2385              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2386           enddo           enddo
2387  c     print*,'>>>> ',ncpused,npt,nplused          
 c         if(ncpused.lt.ncpyz_min)goto 2228 !next doublet  
          if(npt.lt.nptyz_min)goto 2228 !next doublet  
2388           if(nplused.lt.nplyz_min)goto 2228 !next doublet           if(nplused.lt.nplyz_min)goto 2228 !next doublet
2389                    
2390  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2325  c               mask_view(iv) = 5 Line 2416  c               mask_view(iv) = 5
2416  c     ptcloud_yz_nt(nclouds_yz)=npt  c     ptcloud_yz_nt(nclouds_yz)=npt
2417           do ipt=1,npt           do ipt=1,npt
2418              db_cloud(npt_tot+ipt) = db_all(ipt)              db_cloud(npt_tot+ipt) = db_all(ipt)
 c     print*,'>> ',ipt,db_all(ipt)  
2419           enddo             enddo  
2420           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2421           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2422              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2423              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)
2424              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)
# Line 2338  c     print*,'>> ',ipt,db_all(ipt) Line 2427  c     print*,'>> ',ipt,db_all(ipt)
2427              print*,'cpcloud_yz '              print*,'cpcloud_yz '
2428       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)
2429              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)  
2430           endif           endif
2431  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2432  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2356  c$$$     $           ,(db_cloud(iii),iii Line 2441  c$$$     $           ,(db_cloud(iii),iii
2441        endif                            endif                    
2442                
2443        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2444           print*,'Y-Z total clouds ',nclouds_yz           print*,'Y-Z total clouds ',nclouds_yz
          print*,' '  
2445        endif        endif
2446                
2447                
# Line 2421  c      include 'momanhough_init.f' Line 2504  c      include 'momanhough_init.f'
2504   91   continue                     91   continue                  
2505        do itr1=1,ntrpt           !loop (1) on TRIPLETS        do itr1=1,ntrpt           !loop (1) on TRIPLETS
2506           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,' **'  
2507                    
2508           do icp=1,ncp_tot           do icp=1,ncp_tot
2509              cp_useds1(icp)=0              cp_useds1(icp)=0
# Line 2456  c         tr_temp(1)=itr1 Line 2537  c         tr_temp(1)=itr1
2537              do itr2=1,ntrpt     !loop (2) on TRIPLETS              do itr2=1,ntrpt     !loop (2) on TRIPLETS
2538                 if(itr2.eq.itr1)goto 11188       !next triplet                 if(itr2.eq.itr1)goto 11188       !next triplet
2539                 if(tr_used(itr2).eq.1)goto 11188 !next triplet                               if(tr_used(itr2).eq.1)goto 11188 !next triplet              
2540    
2541    
2542  *     triplet distance in parameter space  *     triplet distance in parameter space
2543  *     solo i due parametri spaziali per il momemnto  *     solo i due parametri spaziali per il momemnto
2544                 distance=                 distance=
2545       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2
2546       $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2                     $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2
2547                 distance = sqrt(distance)                 distance = sqrt(distance)
2548                  
2549    
2550  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
2551  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE
2552  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
# Line 2475  c         tr_temp(1)=itr1 Line 2559  c         tr_temp(1)=itr1
2559       $              .true.)istrimage=1       $              .true.)istrimage=1
2560    
2561                 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  
2562                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2563                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
2564                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1
# Line 2494  c     print*,idb1,idb2,distance,' cloud Line 2577  c     print*,idb1,idb2,distance,' cloud
2577                    temp1 = temp1 + alfaxz1(itr2)                    temp1 = temp1 + alfaxz1(itr2)
2578                    temp2 = temp2 + alfaxz2(itr2)                    temp2 = temp2 + alfaxz2(itr2)
2579                    temp3 = temp3 + alfaxz3(itr2)                    temp3 = temp3 + alfaxz3(itr2)
 c     print*,'*   itrref,itr2 ',itrref,itr2,distance  
2580                 endif                               endif              
2581                                
2582  11188          continue  11188          continue
2583              enddo               !end loop (2) on TRIPLETS              enddo               !end loop (2) on TRIPLETS
2584                                                
2585  11888       continue  c11888       continue
2586                continue
2587           enddo                  !end loop on... bo?               enddo                  !end loop on... bo?    
2588                    
2589           nptloop=npv           nptloop=npv
# Line 2515  c     print*,'*   itrref,itr2 ',itrref,i Line 2598  c     print*,'*   itrref,itr2 ',itrref,i
2598  *     1bis)  *     1bis)
2599  *     2) it is not already stored  *     2) it is not already stored
2600  *     ------------------------------------------  *     ------------------------------------------
 c     print*,'check cp_used'  
2601           do ip=1,nplanes           do ip=1,nplanes
2602              hit_plane(ip)=0              hit_plane(ip)=0
2603           enddo           enddo
2604           ncpused=0           ncpused=0
2605           do icp=1,ncp_tot           do icp=1,ncp_tot
2606              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2607         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2608         $           .true.)then
2609                 ncpused=ncpused+1                 ncpused=ncpused+1
2610                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2611                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2531  c     print*,'check cp_used' Line 2615  c     print*,'check cp_used'
2615           do ip=1,nplanes           do ip=1,nplanes
2616              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2617           enddo           enddo
 c         if(ncpused.lt.ncpxz_min)goto 22288 !next triplet  
          if(npt.lt.nptxz_min)goto 22288     !next triplet  
2618           if(nplused.lt.nplxz_min)goto 22288 !next triplet           if(nplused.lt.nplxz_min)goto 22288 !next triplet
2619                    
2620  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2566  c               mask_view(iv) = 6 Line 2648  c               mask_view(iv) = 6
2648           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2649                    
2650           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
2651              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'              print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'
             print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'                
2652              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)
2653              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)
2654              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)
# Line 2576  c               mask_view(iv) = 6 Line 2657  c               mask_view(iv) = 6
2657              print*,'cpcloud_xz '              print*,'cpcloud_xz '
2658       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)
2659              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)  
2660           endif           endif
2661  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2662  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2593  c$$$     $           ,(tr_cloud(iii),iii Line 2670  c$$$     $           ,(tr_cloud(iii),iii
2670         endif                             endif                    
2671                
2672        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2673           print*,'X-Z total clouds ',nclouds_xz           print*,'X-Z total clouds ',nclouds_xz
          print*,' '  
2674        endif        endif
2675                
2676                
# Line 2651  c$$$     $           ,(tr_cloud(iii),iii Line 2726  c$$$     $           ,(tr_cloud(iii),iii
2726    
2727        ntracks=0                 !counter of track candidates        ntracks=0                 !counter of track candidates
2728                
2729        do iyz=1,nclouds_yz       !loop on YZ couds        do iyz=1,nclouds_yz       !loop on YZ clouds
2730           do ixz=1,nclouds_xz    !loop on XZ couds           do ixz=1,nclouds_xz    !loop on XZ clouds
2731                            
2732  *     --------------------------------------------------  *     --------------------------------------------------
2733  *     check of consistency of the clouds  *     check of consistency of the clouds
# Line 2661  c$$$     $           ,(tr_cloud(iii),iii Line 2736  c$$$     $           ,(tr_cloud(iii),iii
2736  *     of the two clouds  *     of the two clouds
2737  *     --------------------------------------------------  *     --------------------------------------------------
2738              do ip=1,nplanes              do ip=1,nplanes
2739                 hit_plane(ip)=0                 hit_plane(ip)=0  !n.matching couples (REAL couples, not SINGLETS)
2740                 ncp_match(ip)=0                 ncp_match(ip)=0  !n.matching couples per plane
2741                 do icpp=1,ncouplemax                 do icpp=1,ncouplemax
2742                    cp_match(ip,icpp)=0 !init couple list                    cp_match(ip,icpp)=0 !init couple list
2743                 enddo                 enddo
2744              enddo              enddo
2745              ncp_ok=0              ncp_ok=0            !count n.matching-couples
2746                ncpx_ok=0           !count n.matching-couples with x cluster
2747                ncpy_ok=0           !count n.matching-couples with y cluster
2748    
2749    
2750              do icp=1,ncp_tot    !loop over couples              do icp=1,ncp_tot    !loop over couples
2751  *     get info on  
2752                 cpintersec(icp)=min(                 if(.not.RECOVER_SINGLETS)then
2753       $              cpcloud_yz(iyz,icp),  *     ------------------------------------------------------
2754       $              cpcloud_xz(ixz,icp))  *     if NOT in RECOVER_SINGLETS mode, take the intersection
2755                 if(  *     between xz yz clouds
2756       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.  *     ------------------------------------------------------
2757       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.                    cpintersec(icp)=min(
2758       $              .false.)cpintersec(icp)=0       $                 cpcloud_yz(iyz,icp),
2759         $                 cpcloud_xz(ixz,icp))
2760  *     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
2761    *     ------------------------------------------------------
2762    *     discard the couple if the sensor is in conflict
2763    *     ------------------------------------------------------
2764                      if(
2765         $       (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2766         $       (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2767         $                 .false.)cpintersec(icp)=0
2768                   else
2769    *     ------------------------------------------------------
2770    *     if RECOVER_SINGLETS take the union
2771    *     (otherwise the fake couples formed by singlets would be
2772    *     discarded)    
2773    *     ------------------------------------------------------
2774                      cpintersec(icp)=max(
2775         $                 cpcloud_yz(iyz,icp),
2776         $                 cpcloud_xz(ixz,icp))
2777    c$$$                  if(cpcloud_yz(iyz,icp).gt.0)
2778    c$$$     $                 cpintersec(icp)=cpcloud_yz(iyz,icp)
2779    *     cpintersec is >0 if either yz or xz cloud contains the couple icp
2780                   endif
2781    
2782    c$$$               print*,icp,ip_cp(icp),' -- ',cpintersec(icp)
2783    
2784                 if(cpintersec(icp).ne.0)then                 if(cpintersec(icp).ne.0)then
                   ncp_ok=ncp_ok+1    
2785                                        
2786                    ip=ip_cp(icp)                    ip=ip_cp(icp)
2787                    hit_plane(ip)=1                    hit_plane(ip)=1
2788    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).gt.0)
2789    c$$$     $                 ncp_ok=ncp_ok+1  
2790    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).eq.0)
2791    c$$$     $                 ncpx_ok=ncpx_ok+1
2792    c$$$                  if(clx(ip,icp).eq.0.and.cly(ip,icp).gt.0)
2793    c$$$     $                 ncpy_ok=ncpy_ok+1
2794    
2795                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2796         $                 cpcloud_xz(ixz,icp).gt.0)
2797         $                 ncp_ok=ncp_ok+1  
2798                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2799         $                 cpcloud_xz(ixz,icp).eq.0)
2800         $                 ncpy_ok=ncpy_ok+1  
2801                      if(  cpcloud_yz(iyz,icp).eq.0.and.
2802         $                 cpcloud_xz(ixz,icp).gt.0)
2803         $                 ncpx_ok=ncpx_ok+1  
2804    
2805                    if(cpintersec(icp).eq.1)then                    if(cpintersec(icp).eq.1)then
2806  *     1) only the couple image in sensor 1 matches  *     1) only the couple image in sensor 1 matches
2807                       id=-icp                       id=-icp
# Line 2709  c$$$     $           ,(tr_cloud(iii),iii Line 2828  c$$$     $           ,(tr_cloud(iii),iii
2828              do ip=1,nplanes              do ip=1,nplanes
2829                 nplused=nplused+ hit_plane(ip)                 nplused=nplused+ hit_plane(ip)
2830              enddo              enddo
2831                                        
2832                            if(nplused.lt.3)goto 888 !next combination
2833    ccc            if(nplused.lt.nplxz_min)goto 888 !next combination
2834    ccc            if(nplused.lt.nplyz_min)goto 888 !next combination
2835    *     -----------------------------------------------------------
2836    *     if in RECOVER_SINGLET mode, the two clouds must have
2837    *     at least ONE intersecting real couple
2838    *     -----------------------------------------------------------
2839                if(ncp_ok.lt.1)goto 888 !next combination
2840    
2841              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
2842                 print*,'Combination ',iyz,ixz                 print*,'////////////////////////////'
2843       $              ,' db ',ptcloud_yz(iyz)                 print*,'Cloud combination (Y,X): ',iyz,ixz
2844       $              ,' tr ',ptcloud_xz(ixz)                 print*,' db ',ptcloud_yz(iyz)
2845       $              ,'  -----> # matching couples ',ncp_ok                 print*,' tr ',ptcloud_xz(ixz)
2846              endif                 print*,'  -----> # matching couples ',ncp_ok
2847                   print*,'  -----> # fake couples (X)',ncpx_ok
2848  c            if(nplused.lt.nplxz_min)goto 888 !next combination                 print*,'  -----> # fake couples (Y)',ncpy_ok
2849              if(nplused.lt.nplyz_min)goto 888 !next combination                 do icp=1,ncp_tot
2850              if(ncp_ok.lt.ncpok)goto 888 !next combination                    print*,'cp ',icp,' >'
2851         $                 ,' x ',cpcloud_xz(ixz,icp)
2852  c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'       $                 ,' y ',cpcloud_yz(iyz,icp)
2853  c$$$  print*,'Configurazione cluster XZ'       $                 ,' ==> ',cpintersec(icp)
2854  c$$$  print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))                 enddo
2855  c$$$  print*,'2 -- ',(clx(2,i),i=1,ncp_plane(1))              endif
 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  
2856                                                    
2857              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
                print*,'track candidate', ntracks+1  
2858                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2859                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2860                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
# Line 2801  c$$$            if(AL_INI(5).gt.defmax)g Line 2887  c$$$            if(AL_INI(5).gt.defmax)g
2887                                hit_plane(6)=icp6                                hit_plane(6)=icp6
2888                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
2889                                                                
2890                                  if(DEBUG.eq.1)
2891         $                             print*,'combination: '
2892         $                             ,cp_match(6,icp1)
2893         $                             ,cp_match(5,icp2)
2894         $                             ,cp_match(4,icp3)
2895         $                             ,cp_match(3,icp4)
2896         $                             ,cp_match(2,icp5)
2897         $                             ,cp_match(1,icp6)
2898    
2899    
2900  *                             ---------------------------------------  *                             ---------------------------------------
2901  *                             check if this group of couples has been  *                             check if this group of couples has been
2902  *                             already fitted      *                             already fitted    
# Line 2849  c     $                                 Line 2945  c     $                                
2945       $                                   PFAdef,PFAdef,0.,0.,0.,0.)       $                                   PFAdef,PFAdef,0.,0.,0.,0.)
2946  *                                   *************************  *                                   *************************
2947  *                                   -----------------------------  *                                   -----------------------------
2948                                      xgood(nplanes-ip+1)=1.                                      if(icx.gt.0.and.icy.gt.0)then
2949                                      ygood(nplanes-ip+1)=1.                                         xgood(nplanes-ip+1)=1.
2950                                      xm(nplanes-ip+1)=xPAM                                         ygood(nplanes-ip+1)=1.
2951                                      ym(nplanes-ip+1)=yPAM                                         xm(nplanes-ip+1)=xPAM
2952                                      zm(nplanes-ip+1)=zPAM                                         ym(nplanes-ip+1)=yPAM
2953                                      resx(nplanes-ip+1)=resxPAM                                         zm(nplanes-ip+1)=zPAM
2954                                      resy(nplanes-ip+1)=resyPAM                                         resx(nplanes-ip+1)=resxPAM
2955                                           resy(nplanes-ip+1)=resyPAM
2956                                           if(DEBUG.EQ.1)print*,'(X,Y)'
2957         $                                      ,nplanes-ip+1,xPAM,yPAM
2958                                        else
2959                                           xm_A(nplanes-ip+1) = xPAM_A
2960                                           ym_A(nplanes-ip+1) = yPAM_A
2961                                           xm_B(nplanes-ip+1) = xPAM_B
2962                                           ym_B(nplanes-ip+1) = yPAM_B
2963                                           zm(nplanes-ip+1)
2964         $                                      = (zPAM_A+zPAM_B)/2.
2965                                           resx(nplanes-ip+1) = resxPAM
2966                                           resy(nplanes-ip+1) = resyPAM
2967                                           if(icx.eq.0.and.icy.gt.0)then
2968                                              xgood(nplanes-ip+1)=0.
2969                                              ygood(nplanes-ip+1)=1.
2970                                              resx(nplanes-ip+1) = 1000.
2971                                              if(DEBUG.EQ.1)print*,'(  Y)'
2972         $                                         ,nplanes-ip+1,xPAM,yPAM
2973                                           elseif(icx.gt.0.and.icy.eq.0)then
2974                                              xgood(nplanes-ip+1)=1.
2975                                              ygood(nplanes-ip+1)=0.
2976                                              if(DEBUG.EQ.1)print*,'(X  )'
2977         $                                         ,nplanes-ip+1,xPAM,yPAM
2978                                              resy(nplanes-ip+1) = 1000.
2979                                           else
2980                                              print*,'both icx=0 and icy=0'
2981         $                                         ,' ==> IMPOSSIBLE!!'
2982                                           endif
2983                                        endif
2984  *                                   -----------------------------  *                                   -----------------------------
2985                                   endif                                   endif
2986                                enddo !end loop on planes                                enddo !end loop on planes
# Line 2896  c                                 chi2=- Line 3021  c                                 chi2=-
3021  *     **********************************************************  *     **********************************************************
3022    
3023                                if(chi2.le.0.)goto 666                                              if(chi2.le.0.)goto 666              
3024                                  if(chi2.ge.1.e08)goto 666 !OPTIMIZATION
3025                                  if(chi2.ne.chi2)goto 666  !OPTIMIZATION
3026    
3027  *     --------------------------  *     --------------------------
3028  *     STORE candidate TRACK INFO  *     STORE candidate TRACK INFO
# Line 2922  c                                    mas Line 3049  c                                    mas
3049    
3050                                   XV_STORE(ip,ntracks)=sngl(xv(ip))                                   XV_STORE(ip,ntracks)=sngl(xv(ip))
3051                                   YV_STORE(ip,ntracks)=sngl(yv(ip))                                   YV_STORE(ip,ntracks)=sngl(yv(ip))
3052                                   ZV_STORE(ip,ntracks)=sngl(zv(ip))                                                                       ZV_STORE(ip,ntracks)=sngl(zv(ip))
3053                                   XM_STORE(ip,ntracks)=sngl(xm(ip))                                   XM_STORE(ip,ntracks)=sngl(xm(ip))
3054                                   YM_STORE(ip,ntracks)=sngl(ym(ip))                                   YM_STORE(ip,ntracks)=sngl(ym(ip))
3055                                   ZM_STORE(ip,ntracks)=sngl(zm(ip))                                   ZM_STORE(ip,ntracks)=sngl(zm(ip))
# Line 2941  c                                    mas Line 3068  c                                    mas
3068       $                                   cp_match(ip,hit_plane(ip))       $                                   cp_match(ip,hit_plane(ip))
3069                                      SENSOR_STORE(nplanes-ip+1,ntracks)                                      SENSOR_STORE(nplanes-ip+1,ntracks)
3070       $                              = is_cp(cp_match(ip,hit_plane(ip)))       $                              = is_cp(cp_match(ip,hit_plane(ip)))
3071                                      LADDER_STORE(nplanes-ip+1,ntracks)                                      
3072       $                                   = LADDER(                                      icl=
3073       $                                   clx(ip,icp_cp(       $                                   clx(ip,icp_cp(
3074       $                                   cp_match(ip,hit_plane(ip)       $                                   cp_match(ip,hit_plane(ip)
3075       $                                   ))));       $                                   )));
3076                                        if(icl.eq.0)
3077         $                                   icl=
3078         $                                   cly(ip,icp_cp(
3079         $                                   cp_match(ip,hit_plane(ip)
3080         $                                   )));
3081    
3082                                        LADDER_STORE(nplanes-ip+1,ntracks)
3083         $                                   = LADDER(icl);
3084                                   else                                   else
3085                                      CP_STORE(nplanes-ip+1,ntracks)=0                                      CP_STORE(nplanes-ip+1,ntracks)=0
3086                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0
# Line 2979  c                                    mas Line 3114  c                                    mas
3114                
3115        if(ntracks.eq.0)then        if(ntracks.eq.0)then
3116           iflag=1           iflag=1
3117           return  cc         return
3118        endif        endif
3119                
 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  
3120        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
3121          print*,'****** TRACK CANDIDATES *****************'          print*,'****** TRACK CANDIDATES *****************'
3122          print*,'#         R. chi2        RIG         ndof'          print*,'#         R. chi2        RIG         ndof'
# Line 3052  c$$$      endif Line 3178  c$$$      endif
3178        call track_init        call track_init
3179        do ip=1,nplanes           !loop on planes        do ip=1,nplanes           !loop on planes
3180    
3181             if(DEBUG.EQ.1)print*,' ........... plane ',ip,' ........... '
3182    
3183           xP=XV_STORE(nplanes-ip+1,ibest)           xP=XV_STORE(nplanes-ip+1,ibest)
3184           yP=YV_STORE(nplanes-ip+1,ibest)           yP=YV_STORE(nplanes-ip+1,ibest)
3185           zP=ZV_STORE(nplanes-ip+1,ibest)           zP=ZV_STORE(nplanes-ip+1,ibest)
# Line 3068  c$$$         bxyz(3)=0 Line 3196  c$$$         bxyz(3)=0
3196  *     using improved PFAs  *     using improved PFAs
3197  *     -------------------------------------------------  *     -------------------------------------------------
3198  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3199           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.  c$$$         if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
3200    c$$$     $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3201    c$$$            
3202    c$$$            id=CP_STORE(nplanes-ip+1,ibest)
3203    c$$$            
3204    c$$$            is=is_cp(id)
3205    c$$$            icp=icp_cp(id)
3206    c$$$            if(ip_cp(id).ne.ip)
3207    c$$$     $           print*,'OKKIO!!'
3208    c$$$     $           ,'id ',id,is,icp
3209    c$$$     $           ,ip_cp(id),ip
3210    c$$$            icx=clx(ip,icp)
3211    c$$$            icy=cly(ip,icp)
3212    c$$$c            call xyz_PAM(icx,icy,is,
3213    c$$$c     $           PFA,PFA,
3214    c$$$c     $           AXV_STORE(nplanes-ip+1,ibest),
3215    c$$$c     $           AYV_STORE(nplanes-ip+1,ibest))
3216    c$$$            call xyz_PAM(icx,icy,is,
3217    c$$$     $           PFA,PFA,
3218    c$$$     $           AXV_STORE(nplanes-ip+1,ibest),
3219    c$$$     $           AYV_STORE(nplanes-ip+1,ibest),
3220    c$$$     $           bxyz(1),
3221    c$$$     $           bxyz(2)
3222    c$$$     $           )
3223    c$$$
3224    c$$$            xm(nplanes-ip+1) = xPAM
3225    c$$$            ym(nplanes-ip+1) = yPAM
3226    c$$$            zm(nplanes-ip+1) = zPAM
3227    c$$$            xgood(nplanes-ip+1) = 1
3228    c$$$            ygood(nplanes-ip+1) = 1
3229    c$$$            resx(nplanes-ip+1) = resxPAM
3230    c$$$            resy(nplanes-ip+1) = resyPAM
3231    c$$$
3232    c$$$            dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3233    c$$$            dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3234             if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..or.
3235       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3236                            
3237              id=CP_STORE(nplanes-ip+1,ibest)              id=CP_STORE(nplanes-ip+1,ibest)
# Line 3093  c     $           AYV_STORE(nplanes-ip+1 Line 3256  c     $           AYV_STORE(nplanes-ip+1
3256       $           bxyz(2)       $           bxyz(2)
3257       $           )       $           )
3258    
3259              xm(nplanes-ip+1) = xPAM              if(icx.gt.0.and.icy.gt.0)then
3260              ym(nplanes-ip+1) = yPAM                 xm(nplanes-ip+1) = xPAM
3261              zm(nplanes-ip+1) = zPAM                 ym(nplanes-ip+1) = yPAM
3262              xgood(nplanes-ip+1) = 1                 zm(nplanes-ip+1) = zPAM
3263              ygood(nplanes-ip+1) = 1                 xm_A(nplanes-ip+1) = 0.
3264              resx(nplanes-ip+1) = resxPAM                 ym_A(nplanes-ip+1) = 0.
3265              resy(nplanes-ip+1) = resyPAM                 xm_B(nplanes-ip+1) = 0.
3266                   ym_B(nplanes-ip+1) = 0.
3267              dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))                 xgood(nplanes-ip+1) = 1
3268              dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))                 ygood(nplanes-ip+1) = 1
3269                   resx(nplanes-ip+1) = resxPAM
3270                   resy(nplanes-ip+1) = resyPAM
3271                   dedxtrk_x(nplanes-ip+1)=
3272         $              sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3273                   dedxtrk_y(nplanes-ip+1)=
3274         $              sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3275                else
3276                   xm(nplanes-ip+1) = 0.
3277                   ym(nplanes-ip+1) = 0.
3278                   zm(nplanes-ip+1) = (zPAM_A+zPAM_B)/2.
3279                   xm_A(nplanes-ip+1) = xPAM_A
3280                   ym_A(nplanes-ip+1) = yPAM_A
3281                   xm_B(nplanes-ip+1) = xPAM_B
3282                   ym_B(nplanes-ip+1) = yPAM_B
3283                   xgood(nplanes-ip+1) = 0
3284                   ygood(nplanes-ip+1) = 0
3285                   resx(nplanes-ip+1) = 1000.!resxPAM
3286                   resy(nplanes-ip+1) = 1000.!resyPAM
3287                   dedxtrk_x(nplanes-ip+1)= 0
3288                   dedxtrk_y(nplanes-ip+1)= 0
3289                   if(icx.gt.0)then
3290                      xgood(nplanes-ip+1) = 1
3291                      resx(nplanes-ip+1) = resxPAM
3292                      dedxtrk_x(nplanes-ip+1)=
3293         $                 sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3294                   elseif(icy.gt.0)then
3295                      ygood(nplanes-ip+1) = 1
3296                      resy(nplanes-ip+1) = resyPAM
3297                      dedxtrk_y(nplanes-ip+1)=
3298         $                 sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3299                   endif
3300                endif
3301                            
3302  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3303  *     -------------------------------------------------  *     -------------------------------------------------
# Line 3114  c     $           AYV_STORE(nplanes-ip+1 Line 3309  c     $           AYV_STORE(nplanes-ip+1
3309                                
3310              xgood(nplanes-ip+1)=0              xgood(nplanes-ip+1)=0
3311              ygood(nplanes-ip+1)=0              ygood(nplanes-ip+1)=0
3312    
3313                CP_STORE(nplanes-ip+1,ibest)=0 !re-init
3314                CLS_STORE(nplanes-ip+1,ibest)=0
3315    
3316                                
3317  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3318  *     determine which ladder and sensor are intersected by the track  *     determine which ladder and sensor are intersected by the track
# Line 3136  c     $           AYV_STORE(nplanes-ip+1 Line 3335  c     $           AYV_STORE(nplanes-ip+1
3335  *     ===========================================  *     ===========================================
3336  *     STEP 1 >>>>>>>  try to include a new couple  *     STEP 1 >>>>>>>  try to include a new couple
3337  *     ===========================================  *     ===========================================
3338  c            if(DEBUG.EQ.1)print*,'>>>> try to include a new couple'              distmin=100000000.
             distmin=1000000.  
3339              xmm = 0.              xmm = 0.
3340              ymm = 0.              ymm = 0.
3341              zmm = 0.              zmm = 0.
# Line 3150  c            if(DEBUG.EQ.1)print*,'>>>> Line 3348  c            if(DEBUG.EQ.1)print*,'>>>>
3348              do icp=1,ncp_plane(ip) !loop on couples on plane icp              do icp=1,ncp_plane(ip) !loop on couples on plane icp
3349                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3350                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3351                   if(icx.eq.0.or.icy.eq.0)goto 1188!if fake couple, jump to next
3352                 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
3353  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
3354  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
3355       $              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
3356       $              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
3357       $              .false.)goto 1188 !then jump to next couple.       $              .false.)goto 1188 !then jump to next couple.
3358  *            *          
3359                 call xyz_PAM(icx,icy,ist,                 call xyz_PAM(icx,icy,ist,
# Line 3168  c     $              cl_used(icy).eq.1.o Line 3367  c     $              cl_used(icy).eq.1.o
3367                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3368  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3369                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3370                 if(DEBUG.EQ.1)print*,'( couple ',id                 if(DEBUG.EQ.1)
3371         $              print*,'( couple ',id
3372       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3373                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3374                    xmm = xPAM                    xmm = xPAM
# Line 3180  c               distance = distance / RC Line 3380  c               distance = distance / RC
3380                    idm = id                                      idm = id                  
3381                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3382                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3383  c     QUIQUI --> non devo moltiplicare per clinc?!?!?!                    clincnewc=10*sqrt(rymm**2+rxmm**2
3384                    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  
3385                 endif                 endif
3386   1188          continue   1188          continue
3387              enddo               !end loop on couples on plane icp              enddo               !end loop on couples on plane icp
3388  c            if(distmin.le.clinc)then     !QUIQUI                            if(distmin.le.clincnewc)then    
             if(distmin.le.clincnewc)then     !QUIQUI                
3389  *              -----------------------------------  *              -----------------------------------
3390                 xm(nplanes-ip+1) = xmm !<<<                 xm(nplanes-ip+1) = xmm !<<<
3391                 ym(nplanes-ip+1) = ymm !<<<                 ym(nplanes-ip+1) = ymm !<<<
# Line 3201  c            if(distmin.le.clinc)then   Line 3399  c            if(distmin.le.clinc)then  
3399  *              -----------------------------------  *              -----------------------------------
3400                 CP_STORE(nplanes-ip+1,ibest)=idm                       CP_STORE(nplanes-ip+1,ibest)=idm      
3401                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm
3402       $              ,' (dist.= ',distmin,', cut ',clinc,' )'       $              ,' (dist.= ',distmin,', cut ',clincnewc,' )'
3403                 goto 133         !next plane                 goto 133         !next plane
3404              endif              endif
3405  *     ================================================  *     ================================================
3406  *     STEP 2 >>>>>>>  try to include a single cluster  *     STEP 2 >>>>>>>  try to include a single cluster
3407  *                     either from a couple or single  *                     either from a couple or single
3408  *     ================================================  *     ================================================
 c            if(DEBUG.EQ.1)print*,'>>>> try to include a new cluster'  
3409              distmin=1000000.              distmin=1000000.
3410              xmm_A = 0.          !---------------------------              xmm_A = 0.          !---------------------------
3411              ymm_A = 0.          ! init variables that              ymm_A = 0.          ! init variables that
# Line 3227  c            if(DEBUG.EQ.1)print*,'>>>> Line 3424  c            if(DEBUG.EQ.1)print*,'>>>>
3424              do icp=1,ncp_plane(ip) !loop on cluster inside couples              do icp=1,ncp_plane(ip) !loop on cluster inside couples
3425                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3426                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3427                   if(icx.eq.0.or.icy.eq.0)goto 11882!if fake couple, jump to next
3428                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3429                 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
3430  *                                                !jump to the next couple  *                                                !jump to the next couple
# Line 3245  c     $              AXV_STORE(nplanes-i Line 3443  c     $              AXV_STORE(nplanes-i
3443       $              )                     $              )              
3444                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3445  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3446                 if(DEBUG.EQ.1)print*,'( cl-X ',icx                 if(DEBUG.EQ.1)
3447         $              print*,'( cl-X ',icx
3448       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3449                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3450                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3278  c     $              0.,AYV_STORE(nplane Line 3477  c     $              0.,AYV_STORE(nplane
3477       $              )       $              )
3478                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3479  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3480                 if(DEBUG.EQ.1)print*,'( cl-Y ',icy                 if(DEBUG.EQ.1)
3481         $              print*,'( cl-Y ',icy
3482       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3483                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3484                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3298  c                 dedxmm = sgnl(icy)  !( Line 3498  c                 dedxmm = sgnl(icy)  !(
3498  11882          continue  11882          continue
3499              enddo               !end loop on cluster inside couples              enddo               !end loop on cluster inside couples
3500  *----- single clusters -----------------------------------------------    *----- single clusters -----------------------------------------------  
 c            print*,'## ncls(',ip,') ',ncls(ip)  
3501              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
3502                 icl=cls(ip,ic)                 icl=cls(ip,ic)
 c               if(cl_used(icl).eq.1.or.     !if the cluster is already used  
3503                 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)
3504       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match
3505       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
# Line 3323  c               if(cl_used(icl).eq.1.or. Line 3521  c               if(cl_used(icl).eq.1.or.
3521    
3522                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3523  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3524                 if(DEBUG.EQ.1)print*,'( cl-s ',icl                 if(DEBUG.EQ.1)
3525         $              print*,'( cl-s ',icl
3526       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3527                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
 c                  if(DEBUG.EQ.1)print*,'YES'  
3528                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3529                    ymm_A = yPAM_A                    ymm_A = yPAM_A
3530                    zmm_A = zPAM_A                    zmm_A = zPAM_A
# Line 3347  c                  if(DEBUG.EQ.1)print*, Line 3545  c                  if(DEBUG.EQ.1)print*,
3545                 endif                                   endif                  
3546  18882          continue  18882          continue
3547              enddo               !end loop on single clusters              enddo               !end loop on single clusters
 c            print*,'## distmin ', distmin,' clinc ',clinc  
3548    
 c     QUIQUI------------  
 c     anche qui: non ci vuole clinc???  
3549              if(iclm.ne.0)then              if(iclm.ne.0)then
3550                 if(mod(VIEW(iclm),2).eq.0)then                 if(mod(VIEW(iclm),2).eq.0)then
3551                    clincnew=                    clincnew=
# Line 3361  c     anche qui: non ci vuole clinc??? Line 3556  c     anche qui: non ci vuole clinc???
3556       $                 10*       $                 10*
3557       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))
3558                 endif                 endif
3559  c     QUIQUI------------  
3560                                 if(distmin.le.clincnew)then  
                if(distmin.le.clincnew)then   !QUIQUI  
 c     if(distmin.le.clinc)then          !QUIQUI            
3561                                        
3562                    CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<                        CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<    
3563  *     ----------------------------  *     ----------------------------
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3564                    if(mod(VIEW(iclm),2).eq.0)then                    if(mod(VIEW(iclm),2).eq.0)then
3565                       XGOOD(nplanes-ip+1)=1.                       XGOOD(nplanes-ip+1)=1.
3566                       resx(nplanes-ip+1)=rxmm                       resx(nplanes-ip+1)=rxmm
3567                       if(DEBUG.EQ.1)print*,'%%%% included X-cl ',iclm                       if(DEBUG.EQ.1)
3568         $                    print*,'%%%% included X-cl ',iclm
3569       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3570       $                    ,', dist.= ',distmin       $                    ,', dist.= ',distmin
3571       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3572                    else                    else
3573                       YGOOD(nplanes-ip+1)=1.                       YGOOD(nplanes-ip+1)=1.
3574                       resy(nplanes-ip+1)=rymm                       resy(nplanes-ip+1)=rymm
3575                       if(DEBUG.EQ.1)print*,'%%%% included Y-cl ',iclm                       if(DEBUG.EQ.1)
3576         $                    print*,'%%%% included Y-cl ',iclm
3577       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3578       $                    ,', dist.= ', distmin       $                    ,', dist.= ', distmin
3579       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3580                    endif                    endif
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3581  *     ----------------------------  *     ----------------------------
3582                    xm_A(nplanes-ip+1) = xmm_A                    xm_A(nplanes-ip+1) = xmm_A
3583                    ym_A(nplanes-ip+1) = ymm_A                    ym_A(nplanes-ip+1) = ymm_A
# Line 3405  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3598  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3598        return        return
3599        end        end
3600    
3601    
3602  ***************************************************  ***************************************************
3603  *                                                 *  *                                                 *
3604  *                                                 *  *                                                 *
# Line 3414  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3608  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3608  *                                                 *  *                                                 *
3609  **************************************************  **************************************************
3610  *  *
       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  
   
   
   
3611    
3612    
3613    
# Line 3559  c$$$               cl_used(icl)=ntrk   ! Line 3681  c$$$               cl_used(icl)=ntrk   !
3681          ys(1,ip)=0          ys(1,ip)=0
3682          ys(2,ip)=0          ys(2,ip)=0
3683          sgnlys(ip)=0          sgnlys(ip)=0
3684            sxbad(ip)=0
3685            sybad(ip)=0
3686            multmaxsx(ip)=0
3687            multmaxsy(ip)=0
3688        enddo        enddo
3689        end        end
3690    
# Line 3681  c$$$               cl_used(icl)=ntrk   ! Line 3807  c$$$               cl_used(icl)=ntrk   !
3807        integer ssensor,sladder        integer ssensor,sladder
3808        pig=acos(-1.)        pig=acos(-1.)
3809    
3810    
3811    
3812  *     -------------------------------------  *     -------------------------------------
3813        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3814        nstep_nt(ntr)       = nstep        nstep_nt(ntr)       = nstep
# Line 3728  c$$$               cl_used(icl)=ntrk   ! Line 3856  c$$$               cl_used(icl)=ntrk   !
3856           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)
3857           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)             dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)  
3858        
3859    
3860    ccc         print*,ip,'dedx >>> ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3861    
3862           ax   = axv_nt(ip,ntr)           ax   = axv_nt(ip,ntr)
3863           ay   = ayv_nt(ip,ntr)           ay   = ayv_nt(ip,ntr)
3864           bfx  = BX_STORE(ip,IDCAND)           bfx  = BX_STORE(ip,IDCAND)
# Line 3743  c$$$         angy    = 180.*atan(tgtemp) Line 3874  c$$$         angy    = 180.*atan(tgtemp)
3874           angy = effectiveangle(ay,2*ip-1,bfx)           angy = effectiveangle(ay,2*ip-1,bfx)
3875                    
3876                    
 c         print*,'* ',ip,bfx,bfy,angx,angy  
3877    
3878           id  = CP_STORE(ip,IDCAND) ! couple id           id  = CP_STORE(ip,IDCAND) ! couple id
3879           icl = CLS_STORE(ip,IDCAND)           icl = CLS_STORE(ip,IDCAND)
# Line 3759  c           >>> is a couple Line 3889  c           >>> is a couple
3889              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3890              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3891    
3892              cl_used(cltrx(ip,ntr)) = 1     !tag used clusters                        if(clx(nplanes-ip+1,icp_cp(id)).gt.0)then
3893              cl_used(cltry(ip,ntr)) = 1     !tag used clusters            
3894                   cl_used(cltrx(ip,ntr)) = 1 !tag used clusters          
3895    
3896                   xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))
3897    
3898              xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))                 if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3899              ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))       $              dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3900                  
3901                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3902         $              +10000*mult(cltrx(ip,ntr))
3903                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3904         $              /clsigma(indmax(cltrx(ip,ntr)))
3905                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3906                   xpu(ip,ntr)      = corr
3907    
3908                endif
3909                if(cly(nplanes-ip+1,icp_cp(id)).gt.0)then
3910    
3911              if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)                 cl_used(cltry(ip,ntr)) = 1 !tag used clusters          
      $           dedx_x(ip,ntr)=-dedx_x(ip,ntr)  
             if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)  
      $           dedx_y(ip,ntr)=-dedx_y(ip,ntr)  
3912    
3913              multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))                 ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))
      $                         +10000*mult(cltrx(ip,ntr))  
             seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))  
      $           /clsigma(indmax(cltrx(ip,ntr)))  
             call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)  
             xpu(ip,ntr)      = corr  
3914    
3915              multmaxy(ip,ntr) = maxs(cltry(ip,ntr))                 if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3916       $                         +10000*mult(cltry(ip,ntr))       $              dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3917              seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))                
3918       $           /clsigma(indmax(cltry(ip,ntr)))                 multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3919              call applypfa(PFA,cltry(ip,ntr),angy,corr,res)       $              +10000*mult(cltry(ip,ntr))
3920              ypu(ip,ntr)      = corr                 seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3921         $              /clsigma(indmax(cltry(ip,ntr)))
3922                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3923                   ypu(ip,ntr)      = corr
3924                endif
3925    
3926           elseif(icl.ne.0)then           elseif(icl.ne.0)then
3927    
# Line 3791  c           >>> is a couple Line 3929  c           >>> is a couple
3929    
3930              if(mod(VIEW(icl),2).eq.0)then              if(mod(VIEW(icl),2).eq.0)then
3931                 cltrx(ip,ntr)=icl                 cltrx(ip,ntr)=icl
   
3932                 xbad(ip,ntr) = nbadstrips(4,icl)                 xbad(ip,ntr) = nbadstrips(4,icl)
3933    
3934                 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)
# Line 3805  c           >>> is a couple Line 3942  c           >>> is a couple
3942    
3943              elseif(mod(VIEW(icl),2).eq.1)then              elseif(mod(VIEW(icl),2).eq.1)then
3944                 cltry(ip,ntr)=icl                 cltry(ip,ntr)=icl
   
3945                 ybad(ip,ntr) = nbadstrips(4,icl)                 ybad(ip,ntr) = nbadstrips(4,icl)
3946    
3947                 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)
# Line 3829  c           >>> is a couple Line 3965  c           >>> is a couple
3965           do ip=1,6           do ip=1,6
3966              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)
3967           enddo           enddo
3968             print*,'dedx: '
3969             do ip=1,6
3970                print*,'> ',ip,' -- ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3971             enddo
3972        endif        endif
3973    
 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*,'-----------------------'  
   
3974        end        end
3975    
3976        subroutine fill_level2_siglets        subroutine fill_level2_siglets
# Line 3873  c         if( mask_view(iv).ne.0 )good2( Line 4006  c         if( mask_view(iv).ne.0 )good2(
4006           ip=nplanes-npl(VIEW(icl))+1                       ip=nplanes-npl(VIEW(icl))+1            
4007                    
4008           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
4009    
4010              if(mod(VIEW(icl),2).eq.0)then !=== X views              if(mod(VIEW(icl),2).eq.0)then !=== X views
4011    
4012                 nclsx = nclsx + 1                 nclsx = nclsx + 1
4013                 planex(nclsx) = ip                 planex(nclsx) = ip
4014                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4015                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)
4016                 clsx(nclsx)   = icl                 clsx(nclsx)   = icl
4017                   sxbad(nclsx)  = nbadstrips(1,icl)
4018                   multmaxsx(nclsx) = maxs(icl)+10000*mult(icl)
4019                  
4020    
4021                 do is=1,2                 do is=1,2
4022  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4023  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
4024                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)
4025                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2
4026                 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)  
4027              else                          !=== Y views              else                          !=== Y views
4028                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4029                 planey(nclsy) = ip                 planey(nclsy) = ip
4030                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4031                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)
4032                 clsy(nclsy)   = icl                 clsy(nclsy)   = icl
4033                   sybad(nclsy)  = nbadstrips(1,icl)
4034                   multmaxsy(nclsy) = maxs(icl)+10000*mult(icl)
4035    
4036    
4037                 do is=1,2                 do is=1,2
4038  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4039  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
4040                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)
4041                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2
4042                 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)  
4043              endif              endif
4044           endif           endif
4045    
# Line 3919  c$$$               print*,'ys(2,nclsy)   Line 4052  c$$$               print*,'ys(2,nclsy)  
4052  *     associati ad una traccia, e permettere di salvare  *     associati ad una traccia, e permettere di salvare
4053  *     solo questi nell'albero di uscita  *     solo questi nell'albero di uscita
4054  *     --------------------------------------------------  *     --------------------------------------------------
4055                            
   
 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  
           
   
4056        enddo        enddo
4057        end        end
4058    
# Line 3998  c$$$         endif Line 4114  c$$$         endif
4114                 alfayz2_av_nt(iyz)=alfayz2_av(iyz)                 alfayz2_av_nt(iyz)=alfayz2_av(iyz)
4115                 nnn=nnn+ptcloud_yz(iyz)                 nnn=nnn+ptcloud_yz(iyz)
4116              enddo              enddo
4117              do ipt=1,nnn              do ipt=1,min(ndblt_max_nt,nnn)
4118                 db_cloud_nt(ipt)=db_cloud(ipt)                 db_cloud_nt(ipt)=db_cloud(ipt)
4119               enddo               enddo
4120           endif           endif
# Line 4011  c$$$         endif Line 4127  c$$$         endif
4127                 alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)                 alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)
4128                 nnn=nnn+ptcloud_xz(ixz)                               nnn=nnn+ptcloud_xz(ixz)              
4129              enddo              enddo
4130              do ipt=1,nnn              do ipt=1,min(ntrpt_max_nt,nnn)
4131                tr_cloud_nt(ipt)=tr_cloud(ipt)                tr_cloud_nt(ipt)=tr_cloud(ipt)
4132               enddo               enddo
4133           endif           endif

Legend:
Removed from v.1.32  
changed lines
  Added in v.1.41

  ViewVC Help
Powered by ViewVC 1.1.23