/[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.35 by bongi, Thu Nov 20 15:06:26 2008 UTC revision 1.47 by pam-ts, Wed Jun 4 07:57:04 2014 UTC
# Line 20  Line 20 
20        include 'calib.f'        include 'calib.f'
21        include 'level2.f'        include 'level2.f'
22    
   
   
23  c      print*,'======================================================'  c      print*,'======================================================'
24  c$$$      do ic=1,NCLSTR1  c$$$      do ic=1,NCLSTR1
25  c$$$         if(.false.  c$$$         if(.false.
# Line 74  c$$$      enddo Line 72  c$$$      enddo
72  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
73  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
74    
   
75        call cl_to_couples(iflag)        call cl_to_couples(iflag)
76        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
77           goto 880               !go to next event           goto 880               !go to next event
78        endif        endif
79                if(ncp_tot.eq.0)goto 880  !go to next event    
80  *-----------------------------------------------------  *-----------------------------------------------------
81  *-----------------------------------------------------  *-----------------------------------------------------
82  *     HOUGH TRASFORM  *     HOUGH TRASFORM
# Line 113  c$$$      enddo Line 110  c$$$      enddo
110        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
111           goto 880               !go to next event                       goto 880               !go to next event            
112        endif        endif
113          if(ndblt.eq.0.or.ntrpt.eq.0)goto 880 !go to next event    
114                
115                
116  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
# Line 163  c$$$      enddo Line 161  c$$$      enddo
161        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
162           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
163        endif        endif
164    *     ------------------------------------------------
165    *     first try to release the tolerance
166    *     ------------------------------------------------
167        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then
168          if(cutdistyz.lt.maxcuty/2)then           if(cutdistyz.lt.maxcuty/2)then
169            cutdistyz=cutdistyz+cutystep              cutdistyz=cutdistyz+cutystep
170          else           else
171            cutdistyz=cutdistyz+(3*cutystep)              cutdistyz=cutdistyz+(3*cutystep)
172          endif           endif
173          goto 878                           if(DEBUG.EQ.1)print*,'try again - cutdistyz ',cutdistyz
174        endif                               goto 878                
175          endif    
176    *     ------------------------------------------------
177    *     hence reduce the minimum number of plane
178    *     ------------------------------------------------
179          if(nclouds_yz.eq.0.and.nplyz_min.gt.3)then
180             nplyz_min=nplyz_min-1
181             if(DEBUG.EQ.1)print*,'try again - nplyz_min ',nplyz_min
182             goto 878
183          endif
184    
185          if(nclouds_yz.eq.0)goto 880 !go to next event    
186    
187        if(planehit.eq.3) goto 881            
188    ccc   if(planehit.eq.3) goto 881    
189                
190   879  continue     879  continue  
191        call trip_to_XZcloud(iflag)        call trip_to_XZcloud(iflag)
192        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
193           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
194        endif        endif
195                              *     ------------------------------------------------
196    *     first try to release the tolerance
197    *     ------------------------------------------------                          
198        if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then        if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then
199          cutdistxz=cutdistxz+cutxstep          cutdistxz=cutdistxz+cutxstep
200             if(DEBUG.EQ.1)print*,'try again - cutdistxz ',cutdistxz
201          goto 879                          goto 879                
202        endif                            endif                    
203    *     ------------------------------------------------
204    *     hence reduce the minimum number of plane
205    *     ------------------------------------------------
206          if(nclouds_xz.eq.0.and.nplxz_min.gt.3)then
207             nplxz_min=nplxz_min-1
208             if(DEBUG.EQ.1)print*,'try again - nplxz_min ',nplxz_min
209             goto 879
210          endif
211    
212          if(nclouds_xz.eq.0)goto 880 !go to next event    
213    
214            
215   881  continue    c$$$ 881  continue  
216  *     if there is at least three planes on the Y view decreases cuts on X view  c$$$*     if there is at least three planes on the Y view decreases cuts on X view
217        if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.  c$$$      if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.
218       $     nplxz_min.ne.y_min_start)then  c$$$     $     nplxz_min.ne.y_min_start)then
219          nptxz_min=x_min_step      c$$$        nptxz_min=x_min_step    
220          nplxz_min=x_min_start-x_min_step                c$$$        nplxz_min=x_min_start-x_min_step              
221          goto 879                  c$$$        goto 879                
222        endif                      c$$$      endif                    
223                    
224   880  return   880  return
225        end        end
# Line 243  c      include 'momanhough_init.f' Line 269  c      include 'momanhough_init.f'
269  *  *
270  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
271  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
272           ntrk=0                 !counter of identified physical tracks  ccc         ntrk=0                 !counter of identified physical tracks
273    
274  11111    continue               !<<<<<<< come here when performing a new search  c11111    continue               !<<<<<<< come here when performing a new search
275             continue                  !<<<<<<< come here when performing a new search
276    
277             if(nclouds_xz.eq.0)goto 880 !go to next event    
278             if(nclouds_yz.eq.0)goto 880 !go to next event    
279    
280  c         iflag=0  c         iflag=0
281           call clouds_to_ctrack(iflag)           call clouds_to_ctrack(iflag)
282           if(iflag.eq.1)then     !no candidate tracks found           if(iflag.eq.1)then     !no candidate tracks found
283              goto 880            !fill ntp and go to next event                goto 880            !fill ntp and go to next event  
284           endif           endif
285             if(ntracks.eq.0)goto 880 !go to next event    
286    
287           FIMAGE=.false.         !processing best track (not track image)           FIMAGE=.false.         !processing best track (not track image)
288           ibest=0                !best track among candidates           ibest=0                !best track among candidates
# Line 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    
529    
530  *     --- and store the results --------------------------------  *     --- and store the results --------------------------------
          ntrk = ntrk + 1                   !counter of found tracks  
          if(.not.FIMAGE  
      $        .and.iimage.eq.0) image(ntrk)= 0  
          if(.not.FIMAGE  
      $        .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next  
          if(FIMAGE)     image(ntrk)=ntrk-1 !this is the image of the previous  
          call fill_level2_tracks(ntrk)     !==> good2=.true.  
 c         print*,'++++++++++ iimage,fimage,ntrk,image '  
 c     $        ,iimage,fimage,ntrk,image(ntrk)  
   
531           if(ntrk.eq.NTRKMAX)then           if(ntrk.eq.NTRKMAX)then
532              if(verbose.eq.1)              if(verbose.eq.1)
533       $           print*,       $           print*,
# Line 562  c     $        ,iimage,fimage,ntrk,image Line 537  c     $        ,iimage,fimage,ntrk,image
537  cc            good2=.false.  cc            good2=.false.
538              goto 880            !fill ntp and go to next event              goto 880            !fill ntp and go to next event
539           endif           endif
540    
541             ntrk = ntrk + 1                   !counter of found tracks
542             if(.not.FIMAGE
543         $        .and.iimage.eq.0) image(ntrk)= 0
544             if(.not.FIMAGE
545         $        .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next
546             if(FIMAGE)     image(ntrk)=ntrk-1 !this is the image of the previous
547             call fill_level2_tracks(ntrk)     !==> good2=.true.
548    
549    c$$$         if(ntrk.eq.NTRKMAX)then
550    c$$$            if(verbose.eq.1)
551    c$$$     $           print*,
552    c$$$     $           '** warning ** number of identified '//
553    c$$$     $           'tracks exceeds vector dimension '
554    c$$$     $           ,'( ',NTRKMAX,' )'
555    c$$$cc            good2=.false.
556    c$$$            goto 880            !fill ntp and go to next event
557    c$$$         endif
558           if(iimage.ne.0)then           if(iimage.ne.0)then
559              FIMAGE=.true.       !              FIMAGE=.true.       !
560              goto 1212           !>>> fit image-track              goto 1212           !>>> fit image-track
561           endif           endif
562    
 *     --- 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  
 *     **********************************************  
   
   
563    
564   880     return   880     return
565        end        end
# Line 699  c     $        rchi2best.lt.15..and. Line 660  c     $        rchi2best.lt.15..and.
660        parameter (ndivx=30)        parameter (ndivx=30)
661    
662    
 c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy  
663                
664        resxPAM = 0        resxPAM = 0
665        resyPAM = 0        resyPAM = 0
# Line 713  c$$$      print*,icx,icy,sensor,PFAx,PFA Line 673  c$$$      print*,icx,icy,sensor,PFAx,PFA
673        xPAM_B = 0.D0        xPAM_B = 0.D0
674        yPAM_B = 0.D0        yPAM_B = 0.D0
675        zPAM_B = 0.D0        zPAM_B = 0.D0
 cc      print*,'## xyz_PAM: ',icx,icy,sensor,PFAx,PFAy,angx,angy  
676    
677        if(sensor.lt.1.or.sensor.gt.2)then        if(sensor.lt.1.or.sensor.gt.2)then
678           print*,'xyz_PAM   ***ERROR*** wrong input '           print*,'xyz_PAM   ***ERROR*** wrong input '
# Line 757  c         resxPAM = RESXAV Line 716  c         resxPAM = RESXAV
716           stripx  = stripx + corr           stripx  = stripx + corr
717           resxPAM = res           resxPAM = res
718    
719   10   endif   10   continue
720          endif
721            
722  *     -----------------  *     -----------------
723  *     CLUSTER Y  *     CLUSTER Y
# Line 803  c         resyPAM = RESYAV Line 763  c         resyPAM = RESYAV
763           stripy  = stripy + corr           stripy  = stripy + corr
764           resyPAM = res           resyPAM = res
765    
766   20   endif   20   continue
767          endif
768    
 cc      print*,'## stripx,stripy ',stripx,stripy  
769    
770  c===========================================================  c===========================================================
771  C     COUPLE  C     COUPLE
# Line 885  C======================================= Line 845  C=======================================
845              nldx = nldy              nldx = nldy
846              viewx = viewy + 1              viewx = viewy + 1
847    
848              yi   = dcoordsi(stripy,viewy)              xi = dcoordsi(0.5*(nstrips+1),viewx) !sensor center
849                yi = dcoordsi(stripy,viewy)
850                zi = 0.D0
851    
852              xi_A = edgeY_d - SiDimX/2              xi_A = edgeY_d - SiDimX/2
853              yi_A = yi              yi_A = yi
# Line 895  C======================================= Line 857  C=======================================
857              yi_B = yi              yi_B = yi
858              zi_B = 0.              zi_B = 0.
859    
 c            print*,'Y-cl ',icy,stripy,' --> ',yi  
 c            print*,xi_A,' <--> ',xi_B  
860                            
861           elseif(icx.ne.0)then           elseif(icx.ne.0)then
862  c===========================================================  c===========================================================
# Line 907  C======================================= Line 867  C=======================================
867              nldy = nldx              nldy = nldx
868              viewy = viewx - 1              viewy = viewx - 1
869    
 c            print*,'X-singlet ',icx,nplx,nldx,viewx,stripx  
 c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  
870              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
871       $           .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...
872                 if(DEBUG.EQ.1) then                 if(DEBUG.EQ.1) then
# Line 916  c            if((stripx.le.3).or.(stripx Line 874  c            if((stripx.le.3).or.(stripx
874       $                 ' WARNING: false X strip: strip ',stripx       $                 ' WARNING: false X strip: strip ',stripx
875                 endif                 endif
876              endif              endif
877              xi   = dcoordsi(stripx,viewx)  
878                xi = dcoordsi(stripx,viewx)
879                yi = dcoordsi(0.5*(nstrips+1),viewy) !sensor center
880                zi = 0.D0
881    
882              xi_A = xi              xi_A = xi
883              yi_A = edgeX_d - SiDimY/2              yi_A = edgeX_d - SiDimY/2
# Line 932  c            if((stripx.le.3).or.(stripx Line 893  c            if((stripx.le.3).or.(stripx
893                 yi_B = yi                 yi_B = yi
894              endif              endif
895    
 c            print*,'X-cl ',icx,stripx,' --> ',xi  
 c            print*,yi_A,' <--> ',yi_B  
896    
897           else           else
898              if(DEBUG.EQ.1) then              if(DEBUG.EQ.1) then
# Line 979  c     N.B. I convert angles from microra Line 938  c     N.B. I convert angles from microra
938       $        + zi_B       $        + zi_B
939       $        + dz(nplx,nldx,sensor)       $        + dz(nplx,nldx,sensor)
940    
941    
942    
943             xrt = xi
944         $        - omega(nplx,nldx,sensor)*yi
945         $        + gamma(nplx,nldx,sensor)*zi
946         $        + dx(nplx,nldx,sensor)
947            
948             yrt = omega(nplx,nldx,sensor)*xi
949         $        + yi
950         $        - beta(nplx,nldx,sensor)*zi
951         $        + dy(nplx,nldx,sensor)
952            
953             zrt = -gamma(nplx,nldx,sensor)*xi
954         $        + beta(nplx,nldx,sensor)*yi
955         $        + zi
956         $        + dz(nplx,nldx,sensor)
957    
958    
959                    
960  c      xrt = xi  c      xrt = xi
961  c      yrt = yi  c      yrt = yi
# Line 989  c     (xPAM,yPAM,zPAM) = measured coordi Line 966  c     (xPAM,yPAM,zPAM) = measured coordi
966  c                        in PAMELA reference system  c                        in PAMELA reference system
967  c------------------------------------------------------------------------  c------------------------------------------------------------------------
968    
969           xPAM = 0.D0           xPAM = dcoord(xrt,viewx,nldx,sensor) / 1.d4
970           yPAM = 0.D0           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
971           zPAM = 0.D0           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
972    c$$$         xPAM = 0.D0
973    c$$$         yPAM = 0.D0
974    c$$$         zPAM = 0.D0
975    
976           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4
977           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4
# Line 1002  c--------------------------------------- Line 982  c---------------------------------------
982           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
983                    
984    
 c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'  
985    
986        else        else
987           if(DEBUG.EQ.1) then           if(DEBUG.EQ.1) then
# Line 1013  c         print*,'A-(',xPAM_A,yPAM_A,') Line 992  c         print*,'A-(',xPAM_A,yPAM_A,')
992        endif        endif
993                    
994    
 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  
995    
996   100  continue   100  continue
997        end        end
# Line 1063  c$$$      PFAy = 'COG4'!PFA Line 1039  c$$$      PFAy = 'COG4'!PFA
1039        call idtoc(pfaid,PFAx)        call idtoc(pfaid,PFAx)
1040        call idtoc(pfaid,PFAy)        call idtoc(pfaid,PFAy)
1041    
 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  
1042                
1043        if(icx.ne.0.and.icy.ne.0)then        if(icx.ne.0.and.icy.ne.0)then
1044    
1045           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
1046           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  
1047                    
1048           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1049              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster icx=',icx
1050       $           ,' does not belong to plane: ',ip       $           ,' belongs to plane ',(nplanes-ipx+1)            
1051         $           ,' and not ',ip
1052              icx = -1*icx              icx = -1*icx
1053              return              return
1054           endif           endif
1055           if( (nplanes-ipy+1).ne.ip )then           if( (nplanes-ipy+1).ne.ip )then
1056              print*,'xyzpam: ***WARNING*** cluster ',icy              print*,'xyzpam: ***WARNING*** cluster icy=',icy
1057       $           ,' does not belong to plane: ',ip       $           ,' belongs to plane ',(nplanes-ipy+1)            
1058              icy = -1*icy       $           ,' and not ',ip
1059                 icy = -1*icy
1060              return              return
1061           endif           endif
1062    
# Line 1102  c$$$     $        ,' does not belong to Line 1072  c$$$     $        ,' does not belong to
1072           zm(ip) = zPAM           zm(ip) = zPAM
1073           xm_A(ip) = 0.D0           xm_A(ip) = 0.D0
1074           ym_A(ip) = 0.D0           ym_A(ip) = 0.D0
1075             zm_A(ip) = 0.D0
1076           xm_B(ip) = 0.D0           xm_B(ip) = 0.D0
1077           ym_B(ip) = 0.D0           ym_B(ip) = 0.D0
1078             zm_B(ip) = 0.D0
1079    
1080  c         zv(ip) = zPAM  c         zv(ip) = zPAM
1081    
1082        elseif(icx.eq.0.and.icy.ne.0)then        elseif(icx.eq.0.and.icy.ne.0)then
1083    
1084           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  
1085           if( (nplanes-ipy+1).ne.ip )then           if( (nplanes-ipy+1).ne.ip )then
1086              print*,'xyzpam: ***WARNING*** cluster ',icy              print*,'xyzpam: ***WARNING*** cluster icy=',icy
1087       $           ,' does not belong to plane: ',ip       $           ,' belongs to plane ',(nplanes-ipy+1)            
1088         $           ,' and not ',ip
1089              icy = -1*icy              icy = -1*icy
1090              return              return
1091           endif           endif
# Line 1127  c$$$     $        ,' does not belong to Line 1097  c$$$     $        ,' does not belong to
1097           resx(ip)  = 1000.           resx(ip)  = 1000.
1098           resy(ip)  = resyPAM           resy(ip)  = resyPAM
1099    
 cPP --- old ---  
1100  c$$$         xm(ip) = -100.  c$$$         xm(ip) = -100.
1101  c$$$         ym(ip) = -100.  c$$$         ym(ip) = -100.
1102  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1103  c$$$         xm_A(ip) = xPAM_A           xm(ip) = xPAM
1104  c$$$         ym_A(ip) = yPAM_A           ym(ip) = yPAM
1105  c$$$         xm_B(ip) = xPAM_B           zm(ip) = zPAM
 c$$$         ym_B(ip) = yPAM_B  
 cPP --- new ---  
          xm(ip) = -100.  
          ym(ip) = -100.  
          zm(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4  
1106           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1107           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1108           zm_A(ip) = zPAM_A           zm_A(ip) = zPAM_A
1109           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
1110           ym_B(ip) = yPAM_B           ym_B(ip) = yPAM_B
1111           zm_B(ip) = zPAM_B           zm_B(ip) = zPAM_B
 cPP -----------  
1112    
1113  c         zv(ip) = (zPAM_A+zPAM_B)/2.  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1114                    
1115        elseif(icx.ne.0.and.icy.eq.0)then        elseif(icx.ne.0.and.icy.eq.0)then
1116    
1117           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  
1118    
1119           if( (nplanes-ipx+1).ne.ip )then           if( (nplanes-ipx+1).ne.ip )then
1120              print*,'xyzpam: ***WARNING*** cluster ',icx              print*,'xyzpam: ***WARNING*** cluster icx=',icx
1121       $           ,' does not belong to plane: ',ip       $           ,' belongs to plane ',(nplanes-ipx+1)            
1122         $           ,' and not ',ip
1123              icx = -1*icx              icx = -1*icx
1124              return              return
1125           endif           endif
# Line 1170  c$$$     $        ,' does not belong to Line 1131  c$$$     $        ,' does not belong to
1131           resx(ip)  = resxPAM           resx(ip)  = resxPAM
1132           resy(ip)  = 1000.           resy(ip)  = 1000.
1133    
 cPP --- old ---  
1134  c$$$         xm(ip) = -100.  c$$$         xm(ip) = -100.
1135  c$$$         ym(ip) = -100.  c$$$         ym(ip) = -100.
1136  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1137  c$$$         xm_A(ip) = xPAM_A           xm(ip) = xPAM
1138  c$$$         ym_A(ip) = yPAM_A           ym(ip) = yPAM
1139  c$$$         xm_B(ip) = xPAM_B           zm(ip) = zPAM
 c$$$         ym_B(ip) = yPAM_B  
 cPP --- new ---  
          xm(ip) = -100.  
          ym(ip) = -100.  
          zm(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4  
1140           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1141           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1142           zm_A(ip) = zPAM_A           zm_A(ip) = zPAM_A
1143           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
1144           ym_B(ip) = yPAM_B           ym_B(ip) = yPAM_B
1145           zm_B(ip) = zPAM_B           zm_B(ip) = zPAM_B
1146  cPP -----------          
   
1147  c         zv(ip) = (zPAM_A+zPAM_B)/2.  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1148    
1149        else        else
# Line 1198  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1152  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1152           if(lad.ne.0)il=lad           if(lad.ne.0)il=lad
1153           is = 1           is = 1
1154           if(sensor.ne.0)is=sensor           if(sensor.ne.0)is=sensor
 c         print*,nplanes-ip+1,il,is  
1155    
1156           xgood(ip) = 0.           xgood(ip) = 0.
1157           ygood(ip) = 0.           ygood(ip) = 0.
# Line 1210  c         print*,nplanes-ip+1,il,is Line 1163  c         print*,nplanes-ip+1,il,is
1163           zm(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4           zm(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4
1164           xm_A(ip) = 0.           xm_A(ip) = 0.
1165           ym_A(ip) = 0.           ym_A(ip) = 0.
1166             zm_A(ip) = 0.
1167           xm_B(ip) = 0.           xm_B(ip) = 0.
1168           ym_B(ip) = 0.           ym_B(ip) = 0.
1169             zm_B(ip) = 0.
1170    
1171  c         zv(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4  c         zv(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4
1172    
1173        endif        endif
1174    
1175        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
 c         print*,'----------------------------- track coord'  
1176  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1177           write(*,22222)ip,zm(ip),xm(ip),ym(ip)           write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1178       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1179       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)
 c$$$         print*,'-----------------------------'  
1180        endif        endif
1181        end        end
1182    
# Line 1266  c$$$         print*,'------------------- Line 1219  c$$$         print*,'-------------------
1219    
1220  *     ----------------------  *     ----------------------
1221        if (        if (
1222       +     xPAM.eq.0.and.  c$$$     +     xPAM.eq.0.and.
1223       +     yPAM.eq.0.and.  c$$$     +     yPAM.eq.0.and.
1224       +     zPAM.eq.0.and.  c$$$     +     zPAM.eq.0.and.
1225       +     xPAM_A.ne.0.and.       +     xPAM_A.ne.0.and.
1226       +     yPAM_A.ne.0.and.       +     yPAM_A.ne.0.and.
1227       +     zPAM_A.ne.0.and.       +     zPAM_A.ne.0.and.
# Line 1310  c$$$         print*,'------------------- Line 1263  c$$$         print*,'-------------------
1263  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1264           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1265    
 c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',re  
1266    
1267                    
1268  *     ----------------------  *     ----------------------
1269        elseif(        elseif(
1270       +     xPAM.ne.0.and.  c$$$     +     xPAM.ne.0.and.
1271       +     yPAM.ne.0.and.  c$$$     +     yPAM.ne.0.and.
1272       +     zPAM.ne.0.and.  c$$$     +     zPAM.ne.0.and.
1273       +     xPAM_A.eq.0.and.       +     xPAM_A.eq.0.and.
1274       +     yPAM_A.eq.0.and.       +     yPAM_A.eq.0.and.
1275       +     zPAM_A.eq.0.and.       +     zPAM_A.eq.0.and.
# Line 1340  c$$$     $        + Line 1290  c$$$     $        +
1290  c$$$     $        ((yPAM-YPP)/resyPAM)**2  c$$$     $        ((yPAM-YPP)/resyPAM)**2
1291           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1292    
 c$$$         print*,xPAM,yPAM,zPAM  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',resxPAM,resyPAM  
1293                    
1294        else        else
1295                    
 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  
1296        endif          endif  
1297    
1298        distance_to = sngl(distance)        distance_to = sngl(distance)
# Line 1415  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1357  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1357  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1358  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1359  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  
1360                 xi = dcoordsi(stripx,viewx)                 xi = dcoordsi(stripx,viewx)
1361                 yi = dcoordsi(stripy,viewy)                 yi = dcoordsi(stripy,viewy)
1362                 zi = 0.D0                 zi = 0.D0
# Line 1448  c--------------------------------------- Line 1384  c---------------------------------------
1384    
1385                 yvv(iv)=sngl(yvvv)                 yvv(iv)=sngl(yvvv)
1386                 xvv(iv)=sngl(xvvv)                 xvv(iv)=sngl(xvvv)
 c               print*,'LADDER ',il,' SENSOR ',is,' vertexes >> '  
 c     $              ,iv,xvv(iv),yvv(iv)  
1387              enddo               !end loop on sensor vertexes              enddo               !end loop on sensor vertexes
1388    
1389              dtot=0.              dtot=0.
# Line 1457  c     $              ,iv,xvv(iv),yvv(iv) Line 1391  c     $              ,iv,xvv(iv),yvv(iv)
1391                 iv1=iside                 iv1=iside
1392                 iv2=mod(iside,4)+1                 iv2=mod(iside,4)+1
1393  *     straight line passing trhough two consecutive vertexes  *     straight line passing trhough two consecutive vertexes
1394                 AA = (yvv(iv1)-yvv(iv2))/(xvv(iv1)-xvv(iv2))                 AA = REAL((yvv(iv1)-yvv(iv2))/(xvv(iv1)-xvv(iv2))) !EM GCC4.7
1395                 BB = yvv(iv1) - AA*xvv(iv1)                 BB = REAL(yvv(iv1) - AA*xvv(iv1)) !EM GCC4.7
1396  *     point along the straight line closer to the track  *     point along the straight line closer to the track
1397                 xoo = (xPAM+AA*yPAM-AA*BB)/(1+AA**2)                 xoo = (xPAM+AA*yPAM-AA*BB)/(1+AA**2)
1398                 yoo = AA*xoo + BB                 yoo = AA*xoo + BB
# Line 1470  c     $              ,iv,xvv(iv),yvv(iv) Line 1404  c     $              ,iv,xvv(iv),yvv(iv)
1404                 iv1=iside                 iv1=iside
1405                 iv2=mod(iside,4)+1                 iv2=mod(iside,4)+1
1406  *     straight line passing trhough two consecutive vertexes  *     straight line passing trhough two consecutive vertexes
1407                 AA = (xvv(iv1)-xvv(iv2))/(yvv(iv1)-yvv(iv2))                 AA = REAL((xvv(iv1)-xvv(iv2))/(yvv(iv1)-yvv(iv2))) !EM GCC4.7
1408                 BB = xvv(iv1) - AA*yvv(iv1)                 BB = REAL(xvv(iv1) - AA*yvv(iv1)) !EM GCC4.7
1409  *     point along the straight line closer to the track  *     point along the straight line closer to the track
1410                 yoo = (yPAM+AA*xPAM-AA*BB)/(1+AA**2)                 yoo = (yPAM+AA*xPAM-AA*BB)/(1+AA**2)
1411                 xoo = AA*yoo + BB                 xoo = AA*yoo + BB
# Line 1574  c      include 'common_analysis.f' Line 1508  c      include 'common_analysis.f'
1508        is_cp=0        is_cp=0
1509        if(id.lt.0)is_cp=1        if(id.lt.0)is_cp=1
1510        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 !!!'  
1511    
1512        return        return
1513        end        end
# Line 1673  c      include 'level1.f' Line 1606  c      include 'level1.f'
1606        integer iflag        integer iflag
1607    
1608        integer badseed,badclx,badcly        integer badseed,badclx,badcly
1609        
1610          iflag = iflag
1611        if(DEBUG.EQ.1)print*,'cl_to_couples:'        if(DEBUG.EQ.1)print*,'cl_to_couples:'
1612    
1613    cc      if(RECOVER_SINGLETS.and..not.SECOND_SEARCH)goto 80
1614    
1615  *     init variables  *     init variables
       ncp_tot=0  
1616        do ip=1,nplanes        do ip=1,nplanes
1617           do ico=1,ncouplemax           do ico=1,ncouplemax
1618              clx(ip,ico)=0              clx(ip,ico)=0
# Line 1690  c      include 'level1.f' Line 1625  c      include 'level1.f'
1625           ncls(ip)=0           ncls(ip)=0
1626        enddo        enddo
1627        do icl=1,nclstrmax_level2        do icl=1,nclstrmax_level2
1628           cl_single(icl) = 1           cl_single(icl) = 1     !all are single
1629           cl_good(icl)   = 0           cl_good(icl)   = 0     !all are bad
1630        enddo        enddo
1631        do iv=1,nviews        do iv=1,nviews
1632           ncl_view(iv)  = 0           ncl_view(iv)  = 0
# Line 1719  c            mask_view(iv) = 1 Line 1654  c            mask_view(iv) = 1
1654        do icx=1,nclstr1          !loop on cluster (X)        do icx=1,nclstr1          !loop on cluster (X)
1655           if(mod(VIEW(icx),2).eq.1)goto 10           if(mod(VIEW(icx),2).eq.1)goto 10
1656                    
1657             if(cl_used(icx).ne.0)goto 10
1658    
1659  *     ----------------------------------------------------  *     ----------------------------------------------------
1660  *     jump masked views (X VIEW)  *     jump masked views (X VIEW)
1661  *     ----------------------------------------------------  *     ----------------------------------------------------
# Line 1726  c            mask_view(iv) = 1 Line 1663  c            mask_view(iv) = 1
1663  *     ----------------------------------------------------  *     ----------------------------------------------------
1664  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1665  *     ----------------------------------------------------  *     ----------------------------------------------------
1666           if(sgnl(icx).lt.dedx_x_min)then           if(sgnl(icx)/mip(VIEW(icx),LADDER(icx)).lt.dedx_x_min)then
1667              cl_single(icx)=0              cl_single(icx)=0
1668              goto 10              goto 10
1669           endif           endif
# Line 1767  c     endif Line 1704  c     endif
1704                    
1705           do icy=1,nclstr1       !loop on cluster (Y)           do icy=1,nclstr1       !loop on cluster (Y)
1706              if(mod(VIEW(icy),2).eq.0)goto 20              if(mod(VIEW(icy),2).eq.0)goto 20
1707    
1708                if(cl_used(icx).ne.0)goto 20
1709                            
1710  *     ----------------------------------------------------  *     ----------------------------------------------------
1711  *     jump masked views (Y VIEW)  *     jump masked views (Y VIEW)
# Line 1776  c     endif Line 1715  c     endif
1715  *     ----------------------------------------------------  *     ----------------------------------------------------
1716  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1717  *     ----------------------------------------------------  *     ----------------------------------------------------
1718              if(sgnl(icy).lt.dedx_y_min)then              if(sgnl(icy)/mip(VIEW(icy),LADDER(icy)) .lt.dedx_y_min)then
1719                 cl_single(icy)=0                 cl_single(icy)=0
1720                 goto 20                 goto 20
1721              endif              endif
# Line 1854  c                  cut = chcut * sch(npl Line 1793  c                  cut = chcut * sch(npl
1793       $                 ,'( ',ncouplemax,' ) --> masked!'       $                 ,'( ',ncouplemax,' ) --> masked!'
1794  c                  mask_view(nviewx(nplx)) = 2  c                  mask_view(nviewx(nplx)) = 2
1795  c                  mask_view(nviewy(nply)) = 2  c                  mask_view(nviewy(nply)) = 2
1796                    mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1                   mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1
1797                    mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1                   mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1
1798                    goto 10                    goto 10
1799                 endif                 endif
1800                                
# Line 1875  c                  mask_view(nviewy(nply Line 1814  c                  mask_view(nviewy(nply
1814   10      continue   10      continue
1815        enddo                     !end loop on clusters(X)        enddo                     !end loop on clusters(X)
1816                
         
1817        do icl=1,nclstr1        do icl=1,nclstr1
1818           if(cl_single(icl).eq.1)then           if(cl_single(icl).eq.1)then
1819              ip=npl(VIEW(icl))              ip=npl(VIEW(icl))
# Line 1883  c                  mask_view(nviewy(nply Line 1821  c                  mask_view(nviewy(nply
1821              cls(ip,ncls(ip))=icl              cls(ip,ncls(ip))=icl
1822           endif           endif
1823        enddo        enddo
1824    
1825    c 80   continue
1826          continue
1827                
1828                
1829        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
1830           print*,'clusters  ',nclstr1           print*,'clusters  ',nclstr1
1831           print*,'good    ',(cl_good(i),i=1,nclstr1)           print*,'good    ',(cl_good(i),i=1,nclstr1)
1832             print*,'used    ',(cl_used(i),i=1,nclstr1)
1833           print*,'singlets',(cl_single(i),i=1,nclstr1)           print*,'singlets',(cl_single(i),i=1,nclstr1)
1834           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1835        endif        endif
1836    
1837      
1838          if(.not.RECOVER_SINGLETS)goto 81
1839    
1840    *     ////////////////////////////////////////////////
1841    *     PATCH to recover events with less than 3 couples
1842    *     ////////////////////////////////////////////////    
1843    *     loop over singlet and create "fake" couples
1844    *     (with clx=0 or cly=0)
1845    *    
1846    
1847          if(DEBUG.EQ.1)
1848         $     print*,'>>> Recover singlets '
1849         $     ,'(creates fake couples) <<<'
1850          do icl=1,nclstr1
1851             if(
1852         $        cl_single(icl).eq.1.and.
1853         $        cl_used(icl).eq.0.and.
1854         $        .true.)then
1855    *     ----------------------------------------------------
1856    *     jump masked views
1857    *     ----------------------------------------------------
1858                if( mask_view(VIEW(icl)).ne.0 ) goto 21
1859                if(mod(VIEW(icl),2).eq.0)then !=== X views
1860    *     ----------------------------------------------------
1861    *     cut on charge (X VIEW)
1862    *     ----------------------------------------------------
1863                   if(sgnl(icl).lt.dedx_x_min) goto 21
1864                  
1865                   nplx=npl(VIEW(icl))
1866    *     ------------------> (FAKE) COUPLE <-----------------
1867                   ncp_plane(nplx) = ncp_plane(nplx) + 1
1868                   clx(nplx,ncp_plane(nplx))=icl
1869                   cly(nplx,ncp_plane(nplx))=0
1870    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1871    *     ----------------------------------------------------
1872                  
1873                else                !=== Y views
1874    *     ----------------------------------------------------
1875    *     cut on charge (Y VIEW)
1876    *     ----------------------------------------------------
1877                   if(sgnl(icl).lt.dedx_y_min) goto 21
1878                  
1879                   nply=npl(VIEW(icl))
1880    *     ------------------> (FAKE) COUPLE <-----------------
1881                   ncp_plane(nply) = ncp_plane(nply) + 1
1882                   clx(nply,ncp_plane(nply))=0
1883                   cly(nply,ncp_plane(nply))=icl
1884    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1885    *     ----------------------------------------------------
1886                  
1887                endif
1888             endif                  !end "single" condition
1889     21      continue
1890          enddo                     !end loop over clusters
1891    
1892          if(DEBUG.EQ.1)
1893         $     print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1894    
1895    
1896     81   continue
1897                
1898        do ip=1,6        ncp_tot=0
1899          do ip=1,NPLANES
1900           ncp_tot = ncp_tot + ncp_plane(ip)           ncp_tot = ncp_tot + ncp_plane(ip)
1901        enddo        enddo
1902          if(DEBUG.EQ.1)
1903         $     print*,'n.couple tot:      ',ncp_tot
1904                
1905        return        return
1906        end        end
# Line 1957  c      double precision xm3,ym3,zm3 Line 1963  c      double precision xm3,ym3,zm3
1963  *     --------------------------------------------  *     --------------------------------------------
1964        do ip=1,nplanes        do ip=1,nplanes
1965           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  
1966              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7
1967              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7
1968           endif           endif
# Line 1969  c            mask_view(nviewy(ip)) = 8 Line 1973  c            mask_view(nviewy(ip)) = 8
1973        ntrpt=0                   !number of triplets        ntrpt=0                   !number of triplets
1974                
1975        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1
1976    c$$$         print*,'(1) ip ',ip1
1977    c$$$     $        ,mask_view(nviewx(ip1))
1978    c$$$     $        ,mask_view(nviewy(ip1))        
1979           if(  mask_view(nviewx(ip1)).ne.0 .or.           if(  mask_view(nviewx(ip1)).ne.0 .or.
1980       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
1981           do is1=1,2             !loop on sensors - COPPIA 1                       do is1=1,2             !loop on sensors - COPPIA 1            
1982              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
1983                 icx1=clx(ip1,icp1)                 icx1=clx(ip1,icp1)
1984                 icy1=cly(ip1,icp1)                 icy1=cly(ip1,icp1)
1985                  
1986    c$$$               print*,'(1) ip ',ip1,' icp ',icp1
1987    
1988  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
1989  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
1990                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
1991                 xm1=xPAM                 xm1=REAL(xPAM) !EM GCC4.7
1992                 ym1=yPAM                 ym1=REAL(yPAM) !EM GCC4.7
1993                 zm1=zPAM                                   zm1=REAL(zPAM) !EM GCC4.7
 c     print*,'***',is1,xm1,ym1,zm1  
1994    
1995                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
1996    c$$$                  print*,'(2) ip ',ip2
1997    c$$$     $                 ,mask_view(nviewx(ip2))
1998    c$$$     $                 ,mask_view(nviewy(ip2))
1999                    if(  mask_view(nviewx(ip2)).ne.0 .or.                    if(  mask_view(nviewx(ip2)).ne.0 .or.
2000       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
2001                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                                        do is2=1,2    !loop on sensors -ndblt COPPIA 2                    
2002                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
2003                          icx2=clx(ip2,icp2)                          icx2=clx(ip2,icp2)
2004                          icy2=cly(ip2,icp2)                          icy2=cly(ip2,icp2)
2005    
2006    c$$$                        print*,'(2) ip ',ip2,' icp ',icp2
2007    
2008  c                        call xyz_PAM  c                        call xyz_PAM
2009  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
2010  c                        call xyz_PAM  c                        call xyz_PAM
2011  c     $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.) !(1)  c     $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.) !(1)
2012                          call xyz_PAM                          call xyz_PAM
2013       $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.,0.,0.)       $                       (icx2,icy2,is2,PFAdef,PFAdef,0.,0.,0.,0.)
2014                          xm2=xPAM                          xm2=REAL(xPAM) !EM GCC4.7
2015                          ym2=yPAM                          ym2=REAL(yPAM) !EM GCC4.7
2016                          zm2=zPAM                          zm2=REAL(zPAM) !EM GCC4.7
2017                                                    
2018    *                       ---------------------------------------------------
2019    *                       both couples must have a y-cluster
2020    *                       (condition necessary when in RECOVER_SINGLETS mode)
2021    *                       ---------------------------------------------------
2022                            if(icy1.eq.0.or.icy2.eq.0)goto 111
2023    
2024                            if(cl_used(icy1).ne.0)goto 111
2025                            if(cl_used(icy2).ne.0)goto 111
2026    
2027                            
2028  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2029  *     track parameters on Y VIEW  *     track parameters on Y VIEW
2030  *     (2 couples needed)  *     (2 couples needed)
# Line 2009  c     $                       (icx2,icy2 Line 2034  c     $                       (icx2,icy2
2034       $                          '** warning ** number of identified '//       $                          '** warning ** number of identified '//
2035       $                          'doublets exceeds vector dimention '       $                          'doublets exceeds vector dimention '
2036       $                          ,'( ',ndblt_max,' )'       $                          ,'( ',ndblt_max,' )'
2037  c                           good2=.false.  c     good2=.false.
2038  c                           goto 880 !fill ntp and go to next event  c     goto 880 !fill ntp and go to next event
2039                             do iv=1,12                             do iv=1,12
2040  c                              mask_view(iv) = 3  c     mask_view(iv) = 3
2041                                mask_view(iv) = mask_view(iv)+ 2**2                                mask_view(iv) = mask_view(iv)+ 2**2
2042                             enddo                             enddo
2043                             iflag=1                             iflag=1
2044                             return                             return
2045                          endif                          endif
2046                            
2047                            
2048    ccc                        print*,'<doublet> ',icp1,icp2
2049    
2050                          ndblt = ndblt + 1                          ndblt = ndblt + 1
2051  *     store doublet info  *     store doublet info
2052                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)
# Line 2025  c                              mask_view Line 2054  c                              mask_view
2054  *     tg(th_yz)  *     tg(th_yz)
2055                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)
2056  *     y0 (cm)  *     y0 (cm)
2057                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1                      alfayz1(ndblt)=alfayz2(ndblt)*(REAL(zini)-zm1)+ym1! EM GCC4.7 zm1, ym1 and alfayz1/2 are REAL
2058                                                      
2059  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2060  ****  reject non phisical couples                    ****  ****  reject non phisical couples                    ****
2061  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2062                            if(SECOND_SEARCH)goto 111
2063                          if(                          if(
2064       $                       abs(alfayz2(ndblt)).gt.alfyz2_max       $                       abs(alfayz2(ndblt)).gt.alfyz2_max
2065       $                       .or.       $                       .or.
2066       $                       abs(alfayz1(ndblt)).gt.alfyz1_max       $                       abs(alfayz1(ndblt)).gt.alfyz1_max
2067       $                       )ndblt = ndblt-1       $                       )ndblt = ndblt-1
2068                                                    
2069  c$$$      if(iev.eq.33)then                          
2070  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$$$  
2071  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2072  *     track parameters on Y VIEW - end  *     track parameters on Y VIEW - end
2073  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2074    
2075    
2076                            if(icx1.ne.0)then
2077                               if(cl_used(icx1).ne.0)goto 31
2078                            endif
2079                            if(icx2.ne.0)then
2080                               if(cl_used(icx2).ne.0)goto 31
2081                            endif
2082    
2083                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2084    
2085                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2086    c$$$                           print*,'(3) ip ',ip3
2087    c$$$     $                          ,mask_view(nviewx(ip3))
2088    c$$$     $                          ,mask_view(nviewy(ip3))                          
2089                             if(  mask_view(nviewx(ip3)).ne.0 .or.                             if(  mask_view(nviewx(ip3)).ne.0 .or.
2090       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2091                             do is3=1,2 !loop on sensors - COPPIA 3                             do is3=1,2 !loop on sensors - COPPIA 3
# Line 2058  c$$$ Line 2093  c$$$
2093                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
2094                                   icx3=clx(ip3,icp3)                                   icx3=clx(ip3,icp3)
2095                                   icy3=cly(ip3,icp3)                                   icy3=cly(ip3,icp3)
2096    
2097    c$$$                                 print*,'(3) ip ',ip3,' icp ',icp3
2098    
2099    *     ---------------------------------------------------
2100    *     all three couples must have a x-cluster
2101    *     (condition necessary when in RECOVER_SINGLETS mode)
2102    *     ---------------------------------------------------
2103                                     if(
2104         $                                icx1.eq.0.or.
2105         $                                icx2.eq.0.or.
2106         $                                icx3.eq.0.or.
2107         $                                .false.)goto 29
2108                                    
2109                                     if(cl_used(icx1).ne.0)goto 29
2110                                     if(cl_used(icx2).ne.0)goto 29
2111                                     if(cl_used(icx3).ne.0)goto 29
2112    
2113  c                                 call xyz_PAM  c                                 call xyz_PAM
2114  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2115  c                                 call xyz_PAM  c                                 call xyz_PAM
# Line 2065  c     $                               (i Line 2117  c     $                               (i
2117                                   call xyz_PAM                                   call xyz_PAM
2118       $                                (icx3,icy3,is3,PFAdef,PFAdef       $                                (icx3,icy3,is3,PFAdef,PFAdef
2119       $                                ,0.,0.,0.,0.)       $                                ,0.,0.,0.,0.)
2120                                   xm3=xPAM                                   xm3=REAL(xPAM) !EM GCC4.7
2121                                   ym3=yPAM                                   ym3=REAL(yPAM) !EM GCC4.7
2122                                   zm3=zPAM                                   zm3=REAL(zPAM) !EM GCC4.7
2123    
2124    
2125  *     find the circle passing through the three points  *     find the circle passing through the three points
2126  c$$$                                 call tricircle(3,xp,zp,angp,resp,chi                                   iflag_t = DEBUG
 c$$$     $                                ,xc,zc,radius,iflag)  
                                  iflag = DEBUG  
2127                                   call tricircle(3,xp,zp,angp,resp,chi                                   call tricircle(3,xp,zp,angp,resp,chi
2128       $                                ,xc,zc,radius,iflag)       $                                ,xc,zc,radius,iflag_t)
 c     print*,xc,zc,radius  
2129  *     the circle must intersect the reference plane  *     the circle must intersect the reference plane
2130                                   if(  cc                                 if(iflag.ne.0)goto 29
2131  c     $                                 (xc.le.-1.*xclimit.or.                                   if(iflag_t.ne.0)then
2132  c     $                                 xc.ge.xclimit).and.  *     if tricircle fails, evaluate a straight line
2133       $                                radius**2.ge.(ZINI-zc)**2.and.                                      if(DEBUG.eq.1)
2134       $                                iflag.eq.0.and.       $                                   print*,'TRICIRCLE failure'
2135       $                                .true.)then       $                                   ,' >>> straight line'
2136                                                                        radius=0.
2137                                        xc=0.
2138                                        yc=0.
2139                                        
2140                                        SZZ=0.                  
2141                                        SZX=0.
2142                                        SSX=0.
2143                                        SZ=0.
2144                                        S1=0.
2145                                        X0=0.
2146                                        Ax=0.
2147                                        BX=0.
2148                                        DO I=1,3
2149                                           XX = XP(I)
2150                                           SZZ=SZZ+ZP(I)*ZP(I)
2151                                           SZX=SZX+ZP(I)*XX
2152                                           SSX=SSX+XX
2153                                           SZ=SZ+ZP(I)
2154                                           S1=S1+1.
2155                                        ENDDO
2156                                        DET=SZZ*S1-SZ*SZ
2157                                        AX=(SZX*S1-SZ*SSX)/DET
2158                                        BX=(SZZ*SSX-SZX*SZ)/DET
2159                                        X0  = AX*REAL(ZINI)+BX ! EM GCC4.7
2160                                        
2161                                     endif
2162    
2163                                     if(  .not.SECOND_SEARCH.and.
2164         $                                radius**2.lt.(ZINI-zc)**2)goto 29
2165                                                                      
2166  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2167  *     track parameters on X VIEW  *     track parameters on X VIEW
2168  *     (3 couples needed)  *     (3 couples needed)
2169  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2170                                   if(ntrpt.eq.ntrpt_max)then                                   if(ntrpt.eq.ntrpt_max)then
2171                                      if(verbose.eq.1)print*,                                      if(verbose.eq.1)print*,
2172       $                     '** warning ** number of identified '//       $                                   '** warning **'//
2173       $                     'triplets exceeds vector dimention '       $                                   ' number of identified '//
2174       $                    ,'( ',ntrpt_max,' )'       $                                   'triplets exceeds'//
2175  c                                    good2=.false.       $                                   ' vector dimention '
2176  c                                    goto 880 !fill ntp and go to next event       $                                   ,'( ',ntrpt_max,' )'
2177    c     good2=.false.
2178    c     goto 880 !fill ntp and go to next event
2179                                      do iv=1,nviews                                      do iv=1,nviews
2180  c                                       mask_view(iv) = 4  c     mask_view(iv) = 4
2181                                         mask_view(iv)=mask_view(iv)+ 2**3                                         mask_view(iv) =
2182         $                                      mask_view(iv)+ 2**3
2183                                      enddo                                      enddo
2184                                      iflag=1                                      iflag=1
2185                                      return                                      return
2186                                   endif                                   endif
2187    
2188    ccc                                 print*,'<triplet> ',icp1,icp2,icp3
2189                                    
2190                                   ntrpt = ntrpt +1                                   ntrpt = ntrpt +1
2191  *     store triplet info  *     store triplet info
2192                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)
2193                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)
2194                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)
2195                                                                    
2196                                   if(xc.lt.0)then                                   if(radius.ne.0.and.xc.lt.0)then
2197  *************POSITIVE DEFLECTION  *************POSITIVE DEFLECTION
2198                alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)             alfaxz1(ntrpt) = xc+sqrt(radius**2-(REAL(ZINI)-zc)**2) !EM GCC4.7
2199                alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)             alfaxz2(ntrpt) = (REAL(ZINI)-zc)/
2200                alfaxz3(ntrpt) = 1/radius       $          sqrt(radius**2-(REAL(ZINI)-zc)**2) !EM GCC4.7
2201                                   else             alfaxz3(ntrpt) = 1/radius
2202                                    else if(radius.ne.0.and.xc.ge.0)then
2203  *************NEGATIVE DEFLECTION  *************NEGATIVE DEFLECTION
2204                alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)             alfaxz1(ntrpt) = xc-sqrt(radius**2-(REAL(ZINI)-zc)**2)
2205                alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)             alfaxz2(ntrpt) = -(REAL(ZINI)-zc)/
2206                alfaxz3(ntrpt) = -1/radius       $          sqrt(radius**2-(REAL(ZINI)-zc)**2) !EM GCC4.7
2207                                   endif             alfaxz3(ntrpt) = -1/radius
2208                                                                    else if(radius.eq.0)then
2209    *************straight fit
2210                 alfaxz1(ntrpt) = X0
2211                 alfaxz2(ntrpt) = AX
2212                 alfaxz3(ntrpt) = 0.
2213                                    endif
2214    
2215    c$$$                                print*,'alfaxz1 ', alfaxz1(ntrpt)
2216    c$$$                                print*,'alfaxz2 ', alfaxz2(ntrpt)
2217    c$$$                                print*,'alfaxz3 ', alfaxz3(ntrpt)
2218                                        
2219  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2220  ****  reject non phisical triplets                   ****  ****  reject non phisical triplets                   ****
2221  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2222                                   if(                                  if(SECOND_SEARCH)goto 29
2223       $                                abs(alfaxz2(ntrpt)).gt.alfxz2_max                                  if(
2224       $                                .or.       $                               abs(alfaxz2(ntrpt)).gt.
2225       $                                abs(alfaxz1(ntrpt)).gt.alfxz1_max       $                               alfxz2_max
2226       $                                )ntrpt = ntrpt-1       $                               .or.
2227                                         $                               abs(alfaxz1(ntrpt)).gt.
2228                                         $                               alfxz1_max
2229  c     print*,alfaxz1(ntrpt),alfaxz2(ntrpt),alfaxz3(ntrpt)       $                               )ntrpt = ntrpt-1
2230                                                                    
2231  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2232  *     track parameters on X VIEW - end  *     track parameters on X VIEW - end
2233  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2234                                endif                                
2235     29                           continue
2236                             enddo !end loop on COPPIA 3                             enddo !end loop on COPPIA 3
2237                          enddo   !end loop on sensors - COPPIA 3                          enddo   !end loop on sensors - COPPIA 3
2238   30                     continue   30                     continue
2239                       enddo      !end loop on planes  - COPPIA 3                       enddo      !end loop on planes  - COPPIA 3
2240   31                  continue  
2241                         31                  continue                    
2242   1                enddo         !end loop on COPPIA 2  c 1                enddo         !end loop on COPPIA 2
2243                     enddo         !end loop on COPPIA 2
2244                 enddo            !end loop on sensors - COPPIA 2                 enddo            !end loop on sensors - COPPIA 2
2245   20            continue   20            continue
2246              enddo               !end loop on planes  - COPPIA 2              enddo               !end loop on planes  - COPPIA 2
2247                
2248    c 11         continue
2249              continue
2250           enddo                  !end loop on COPPIA1           enddo                  !end loop on COPPIA1
2251        enddo                     !end loop on sensors - COPPIA 1        enddo                     !end loop on sensors - COPPIA 1
2252   10   continue   10   continue
# Line 2216  c      include 'momanhough_init.f' Line 2318  c      include 'momanhough_init.f'
2318        do idb1=1,ndblt           !loop (1) on DOUBLETS        do idb1=1,ndblt           !loop (1) on DOUBLETS
2319           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
2320                            
 c     print*,'--------------'  
 c     print*,'** ',idb1,' **'  
               
2321           do icp=1,ncp_tot           do icp=1,ncp_tot
2322              cp_useds1(icp)=0    !init              cp_useds1(icp)=0    !init
2323              cp_useds2(icp)=0    !init              cp_useds2(icp)=0    !init
# Line 2254  ccccc if(db_used(idbref).eq.1)goto 1188 Line 2353  ccccc if(db_used(idbref).eq.1)goto 1188
2353  *     doublet distance in parameter space  *     doublet distance in parameter space
2354                 distance=                 distance=
2355       $              ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2       $              ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2
2356       $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2                     $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2
2357                 distance = sqrt(distance)                 distance = sqrt(distance)
2358                                
 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  
2359                 if(distance.lt.cutdistyz)then                 if(distance.lt.cutdistyz)then
2360    
 c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  
2361                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1
2362                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1
2363                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1
# Line 2282  c     print*,idb1,idb2,distance,' cloud Line 2373  c     print*,idb1,idb2,distance,' cloud
2373    
2374                    temp1 = temp1 + alfayz1(idb2)                    temp1 = temp1 + alfayz1(idb2)
2375                    temp2 = temp2 + alfayz2(idb2)                    temp2 = temp2 + alfayz2(idb2)
 c     print*,'*   idbref,idb2 ',idbref,idb2  
2376                 endif                               endif              
2377                                
2378   1118          continue   1118          continue
2379              enddo               !end loop (2) on DOUBLETS              enddo               !end loop (2) on DOUBLETS
2380                            
2381   1188       continue  c 1188       continue
2382                continue
2383           enddo                  !end loop on... bo?           enddo                  !end loop on... bo?
2384                    
2385           nptloop=npv           nptloop=npv
# Line 2305  c     print*,'*   idbref,idb2 ',idbref,i Line 2396  c     print*,'*   idbref,idb2 ',idbref,i
2396           enddo           enddo
2397           ncpused=0           ncpused=0
2398           do icp=1,ncp_tot           do icp=1,ncp_tot
2399              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2400         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2401         $           .true.)then
2402                 ncpused=ncpused+1                 ncpused=ncpused+1
2403                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2404                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2315  c     print*,'*   idbref,idb2 ',idbref,i Line 2408  c     print*,'*   idbref,idb2 ',idbref,i
2408           do ip=1,nplanes           do ip=1,nplanes
2409              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2410           enddo           enddo
2411  c     print*,'>>>> ',ncpused,npt,nplused          
 c         if(ncpused.lt.ncpyz_min)goto 2228 !next doublet  
          if(npt.lt.nptyz_min)goto 2228 !next doublet  
2412           if(nplused.lt.nplyz_min)goto 2228 !next doublet           if(nplused.lt.nplyz_min)goto 2228 !next doublet
2413                    
2414  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2349  c               mask_view(iv) = 5 Line 2440  c               mask_view(iv) = 5
2440  c     ptcloud_yz_nt(nclouds_yz)=npt  c     ptcloud_yz_nt(nclouds_yz)=npt
2441           do ipt=1,npt           do ipt=1,npt
2442              db_cloud(npt_tot+ipt) = db_all(ipt)              db_cloud(npt_tot+ipt) = db_all(ipt)
 c     print*,'>> ',ipt,db_all(ipt)  
2443           enddo             enddo  
2444           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2445           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2446              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2447              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)
2448              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)
# Line 2362  c     print*,'>> ',ipt,db_all(ipt) Line 2451  c     print*,'>> ',ipt,db_all(ipt)
2451              print*,'cpcloud_yz '              print*,'cpcloud_yz '
2452       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)
2453              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)  
2454           endif           endif
2455  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2456  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2380  c$$$     $           ,(db_cloud(iii),iii Line 2465  c$$$     $           ,(db_cloud(iii),iii
2465        endif                            endif                    
2466                
2467        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2468           print*,'Y-Z total clouds ',nclouds_yz           print*,'Y-Z total clouds ',nclouds_yz
          print*,' '  
2469        endif        endif
2470                
2471                
# Line 2445  c      include 'momanhough_init.f' Line 2528  c      include 'momanhough_init.f'
2528   91   continue                     91   continue                  
2529        do itr1=1,ntrpt           !loop (1) on TRIPLETS        do itr1=1,ntrpt           !loop (1) on TRIPLETS
2530           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,' **'  
2531                    
2532           do icp=1,ncp_tot           do icp=1,ncp_tot
2533              cp_useds1(icp)=0              cp_useds1(icp)=0
# Line 2480  c         tr_temp(1)=itr1 Line 2561  c         tr_temp(1)=itr1
2561              do itr2=1,ntrpt     !loop (2) on TRIPLETS              do itr2=1,ntrpt     !loop (2) on TRIPLETS
2562                 if(itr2.eq.itr1)goto 11188       !next triplet                 if(itr2.eq.itr1)goto 11188       !next triplet
2563                 if(tr_used(itr2).eq.1)goto 11188 !next triplet                               if(tr_used(itr2).eq.1)goto 11188 !next triplet              
2564    
2565    
2566  *     triplet distance in parameter space  *     triplet distance in parameter space
2567  *     solo i due parametri spaziali per il momemnto  *     solo i due parametri spaziali per il momemnto
2568                 distance=                 distance=
2569       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2
2570       $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2                     $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2
2571                 distance = sqrt(distance)                 distance = sqrt(distance)
2572                  
2573    
2574  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
2575  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE  *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE
2576  *     ------------------------------------------------------------------------  *     ------------------------------------------------------------------------
# Line 2499  c         tr_temp(1)=itr1 Line 2583  c         tr_temp(1)=itr1
2583       $              .true.)istrimage=1       $              .true.)istrimage=1
2584    
2585                 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  
2586                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2587                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
2588                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1
# Line 2518  c     print*,idb1,idb2,distance,' cloud Line 2601  c     print*,idb1,idb2,distance,' cloud
2601                    temp1 = temp1 + alfaxz1(itr2)                    temp1 = temp1 + alfaxz1(itr2)
2602                    temp2 = temp2 + alfaxz2(itr2)                    temp2 = temp2 + alfaxz2(itr2)
2603                    temp3 = temp3 + alfaxz3(itr2)                    temp3 = temp3 + alfaxz3(itr2)
 c     print*,'*   itrref,itr2 ',itrref,itr2,distance  
2604                 endif                               endif              
2605                                
2606  11188          continue  11188          continue
2607              enddo               !end loop (2) on TRIPLETS              enddo               !end loop (2) on TRIPLETS
2608                                                
2609  11888       continue  c11888       continue
2610                continue
2611           enddo                  !end loop on... bo?               enddo                  !end loop on... bo?    
2612                    
2613           nptloop=npv           nptloop=npv
# Line 2539  c     print*,'*   itrref,itr2 ',itrref,i Line 2622  c     print*,'*   itrref,itr2 ',itrref,i
2622  *     1bis)  *     1bis)
2623  *     2) it is not already stored  *     2) it is not already stored
2624  *     ------------------------------------------  *     ------------------------------------------
 c     print*,'check cp_used'  
2625           do ip=1,nplanes           do ip=1,nplanes
2626              hit_plane(ip)=0              hit_plane(ip)=0
2627           enddo           enddo
2628           ncpused=0           ncpused=0
2629           do icp=1,ncp_tot           do icp=1,ncp_tot
2630              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2631         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2632         $           .true.)then
2633                 ncpused=ncpused+1                 ncpused=ncpused+1
2634                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2635                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2555  c     print*,'check cp_used' Line 2639  c     print*,'check cp_used'
2639           do ip=1,nplanes           do ip=1,nplanes
2640              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2641           enddo           enddo
 c         if(ncpused.lt.ncpxz_min)goto 22288 !next triplet  
          if(npt.lt.nptxz_min)goto 22288     !next triplet  
2642           if(nplused.lt.nplxz_min)goto 22288 !next triplet           if(nplused.lt.nplxz_min)goto 22288 !next triplet
2643                    
2644  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2590  c               mask_view(iv) = 6 Line 2672  c               mask_view(iv) = 6
2672           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2673                    
2674           if(DEBUG.EQ.1)then           if(DEBUG.EQ.1)then
2675              print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'              print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'
             print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'                
2676              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)
2677              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)
2678              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)
# Line 2600  c               mask_view(iv) = 6 Line 2681  c               mask_view(iv) = 6
2681              print*,'cpcloud_xz '              print*,'cpcloud_xz '
2682       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)       $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)
2683              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)  
2684           endif           endif
2685  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2686  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2617  c$$$     $           ,(tr_cloud(iii),iii Line 2694  c$$$     $           ,(tr_cloud(iii),iii
2694         endif                             endif                    
2695                
2696        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2697           print*,'X-Z total clouds ',nclouds_xz           print*,'X-Z total clouds ',nclouds_xz
          print*,' '  
2698        endif        endif
2699                
2700                
# Line 2675  c$$$     $           ,(tr_cloud(iii),iii Line 2750  c$$$     $           ,(tr_cloud(iii),iii
2750    
2751        ntracks=0                 !counter of track candidates        ntracks=0                 !counter of track candidates
2752                
2753        do iyz=1,nclouds_yz       !loop on YZ couds        do iyz=1,nclouds_yz       !loop on YZ clouds
2754           do ixz=1,nclouds_xz    !loop on XZ couds           do ixz=1,nclouds_xz    !loop on XZ clouds
2755                            
2756  *     --------------------------------------------------  *     --------------------------------------------------
2757  *     check of consistency of the clouds  *     check of consistency of the clouds
# Line 2685  c$$$     $           ,(tr_cloud(iii),iii Line 2760  c$$$     $           ,(tr_cloud(iii),iii
2760  *     of the two clouds  *     of the two clouds
2761  *     --------------------------------------------------  *     --------------------------------------------------
2762              do ip=1,nplanes              do ip=1,nplanes
2763                 hit_plane(ip)=0                 hit_plane(ip)=0  !n.matching couples (REAL couples, not SINGLETS)
2764                 ncp_match(ip)=0                 ncp_match(ip)=0  !n.matching couples per plane
2765                 do icpp=1,ncouplemax                 do icpp=1,ncouplemax
2766                    cp_match(ip,icpp)=0 !init couple list                    cp_match(ip,icpp)=0 !init couple list
2767                 enddo                 enddo
2768              enddo              enddo
2769              ncp_ok=0              ncp_ok=0            !count n.matching-couples
2770                ncpx_ok=0           !count n.matching-couples with x cluster
2771                ncpy_ok=0           !count n.matching-couples with y cluster
2772    
2773    
2774              do icp=1,ncp_tot    !loop over couples              do icp=1,ncp_tot    !loop over couples
2775  *     get info on  
2776                 cpintersec(icp)=min(                 if(.not.RECOVER_SINGLETS)then
2777       $              cpcloud_yz(iyz,icp),  *     ------------------------------------------------------
2778       $              cpcloud_xz(ixz,icp))  *     if NOT in RECOVER_SINGLETS mode, take the intersection
2779                 if(  *     between xz yz clouds
2780       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.  *     ------------------------------------------------------
2781       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.                    cpintersec(icp)=min(
2782       $              .false.)cpintersec(icp)=0       $                 cpcloud_yz(iyz,icp),
2783         $                 cpcloud_xz(ixz,icp))
2784  *     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
2785    *     ------------------------------------------------------
2786    *     discard the couple if the sensor is in conflict
2787    *     ------------------------------------------------------
2788                      if(
2789         $       (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2790         $       (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2791         $                 .false.)cpintersec(icp)=0
2792                   else
2793    *     ------------------------------------------------------
2794    *     if RECOVER_SINGLETS take the union
2795    *     (otherwise the fake couples formed by singlets would be
2796    *     discarded)    
2797    *     ------------------------------------------------------
2798                      cpintersec(icp)=max(
2799         $                 cpcloud_yz(iyz,icp),
2800         $                 cpcloud_xz(ixz,icp))
2801    c$$$                  if(cpcloud_yz(iyz,icp).gt.0)
2802    c$$$     $                 cpintersec(icp)=cpcloud_yz(iyz,icp)
2803    *     cpintersec is >0 if either yz or xz cloud contains the couple icp
2804                   endif
2805    
2806    c$$$               print*,icp,ip_cp(icp),' -- ',cpintersec(icp)
2807    
2808                 if(cpintersec(icp).ne.0)then                 if(cpintersec(icp).ne.0)then
                   ncp_ok=ncp_ok+1    
2809                                        
2810                    ip=ip_cp(icp)                    ip=ip_cp(icp)
2811                    hit_plane(ip)=1                    hit_plane(ip)=1
2812    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).gt.0)
2813    c$$$     $                 ncp_ok=ncp_ok+1  
2814    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).eq.0)
2815    c$$$     $                 ncpx_ok=ncpx_ok+1
2816    c$$$                  if(clx(ip,icp).eq.0.and.cly(ip,icp).gt.0)
2817    c$$$     $                 ncpy_ok=ncpy_ok+1
2818    
2819                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2820         $                 cpcloud_xz(ixz,icp).gt.0)
2821         $                 ncp_ok=ncp_ok+1  
2822                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2823         $                 cpcloud_xz(ixz,icp).eq.0)
2824         $                 ncpy_ok=ncpy_ok+1  
2825                      if(  cpcloud_yz(iyz,icp).eq.0.and.
2826         $                 cpcloud_xz(ixz,icp).gt.0)
2827         $                 ncpx_ok=ncpx_ok+1  
2828    
2829                    if(cpintersec(icp).eq.1)then                    if(cpintersec(icp).eq.1)then
2830  *     1) only the couple image in sensor 1 matches  *     1) only the couple image in sensor 1 matches
2831                       id=-icp                       id=-icp
# Line 2733  c$$$     $           ,(tr_cloud(iii),iii Line 2852  c$$$     $           ,(tr_cloud(iii),iii
2852              do ip=1,nplanes              do ip=1,nplanes
2853                 nplused=nplused+ hit_plane(ip)                 nplused=nplused+ hit_plane(ip)
2854              enddo              enddo
2855                                        
2856                            if(nplused.lt.3)goto 888 !next combination
2857    ccc            if(nplused.lt.nplxz_min)goto 888 !next combination
2858    ccc            if(nplused.lt.nplyz_min)goto 888 !next combination
2859    *     -----------------------------------------------------------
2860    *     if in RECOVER_SINGLET mode, the two clouds must have
2861    *     at least ONE intersecting real couple
2862    *     -----------------------------------------------------------
2863                if(ncp_ok.lt.1)goto 888 !next combination
2864    
2865              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
2866                 print*,'Combination ',iyz,ixz                 print*,'////////////////////////////'
2867       $              ,' db ',ptcloud_yz(iyz)                 print*,'Cloud combination (Y,X): ',iyz,ixz
2868       $              ,' tr ',ptcloud_xz(ixz)                 print*,' db ',ptcloud_yz(iyz)
2869       $              ,'  -----> # matching couples ',ncp_ok                 print*,' tr ',ptcloud_xz(ixz)
2870              endif                 print*,'  -----> # matching couples ',ncp_ok
2871                   print*,'  -----> # fake couples (X)',ncpx_ok
2872  c            if(nplused.lt.nplxz_min)goto 888 !next combination                 print*,'  -----> # fake couples (Y)',ncpy_ok
2873              if(nplused.lt.nplyz_min)goto 888 !next combination                 do icp=1,ncp_tot
2874              if(ncp_ok.lt.ncpok)goto 888 !next combination                    print*,'cp ',icp,' >'
2875         $                 ,' x ',cpcloud_xz(ixz,icp)
2876  c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'       $                 ,' y ',cpcloud_yz(iyz,icp)
2877  c$$$  print*,'Configurazione cluster XZ'       $                 ,' ==> ',cpintersec(icp)
2878  c$$$  print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))                 enddo
2879  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  
2880                                                    
2881              if(DEBUG.EQ.1)then              if(DEBUG.EQ.1)then
                print*,'track candidate', ntracks+1  
2882                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2883                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2884                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
# Line 2825  c$$$            if(AL_INI(5).gt.defmax)g Line 2911  c$$$            if(AL_INI(5).gt.defmax)g
2911                                hit_plane(6)=icp6                                hit_plane(6)=icp6
2912                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
2913                                                                
2914                                  if(DEBUG.eq.1)
2915         $                             print*,'combination: '
2916         $                             ,cp_match(6,icp1)
2917         $                             ,cp_match(5,icp2)
2918         $                             ,cp_match(4,icp3)
2919         $                             ,cp_match(3,icp4)
2920         $                             ,cp_match(2,icp5)
2921         $                             ,cp_match(1,icp6)
2922    
2923    
2924  *                             ---------------------------------------  *                             ---------------------------------------
2925  *                             check if this group of couples has been  *                             check if this group of couples has been
2926  *                             already fitted      *                             already fitted    
# Line 2873  c     $                                 Line 2969  c     $                                
2969       $                                   PFAdef,PFAdef,0.,0.,0.,0.)       $                                   PFAdef,PFAdef,0.,0.,0.,0.)
2970  *                                   *************************  *                                   *************************
2971  *                                   -----------------------------  *                                   -----------------------------
2972                                      xgood(nplanes-ip+1)=1.                                      if(icx.gt.0.and.icy.gt.0)then
2973                                      ygood(nplanes-ip+1)=1.                                         xgood(nplanes-ip+1)=1.
2974                                      xm(nplanes-ip+1)=xPAM                                         ygood(nplanes-ip+1)=1.
2975                                      ym(nplanes-ip+1)=yPAM                                         xm(nplanes-ip+1)=xPAM
2976                                      zm(nplanes-ip+1)=zPAM                                         ym(nplanes-ip+1)=yPAM
2977                                      resx(nplanes-ip+1)=resxPAM                                         zm(nplanes-ip+1)=zPAM
2978                                      resy(nplanes-ip+1)=resyPAM                                         resx(nplanes-ip+1)=resxPAM
2979                                           resy(nplanes-ip+1)=resyPAM
2980                                           if(DEBUG.EQ.1)print*,'(X,Y)'
2981         $                                      ,nplanes-ip+1,xPAM,yPAM
2982                                        else
2983                                           xm_A(nplanes-ip+1) = xPAM_A
2984                                           ym_A(nplanes-ip+1) = yPAM_A
2985                                           xm_B(nplanes-ip+1) = xPAM_B
2986                                           ym_B(nplanes-ip+1) = yPAM_B
2987                                           zm(nplanes-ip+1)
2988         $                                      = (zPAM_A+zPAM_B)/2.
2989                                           resx(nplanes-ip+1) = resxPAM
2990                                           resy(nplanes-ip+1) = resyPAM
2991                                           if(icx.eq.0.and.icy.gt.0)then
2992                                              xgood(nplanes-ip+1)=0.
2993                                              ygood(nplanes-ip+1)=1.
2994                                              resx(nplanes-ip+1) = 1000.
2995                                              if(DEBUG.EQ.1)print*,'(  Y)'
2996         $                                         ,nplanes-ip+1,xPAM,yPAM
2997                                           elseif(icx.gt.0.and.icy.eq.0)then
2998                                              xgood(nplanes-ip+1)=1.
2999                                              ygood(nplanes-ip+1)=0.
3000                                              if(DEBUG.EQ.1)print*,'(X  )'
3001         $                                         ,nplanes-ip+1,xPAM,yPAM
3002                                              resy(nplanes-ip+1) = 1000.
3003                                           else
3004                                              print*,'both icx=0 and icy=0'
3005         $                                         ,' ==> IMPOSSIBLE!!'
3006                                           endif
3007                                        endif
3008  *                                   -----------------------------  *                                   -----------------------------
3009                                   endif                                   endif
3010                                enddo !end loop on planes                                enddo !end loop on planes
# Line 2920  c                                 chi2=- Line 3045  c                                 chi2=-
3045  *     **********************************************************  *     **********************************************************
3046    
3047                                if(chi2.le.0.)goto 666                                              if(chi2.le.0.)goto 666              
3048                                  if(chi2.ge.1.e08)goto 666 !OPTIMIZATION
3049                                  if(chi2.ne.chi2)goto 666  !OPTIMIZATION
3050    
3051  *     --------------------------  *     --------------------------
3052  *     STORE candidate TRACK INFO  *     STORE candidate TRACK INFO
# Line 2946  c                                    mas Line 3073  c                                    mas
3073    
3074                                   XV_STORE(ip,ntracks)=sngl(xv(ip))                                   XV_STORE(ip,ntracks)=sngl(xv(ip))
3075                                   YV_STORE(ip,ntracks)=sngl(yv(ip))                                   YV_STORE(ip,ntracks)=sngl(yv(ip))
3076                                   ZV_STORE(ip,ntracks)=sngl(zv(ip))                                                                       ZV_STORE(ip,ntracks)=sngl(zv(ip))
3077                                   XM_STORE(ip,ntracks)=sngl(xm(ip))                                   XM_STORE(ip,ntracks)=sngl(xm(ip))
3078                                   YM_STORE(ip,ntracks)=sngl(ym(ip))                                   YM_STORE(ip,ntracks)=sngl(ym(ip))
3079                                   ZM_STORE(ip,ntracks)=sngl(zm(ip))                                   ZM_STORE(ip,ntracks)=sngl(zm(ip))
# Line 2965  c                                    mas Line 3092  c                                    mas
3092       $                                   cp_match(ip,hit_plane(ip))       $                                   cp_match(ip,hit_plane(ip))
3093                                      SENSOR_STORE(nplanes-ip+1,ntracks)                                      SENSOR_STORE(nplanes-ip+1,ntracks)
3094       $                              = is_cp(cp_match(ip,hit_plane(ip)))       $                              = is_cp(cp_match(ip,hit_plane(ip)))
3095                                      LADDER_STORE(nplanes-ip+1,ntracks)                                      
3096       $                                   = LADDER(                                      icl=
3097       $                                   clx(ip,icp_cp(       $                                   clx(ip,icp_cp(
3098       $                                   cp_match(ip,hit_plane(ip)       $                                   cp_match(ip,hit_plane(ip)
3099       $                                   ))));       $                                   )));
3100                                        if(icl.eq.0)
3101         $                                   icl=
3102         $                                   cly(ip,icp_cp(
3103         $                                   cp_match(ip,hit_plane(ip)
3104         $                                   )));
3105    
3106                                        LADDER_STORE(nplanes-ip+1,ntracks)
3107         $                                   = LADDER(icl);
3108                                   else                                   else
3109                                      CP_STORE(nplanes-ip+1,ntracks)=0                                      CP_STORE(nplanes-ip+1,ntracks)=0
3110                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0
# Line 2983  c                                    mas Line 3118  c                                    mas
3118                                   enddo                                   enddo
3119                                enddo                                enddo
3120                                                                
3121                                RCHI2_STORE(ntracks)=chi2                                RCHI2_STORE(ntracks)=REAL(chi2)
3122                                                                
3123  *     --------------------------------  *     --------------------------------
3124  *     STORE candidate TRACK INFO - end  *     STORE candidate TRACK INFO - end
# Line 3003  c                                    mas Line 3138  c                                    mas
3138                
3139        if(ntracks.eq.0)then        if(ntracks.eq.0)then
3140           iflag=1           iflag=1
3141           return  cc         return
3142        endif        endif
3143                
 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  
3144        if(DEBUG.EQ.1)then        if(DEBUG.EQ.1)then
3145          print*,'****** TRACK CANDIDATES *****************'          print*,'****** TRACK CANDIDATES *****************'
3146          print*,'#         R. chi2        RIG         ndof'          print*,'#         R. chi2        RIG         ndof'
# Line 3060  c$$$      endif Line 3186  c$$$      endif
3186        character*10 PFA        character*10 PFA
3187        common/FINALPFA/PFA        common/FINALPFA/PFA
3188    
3189          double precision xmm,rxmm,xmm_A,xmm_B !EM GCC4.7
3190          double precision ymm,rymm,ymm_A,ymm_B !EM GCC4.7
3191          double precision zmm,zmm_A,zmm_B !EM GCC4.7
3192          double precision clincnewc !EM GCC4.7
3193          double precision clincnew !EM GCC4.7
3194    
3195        real k(6)        real k(6)
3196        DATA k/1.099730,0.418900,0.220939,0.220907,0.418771,1.100674/        DATA k/1.099730,0.418900,0.220939,0.220907,0.418771,1.100674/
3197    
# Line 3094  c$$$         bxyz(3)=0 Line 3226  c$$$         bxyz(3)=0
3226  *     using improved PFAs  *     using improved PFAs
3227  *     -------------------------------------------------  *     -------------------------------------------------
3228  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3229           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.  c$$$         if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
3230    c$$$     $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3231    c$$$            
3232    c$$$            id=CP_STORE(nplanes-ip+1,ibest)
3233    c$$$            
3234    c$$$            is=is_cp(id)
3235    c$$$            icp=icp_cp(id)
3236    c$$$            if(ip_cp(id).ne.ip)
3237    c$$$     $           print*,'OKKIO!!'
3238    c$$$     $           ,'id ',id,is,icp
3239    c$$$     $           ,ip_cp(id),ip
3240    c$$$            icx=clx(ip,icp)
3241    c$$$            icy=cly(ip,icp)
3242    c$$$c            call xyz_PAM(icx,icy,is,
3243    c$$$c     $           PFA,PFA,
3244    c$$$c     $           AXV_STORE(nplanes-ip+1,ibest),
3245    c$$$c     $           AYV_STORE(nplanes-ip+1,ibest))
3246    c$$$            call xyz_PAM(icx,icy,is,
3247    c$$$     $           PFA,PFA,
3248    c$$$     $           AXV_STORE(nplanes-ip+1,ibest),
3249    c$$$     $           AYV_STORE(nplanes-ip+1,ibest),
3250    c$$$     $           bxyz(1),
3251    c$$$     $           bxyz(2)
3252    c$$$     $           )
3253    c$$$
3254    c$$$            xm(nplanes-ip+1) = xPAM
3255    c$$$            ym(nplanes-ip+1) = yPAM
3256    c$$$            zm(nplanes-ip+1) = zPAM
3257    c$$$            xgood(nplanes-ip+1) = 1
3258    c$$$            ygood(nplanes-ip+1) = 1
3259    c$$$            resx(nplanes-ip+1) = resxPAM
3260    c$$$            resy(nplanes-ip+1) = resyPAM
3261    c$$$
3262    c$$$            dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3263    c$$$            dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3264             if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..or.
3265       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3266                            
3267              id=CP_STORE(nplanes-ip+1,ibest)              id=CP_STORE(nplanes-ip+1,ibest)
# Line 3119  c     $           AYV_STORE(nplanes-ip+1 Line 3286  c     $           AYV_STORE(nplanes-ip+1
3286       $           bxyz(2)       $           bxyz(2)
3287       $           )       $           )
3288    
3289              xm(nplanes-ip+1) = xPAM              if(icx.gt.0.and.icy.gt.0)then
3290              ym(nplanes-ip+1) = yPAM                 xm(nplanes-ip+1) = xPAM
3291              zm(nplanes-ip+1) = zPAM                 ym(nplanes-ip+1) = yPAM
3292              xgood(nplanes-ip+1) = 1                 zm(nplanes-ip+1) = zPAM
3293              ygood(nplanes-ip+1) = 1                 xm_A(nplanes-ip+1) = 0.
3294              resx(nplanes-ip+1) = resxPAM                 ym_A(nplanes-ip+1) = 0.
3295              resy(nplanes-ip+1) = resyPAM                 xm_B(nplanes-ip+1) = 0.
3296                   ym_B(nplanes-ip+1) = 0.
3297              dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))                 xgood(nplanes-ip+1) = 1
3298              dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))                 ygood(nplanes-ip+1) = 1
3299                   resx(nplanes-ip+1) = resxPAM
3300                   resy(nplanes-ip+1) = resyPAM
3301                   dedxtrk_x(nplanes-ip+1)=
3302         $              sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3303                   dedxtrk_y(nplanes-ip+1)=
3304         $              sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3305                else
3306                   xm(nplanes-ip+1) = 0.
3307                   ym(nplanes-ip+1) = 0.
3308                   zm(nplanes-ip+1) = (zPAM_A+zPAM_B)/2.
3309                   xm_A(nplanes-ip+1) = xPAM_A
3310                   ym_A(nplanes-ip+1) = yPAM_A
3311                   xm_B(nplanes-ip+1) = xPAM_B
3312                   ym_B(nplanes-ip+1) = yPAM_B
3313                   xgood(nplanes-ip+1) = 0
3314                   ygood(nplanes-ip+1) = 0
3315                   resx(nplanes-ip+1) = 1000.!resxPAM
3316                   resy(nplanes-ip+1) = 1000.!resyPAM
3317                   dedxtrk_x(nplanes-ip+1)= 0
3318                   dedxtrk_y(nplanes-ip+1)= 0
3319                   if(icx.gt.0)then
3320                      xgood(nplanes-ip+1) = 1
3321                      resx(nplanes-ip+1) = resxPAM
3322                      dedxtrk_x(nplanes-ip+1)=
3323         $                 sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3324                   elseif(icy.gt.0)then
3325                      ygood(nplanes-ip+1) = 1
3326                      resy(nplanes-ip+1) = resyPAM
3327                      dedxtrk_y(nplanes-ip+1)=
3328         $                 sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3329                   endif
3330                endif
3331                            
3332  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3333  *     -------------------------------------------------  *     -------------------------------------------------
# Line 3140  c     $           AYV_STORE(nplanes-ip+1 Line 3339  c     $           AYV_STORE(nplanes-ip+1
3339                                
3340              xgood(nplanes-ip+1)=0              xgood(nplanes-ip+1)=0
3341              ygood(nplanes-ip+1)=0              ygood(nplanes-ip+1)=0
3342    
3343                CP_STORE(nplanes-ip+1,ibest)=0 !re-init
3344                CLS_STORE(nplanes-ip+1,ibest)=0
3345    
3346                                
3347  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3348  *     determine which ladder and sensor are intersected by the track  *     determine which ladder and sensor are intersected by the track
# Line 3162  c     $           AYV_STORE(nplanes-ip+1 Line 3365  c     $           AYV_STORE(nplanes-ip+1
3365  *     ===========================================  *     ===========================================
3366  *     STEP 1 >>>>>>>  try to include a new couple  *     STEP 1 >>>>>>>  try to include a new couple
3367  *     ===========================================  *     ===========================================
3368  c            if(DEBUG.EQ.1)print*,'>>>> try to include a new couple'              distmin=100000000.
             distmin=1000000.  
3369              xmm = 0.              xmm = 0.
3370              ymm = 0.              ymm = 0.
3371              zmm = 0.              zmm = 0.
# Line 3176  c            if(DEBUG.EQ.1)print*,'>>>> Line 3378  c            if(DEBUG.EQ.1)print*,'>>>>
3378              do icp=1,ncp_plane(ip) !loop on couples on plane icp              do icp=1,ncp_plane(ip) !loop on couples on plane icp
3379                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3380                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3381                   if(icx.eq.0.or.icy.eq.0)goto 1188!if fake couple, jump to next
3382                 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
3383  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
3384  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
# Line 3194  c     $              cl_used(icy).eq.1.o Line 3397  c     $              cl_used(icy).eq.1.o
3397                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3398  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3399                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3400                 if(DEBUG.EQ.1)print*,'( couple ',id                 if(DEBUG.EQ.1)
3401         $              print*,'( couple ',id
3402       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3403                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3404                    xmm = xPAM                    xmm = xPAM
# Line 3206  c               distance = distance / RC Line 3410  c               distance = distance / RC
3410                    idm = id                                      idm = id                  
3411                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3412                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3413  c     QUIQUI --> non devo moltiplicare per clinc?!?!?!                    clincnewc=10.*dsqrt(rymm**2+rxmm**2
3414                    clincnewc=10*sqrt(rymm**2+rxmm**2 !QUIQUI       $            +DBLE(RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2))))! EM GCC4.7
      $                 +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2))) !QUIQUI  
3415                 endif                 endif
3416   1188          continue   1188          continue
3417              enddo               !end loop on couples on plane icp              enddo               !end loop on couples on plane icp
3418  c            if(distmin.le.clinc)then     !QUIQUI                            if(distmin.le.clincnewc)then    
             if(distmin.le.clincnewc)then     !QUIQUI                
3419  *              -----------------------------------  *              -----------------------------------
3420                 xm(nplanes-ip+1) = xmm !<<<                 xm(nplanes-ip+1) = xmm !<<<
3421                 ym(nplanes-ip+1) = ymm !<<<                 ym(nplanes-ip+1) = ymm !<<<
# Line 3227  c            if(distmin.le.clinc)then   Line 3429  c            if(distmin.le.clinc)then  
3429  *              -----------------------------------  *              -----------------------------------
3430                 CP_STORE(nplanes-ip+1,ibest)=idm                       CP_STORE(nplanes-ip+1,ibest)=idm      
3431                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm
3432       $              ,' (dist.= ',distmin,', cut ',clinc,' )'       $              ,' (dist.= ',distmin,', cut ',clincnewc,' )'
3433                 goto 133         !next plane                 goto 133         !next plane
3434              endif              endif
3435  *     ================================================  *     ================================================
3436  *     STEP 2 >>>>>>>  try to include a single cluster  *     STEP 2 >>>>>>>  try to include a single cluster
3437  *                     either from a couple or single  *                     either from a couple or single
3438  *     ================================================  *     ================================================
 c            if(DEBUG.EQ.1)print*,'>>>> try to include a new cluster'  
3439              distmin=1000000.              distmin=1000000.
3440              xmm_A = 0.          !---------------------------              xmm_A = 0.          !---------------------------
3441              ymm_A = 0.          ! init variables that              ymm_A = 0.          ! init variables that
# Line 3253  c            if(DEBUG.EQ.1)print*,'>>>> Line 3454  c            if(DEBUG.EQ.1)print*,'>>>>
3454              do icp=1,ncp_plane(ip) !loop on cluster inside couples              do icp=1,ncp_plane(ip) !loop on cluster inside couples
3455                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3456                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3457                   if(icx.eq.0.or.icy.eq.0)goto 11882!if fake couple, jump to next
3458                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3459                 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
3460  *                                                !jump to the next couple  *                                                !jump to the next couple
# Line 3271  c     $              AXV_STORE(nplanes-i Line 3473  c     $              AXV_STORE(nplanes-i
3473       $              )                     $              )              
3474                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3475  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3476                 if(DEBUG.EQ.1)print*,'( cl-X ',icx                 if(DEBUG.EQ.1)
3477         $              print*,'( cl-X ',icx
3478       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3479                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3480                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3304  c     $              0.,AYV_STORE(nplane Line 3507  c     $              0.,AYV_STORE(nplane
3507       $              )       $              )
3508                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3509  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3510                 if(DEBUG.EQ.1)print*,'( cl-Y ',icy                 if(DEBUG.EQ.1)
3511         $              print*,'( cl-Y ',icy
3512       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3513                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3514                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3324  c                 dedxmm = sgnl(icy)  !( Line 3528  c                 dedxmm = sgnl(icy)  !(
3528  11882          continue  11882          continue
3529              enddo               !end loop on cluster inside couples              enddo               !end loop on cluster inside couples
3530  *----- single clusters -----------------------------------------------    *----- single clusters -----------------------------------------------  
 c            print*,'## ncls(',ip,') ',ncls(ip)  
3531              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
 c               print*,'-',ic,'-'  
3532                 icl=cls(ip,ic)                 icl=cls(ip,ic)
 c               if(cl_used(icl).eq.1.or.     !if the cluster is already used  
3533                 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)
3534       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match
3535       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
# Line 3350  c               if(cl_used(icl).eq.1.or. Line 3551  c               if(cl_used(icl).eq.1.or.
3551    
3552                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3553  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3554                 if(DEBUG.EQ.1)print*,'( cl-s ',icl                 if(DEBUG.EQ.1)
3555         $              print*,'( cl-s ',icl
3556       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3557                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
 c                  if(DEBUG.EQ.1)print*,'YES'  
3558                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3559                    ymm_A = yPAM_A                    ymm_A = yPAM_A
3560                    zmm_A = zPAM_A                    zmm_A = zPAM_A
# Line 3374  c                  if(DEBUG.EQ.1)print*, Line 3575  c                  if(DEBUG.EQ.1)print*,
3575                 endif                                   endif                  
3576  18882          continue  18882          continue
3577              enddo               !end loop on single clusters              enddo               !end loop on single clusters
 c            print*,'## distmin ', distmin,' clinc ',clinc  
3578    
 c     QUIQUI------------  
 c     anche qui: non ci vuole clinc???  
3579              if(iclm.ne.0)then              if(iclm.ne.0)then
3580                 if(mod(VIEW(iclm),2).eq.0)then                 if(mod(VIEW(iclm),2).eq.0)then
3581                    clincnew=                    clincnew=
3582       $                 20*       $            20.*     !EM GCC4.7
3583       $                 sqrt(rxmm**2+RCHI2_STORE(ibest)*k(ip)*cov(1,1))       $            dsqrt(rxmm**2 +
3584         $             DBLE(RCHI2_STORE(ibest)*k(ip))*cov(1,1))
3585                 else if(mod(VIEW(iclm),2).ne.0)then                 else if(mod(VIEW(iclm),2).ne.0)then
3586                    clincnew=                    clincnew=
3587       $                 10*       $            10.* !EM GCC4.7
3588       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))       $            dsqrt(rymm**2 +
3589         $             DBLE(RCHI2_STORE(ibest)*k(ip))*cov(2,2))
3590                 endif                 endif
3591  c     QUIQUI------------  
3592                                 if(distmin.le.clincnew)then  
                if(distmin.le.clincnew)then   !QUIQUI  
 c     if(distmin.le.clinc)then          !QUIQUI            
3593                                        
3594                    CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<                        CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<    
3595  *     ----------------------------  *     ----------------------------
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3596                    if(mod(VIEW(iclm),2).eq.0)then                    if(mod(VIEW(iclm),2).eq.0)then
3597                       XGOOD(nplanes-ip+1)=1.                       XGOOD(nplanes-ip+1)=1.
3598                       resx(nplanes-ip+1)=rxmm                       resx(nplanes-ip+1)=rxmm
3599                       if(DEBUG.EQ.1)print*,'%%%% included X-cl ',iclm                       if(DEBUG.EQ.1)
3600         $                    print*,'%%%% included X-cl ',iclm
3601       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3602       $                    ,', dist.= ',distmin       $                    ,', dist.= ',distmin
3603       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3604                    else                    else
3605                       YGOOD(nplanes-ip+1)=1.                       YGOOD(nplanes-ip+1)=1.
3606                       resy(nplanes-ip+1)=rymm                       resy(nplanes-ip+1)=rymm
3607                       if(DEBUG.EQ.1)print*,'%%%% included Y-cl ',iclm                       if(DEBUG.EQ.1)
3608         $                    print*,'%%%% included Y-cl ',iclm
3609       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3610       $                    ,', dist.= ', distmin       $                    ,', dist.= ', distmin
3611       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3612                    endif                    endif
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3613  *     ----------------------------  *     ----------------------------
3614                    xm_A(nplanes-ip+1) = xmm_A                    xm_A(nplanes-ip+1) = xmm_A
3615                    ym_A(nplanes-ip+1) = ymm_A                    ym_A(nplanes-ip+1) = ymm_A
                   zm_A(nplanes-ip+1) = zmm_A  
3616                    xm_B(nplanes-ip+1) = xmm_B                    xm_B(nplanes-ip+1) = xmm_B
3617                    ym_B(nplanes-ip+1) = ymm_B                    ym_B(nplanes-ip+1) = ymm_B
                   zm_B(nplanes-ip+1) = zmm_B  
3618                    zm(nplanes-ip+1) = (zmm_A+zmm_B)/2.                    zm(nplanes-ip+1) = (zmm_A+zmm_B)/2.
 c$$$                  zm(nplanes-ip+1) =  
 c$$$     $                 z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4  
3619                    dedxtrk_x(nplanes-ip+1) = dedxmmx !<<<                    dedxtrk_x(nplanes-ip+1) = dedxmmx !<<<
3620                    dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<                    dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<
3621  *     ----------------------------  *     ----------------------------
# Line 3436  c$$$     $                 z_mech_sensor Line 3630  c$$$     $                 z_mech_sensor
3630        return        return
3631        end        end
3632    
3633    
3634  ***************************************************  ***************************************************
3635  *                                                 *  *                                                 *
3636  *                                                 *  *                                                 *
# Line 3445  c$$$     $                 z_mech_sensor Line 3640  c$$$     $                 z_mech_sensor
3640  *                                                 *  *                                                 *
3641  **************************************************  **************************************************
3642  *  *
       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  
   
   
   
3643    
3644    
3645    
# Line 3712  c$$$               cl_used(icl)=ntrk   ! Line 3835  c$$$               cl_used(icl)=ntrk   !
3835        character*10 PFA        character*10 PFA
3836        common/FINALPFA/PFA        common/FINALPFA/PFA
3837    
3838        real sinth,phi,pig        real sinth,phi,pig, npig ! EM GCC4.7
3839        integer ssensor,sladder        integer ssensor,sladder
3840        pig=acos(-1.)        pig=acos(-1.)
3841    
3842    
3843    
3844  *     -------------------------------------  *     -------------------------------------
3845        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3846        nstep_nt(ntr)       = nstep        nstep_nt(ntr)       = nstep
3847  *     -------------------------------------  *     -------------------------------------
3848        phi   = al(4)                  phi   = REAL(al(4))
3849        sinth = al(3)                    sinth = REAL(al(3))
3850        if(sinth.lt.0)then              if(sinth.lt.0)then      
3851           sinth = -sinth                   sinth = -sinth        
3852           phi = phi + pig                 phi = phi + pig      
# Line 3763  c$$$               cl_used(icl)=ntrk   ! Line 3888  c$$$               cl_used(icl)=ntrk   !
3888           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)
3889           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)             dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)  
3890        
3891    
3892    ccc         print*,ip,'dedx >>> ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3893    
3894           ax   = axv_nt(ip,ntr)           ax   = axv_nt(ip,ntr)
3895           ay   = ayv_nt(ip,ntr)           ay   = ayv_nt(ip,ntr)
3896           bfx  = BX_STORE(ip,IDCAND)           bfx  = BX_STORE(ip,IDCAND)
# Line 3778  c$$$         angy    = 180.*atan(tgtemp) Line 3906  c$$$         angy    = 180.*atan(tgtemp)
3906           angy = effectiveangle(ay,2*ip-1,bfx)           angy = effectiveangle(ay,2*ip-1,bfx)
3907                    
3908                    
 c         print*,'* ',ip,bfx,bfy,angx,angy  
3909    
3910           id  = CP_STORE(ip,IDCAND) ! couple id           id  = CP_STORE(ip,IDCAND) ! couple id
3911           icl = CLS_STORE(ip,IDCAND)           icl = CLS_STORE(ip,IDCAND)
# Line 3789  c         print*,'* ',ip,bfx,bfy,angx,an Line 3916  c         print*,'* ',ip,bfx,bfy,angx,an
3916           if(ip.eq.6.and.ssensor.ne.0)ssensor = 3 - ssensor !notazione paolo x align           if(ip.eq.6.and.ssensor.ne.0)ssensor = 3 - ssensor !notazione paolo x align
3917           LS(IP,ntr)      = ssensor+10*sladder           LS(IP,ntr)      = ssensor+10*sladder
3918    
3919           if(id.ne.0)then  c         if(id.ne.0)then
3920    CCCCCC(10 novembre 2009) PATCH X NUCLEI
3921    C     non ho capito perche', ma durante il ritracciamento dei nuclei
3922    C     (quando una traccia viene trovata ma non e' buona) c'e' qualche variabile
3923    C     che non viene reinizializzata correttamente e i cluster esclusi
3924    C     dal fit risultano ancora inclusi...
3925    C
3926             cltrx(ip,ntr)   = 0
3927             cltry(ip,ntr)   = 0
3928    c$$$         if(
3929    c$$$     $        xgood_nt(ip,ntr).eq.1.and.ygood_nt(ip,ntr).eq.1
3930    c$$$     $        .and.
3931    c$$$     $        id.ne.0)then
3932             if(id.ne.0)then        !patch 30/12/09
3933    
3934  c           >>> is a couple  c           >>> is a couple
3935              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3936              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3937    
3938              cl_used(cltrx(ip,ntr)) = 1     !tag used clusters                        if(clx(nplanes-ip+1,icp_cp(id)).gt.0)then
3939              cl_used(cltry(ip,ntr)) = 1     !tag used clusters            
3940                   cl_used(cltrx(ip,ntr)) = 1 !tag used clusters          
3941    
3942              xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))                 xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))
             ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))  
3943    
3944                   if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3945         $              dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3946                  
3947                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3948         $              +10000*mult(cltrx(ip,ntr))
3949                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3950         $              /clsigma(indmax(cltrx(ip,ntr)))
3951                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3952                   xpu(ip,ntr)      = corr
3953    
3954              if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)              endif
3955       $           dedx_x(ip,ntr)=-dedx_x(ip,ntr)              if(cly(nplanes-ip+1,icp_cp(id)).gt.0)then
             if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)  
      $           dedx_y(ip,ntr)=-dedx_y(ip,ntr)  
3956    
3957              multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))                 cl_used(cltry(ip,ntr)) = 1 !tag used clusters          
      $                         +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  
3958    
3959              multmaxy(ip,ntr) = maxs(cltry(ip,ntr))                 ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))
      $                         +10000*mult(cltry(ip,ntr))  
             seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))  
      $           /clsigma(indmax(cltry(ip,ntr)))  
             call applypfa(PFA,cltry(ip,ntr),angy,corr,res)  
             ypu(ip,ntr)      = corr  
3960    
3961           elseif(icl.ne.0)then                 if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3962         $              dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3963                  
3964                   multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3965         $              +10000*mult(cltry(ip,ntr))
3966                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3967         $              /clsigma(indmax(cltry(ip,ntr)))
3968                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3969                   ypu(ip,ntr)      = corr
3970                endif
3971    
3972    c$$$         elseif(icl.ne.0)then
3973             endif                  !patch 30/12/09
3974             if(icl.ne.0)then       !patch 30/12/09
3975    
3976              cl_used(icl) = 1    !tag used clusters                        cl_used(icl) = 1    !tag used clusters          
3977    
# Line 3863  c           >>> is a couple Line 4013  c           >>> is a couple
4013           do ip=1,6           do ip=1,6
4014              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)
4015           enddo           enddo
4016             print*,'dedx: '
4017             do ip=1,6
4018                print*,'> ',ip,' -- ',dedx_x(ip,ntr),dedx_y(ip,ntr)
4019             enddo
4020        endif        endif
4021    
 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*,'-----------------------'  
   
4022        end        end
4023    
4024        subroutine fill_level2_siglets        subroutine fill_level2_siglets
# Line 3918  c         if( mask_view(iv).ne.0 )good2( Line 4065  c         if( mask_view(iv).ne.0 )good2(
4065                 sxbad(nclsx)  = nbadstrips(1,icl)                 sxbad(nclsx)  = nbadstrips(1,icl)
4066                 multmaxsx(nclsx) = maxs(icl)+10000*mult(icl)                 multmaxsx(nclsx) = maxs(icl)+10000*mult(icl)
4067                                
 cc               print*,icl,' >>>> ',sxbad(nclsx)  
4068    
4069                 do is=1,2                 do is=1,2
4070  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4071  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
4072                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)                    call xyz_PAM(icl,0,is,PFAdef,'    ',0.,0.,0.,0.)
4073                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2                    xs(is,nclsx) = REAL((xPAM_A+xPAM_B)/2.) ! EM GCC4.7
4074                 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)  
4075              else                          !=== Y views              else                          !=== Y views
4076                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4077                 planey(nclsy) = ip                 planey(nclsy) = ip
# Line 3940  c$$$               print*,'xs(2,nclsx)   Line 4081  c$$$               print*,'xs(2,nclsx)  
4081                 sybad(nclsy)  = nbadstrips(1,icl)                 sybad(nclsy)  = nbadstrips(1,icl)
4082                 multmaxsy(nclsy) = maxs(icl)+10000*mult(icl)                 multmaxsy(nclsy) = maxs(icl)+10000*mult(icl)
4083    
 cc               print*,icl,' >>>> ',sybad(nclsy)  
4084    
4085                 do is=1,2                 do is=1,2
4086  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4087  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
4088                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)                    call xyz_PAM(0,icl,is,'    ',PFAdef,0.,0.,0.,0.)
4089                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2                    ys(is,nclsy) = REAL((yPAM_A+yPAM_B)/2.) ! EM GCC4.7
4090                 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)  
4091              endif              endif
4092           endif           endif
4093    
# Line 4027  c$$$               print*,'ys(2,nclsy)   Line 4162  c$$$               print*,'ys(2,nclsy)  
4162                 alfayz2_av_nt(iyz)=alfayz2_av(iyz)                 alfayz2_av_nt(iyz)=alfayz2_av(iyz)
4163                 nnn=nnn+ptcloud_yz(iyz)                 nnn=nnn+ptcloud_yz(iyz)
4164              enddo              enddo
4165              do ipt=1,nnn              do ipt=1,min(ndblt_max_nt,nnn)
4166                 db_cloud_nt(ipt)=db_cloud(ipt)                 db_cloud_nt(ipt)=db_cloud(ipt)
4167               enddo               enddo
4168           endif           endif
# Line 4040  c$$$               print*,'ys(2,nclsy)   Line 4175  c$$$               print*,'ys(2,nclsy)  
4175                 alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)                 alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)
4176                 nnn=nnn+ptcloud_xz(ixz)                               nnn=nnn+ptcloud_xz(ixz)              
4177              enddo              enddo
4178              do ipt=1,nnn              do ipt=1,min(ntrpt_max_nt,nnn)
4179                tr_cloud_nt(ipt)=tr_cloud(ipt)                tr_cloud_nt(ipt)=tr_cloud(ipt)
4180               enddo               enddo
4181           endif           endif

Legend:
Removed from v.1.35  
changed lines
  Added in v.1.47

  ViewVC Help
Powered by ViewVC 1.1.23