/[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.24 by pam-fi, Tue May 15 16:22:18 2007 UTC revision 1.38 by pam-fi, Tue Dec 23 11:28:36 2008 UTC
# Line 20  Line 20 
20        include 'calib.f'        include 'calib.f'
21        include 'level2.f'        include 'level2.f'
22    
   
   
23  c      print*,'======================================================'  c      print*,'======================================================'
24  c$$$      do ic=1,NCLSTR1  c$$$      do ic=1,NCLSTR1
25  c$$$         if(.false.  c$$$         if(.false.
# Line 74  c$$$      enddo Line 72  c$$$      enddo
72  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
73  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
74    
   
75        call cl_to_couples(iflag)        call cl_to_couples(iflag)
76        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
77           goto 880               !go to next event           goto 880               !go to next event
78        endif        endif
79                if(ncp_tot.eq.0)goto 880  !go to next event    
80  *-----------------------------------------------------  *-----------------------------------------------------
81  *-----------------------------------------------------  *-----------------------------------------------------
82  *     HOUGH TRASFORM  *     HOUGH TRASFORM
# Line 113  c$$$      enddo Line 110  c$$$      enddo
110        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
111           goto 880               !go to next event                       goto 880               !go to next event            
112        endif        endif
113          if(ndblt.eq.0.or.ntrpt.eq.0)goto 880 !go to next event    
114                
115                
116  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
# Line 163  c$$$      enddo Line 161  c$$$      enddo
161        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
162           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
163        endif        endif
164    *     ------------------------------------------------
165    *     first try to release the tolerance
166    *     ------------------------------------------------
167        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then        if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then
168          if(cutdistyz.lt.maxcuty/2)then           if(cutdistyz.lt.maxcuty/2)then
169            cutdistyz=cutdistyz+cutystep              cutdistyz=cutdistyz+cutystep
170          else           else
171            cutdistyz=cutdistyz+(3*cutystep)              cutdistyz=cutdistyz+(3*cutystep)
172          endif           endif
173          goto 878                           if(DEBUG.EQ.1)print*,'try again - cutdistyz ',cutdistyz
174        endif                               goto 878                
175          endif    
176    *     ------------------------------------------------
177    *     hence reduce the minimum number of plane
178    *     ------------------------------------------------
179          if(nclouds_yz.eq.0.and.nplyz_min.gt.3)then
180             nplyz_min=nplyz_min-1
181             if(DEBUG.EQ.1)print*,'try again - nplyz_min ',nplyz_min
182             goto 878
183          endif
184    
185          if(nclouds_yz.eq.0)goto 880 !go to next event    
186    
187        if(planehit.eq.3) goto 881            
188    ccc   if(planehit.eq.3) goto 881    
189                
190   879  continue     879  continue  
191        call trip_to_XZcloud(iflag)        call trip_to_XZcloud(iflag)
192        if(iflag.eq.1)then        !bad event        if(iflag.eq.1)then        !bad event
193           goto 880               !fill ntp and go to next event                       goto 880               !fill ntp and go to next event            
194        endif        endif
195                              *     ------------------------------------------------
196    *     first try to release the tolerance
197    *     ------------------------------------------------                          
198        if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then        if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then
199          cutdistxz=cutdistxz+cutxstep          cutdistxz=cutdistxz+cutxstep
200             if(DEBUG.EQ.1)print*,'try again - cutdistxz ',cutdistxz
201          goto 879                          goto 879                
202        endif                            endif                    
203    *     ------------------------------------------------
204    *     hence reduce the minimum number of plane
205    *     ------------------------------------------------
206          if(nclouds_xz.eq.0.and.nplxz_min.gt.3)then
207             nplxz_min=nplxz_min-1
208             if(DEBUG.EQ.1)print*,'try again - nplxz_min ',nplxz_min
209             goto 879
210          endif
211    
212          if(nclouds_xz.eq.0)goto 880 !go to next event    
213    
214            
215   881  continue    c$$$ 881  continue  
216  *     if there is at least three planes on the Y view decreases cuts on X view  c$$$*     if there is at least three planes on the Y view decreases cuts on X view
217        if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.  c$$$      if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.
218       $     nplxz_min.ne.y_min_start)then  c$$$     $     nplxz_min.ne.y_min_start)then
219          nptxz_min=x_min_step      c$$$        nptxz_min=x_min_step    
220          nplxz_min=x_min_start-x_min_step                c$$$        nplxz_min=x_min_start-x_min_step              
221          goto 879                  c$$$        goto 879                
222        endif                      c$$$      endif                    
223                    
224   880  return   880  return
225        end        end
# Line 215  c$$$      enddo Line 241  c$$$      enddo
241  c      include 'momanhough_init.f'  c      include 'momanhough_init.f'
242                
243        logical FIMAGE            !        logical FIMAGE            !
244          real trackimage(NTRACKSMAX)
245        real*8 AL_GUESS(5)        real*8 AL_GUESS(5)
246    
247  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
# Line 242  c      include 'momanhough_init.f' Line 269  c      include 'momanhough_init.f'
269  *  *
270  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
271  *-------------------------------------------------------------------------------  *-------------------------------------------------------------------------------
272           ntrk=0                 !counter of identified physical tracks  ccc         ntrk=0                 !counter of identified physical tracks
273    
274  11111    continue               !<<<<<<< come here when performing a new search  11111    continue               !<<<<<<< come here when performing a new search
275    
276             if(nclouds_xz.eq.0)goto 880 !go to next event    
277             if(nclouds_yz.eq.0)goto 880 !go to next event    
278    
279  c         iflag=0  c         iflag=0
280           call clouds_to_ctrack(iflag)           call clouds_to_ctrack(iflag)
281           if(iflag.eq.1)then     !no candidate tracks found           if(iflag.eq.1)then     !no candidate tracks found
282              goto 880            !fill ntp and go to next event                goto 880            !fill ntp and go to next event  
283           endif           endif
284             if(ntracks.eq.0)goto 880 !go to next event    
285    
286           FIMAGE=.false.         !processing best track (not track image)           FIMAGE=.false.         !processing best track (not track image)
287           ibest=0                !best track among candidates           ibest=0                !best track among candidates
# Line 294  c$$$         if(ibest.eq.0)goto 880 !>> Line 325  c$$$         if(ibest.eq.0)goto 880 !>>
325             endif             endif
326           enddo           enddo
327    
 c$$$         rchi2best=1000000000.  
 c$$$         ndofbest=0             !(1)  
 c$$$         do i=1,ntracks  
 c$$$           if(RCHI2_STORE(i).lt.rchi2best.and.  
 c$$$     $          RCHI2_STORE(i).gt.0)then  
 c$$$             ndof=0             !(1)  
 c$$$             do ii=1,nplanes    !(1)  
 c$$$               ndof=ndof        !(1)  
 c$$$     $              +int(xgood_store(ii,i)) !(1)  
 c$$$     $              +int(ygood_store(ii,i)) !(1)  
 c$$$             enddo              !(1)  
 c$$$             if(ndof.ge.ndofbest)then !(1)  
 c$$$               ibest=i  
 c$$$               rchi2best=RCHI2_STORE(i)  
 c$$$               ndofbest=ndof    !(1)  
 c$$$             endif              !(1)  
 c$$$           endif  
 c$$$         enddo  
328    
329           if(ibest.eq.0)goto 880 !>> no good candidates           if(ibest.eq.0)goto 880 !>> no good candidates
330  *-------------------------------------------------------------------------------      *-------------------------------------------------------------------------------    
# Line 331  c$$$         enddo Line 344  c$$$         enddo
344              iimage=0              iimage=0
345           endif           endif
346           if(icand.eq.0)then           if(icand.eq.0)then
347              if(VERBOSE)then              if(VERBOSE.EQ.1)then
348                 print*,'HAI FATTO UN CASINO!!!!!! icand = ',icand                 print*,'HAI FATTO UN CASINO!!!!!! icand = ',icand
349       $              ,ibest,iimage       $              ,ibest,iimage
350              endif              endif
# Line 349  c$$$         enddo Line 362  c$$$         enddo
362           do i=1,5           do i=1,5
363              AL_GUESS(i)=AL(i)              AL_GUESS(i)=AL(i)
364           enddo           enddo
 c         print*,'## guess: ',al  
365    
366           do i=1,5           do i=1,5
367              AL(i)=dble(AL_STORE(i,icand))                          AL(i)=dble(AL_STORE(i,icand))            
# Line 360  c         print*,'## guess: ',al Line 372  c         print*,'## guess: ',al
372           jstep=0                !# minimization steps           jstep=0                !# minimization steps
373    
374           iprint=0           iprint=0
375  c         if(DEBUG)iprint=1  c         if(DEBUG.EQ.1)iprint=1
376           if(VERBOSE)iprint=1           if(VERBOSE.EQ.1)iprint=1
377           if(DEBUG)iprint=2           if(DEBUG.EQ.1)iprint=2
378           call mini2(jstep,ifail,iprint)           call mini2(jstep,ifail,iprint)
379           if(ifail.ne.0) then  cc         if(ifail.ne.0) then
380              if(VERBOSE)then           if(ifail.ne.0.or.CHI2.ne.CHI2) then !new
381                if(CHI2.ne.CHI2)CHI2=-9999. !new
382                if(VERBOSE.EQ.1)then
383                 print *,                 print *,
384       $              '*** MINIMIZATION FAILURE *** (after refinement) '       $              '*** MINIMIZATION FAILURE *** (after refinement) '
385       $              ,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*,'----------------------------------------------'  
386              endif              endif
 c            chi2=-chi2  
387           endif           endif
388                    
389           if(DEBUG)then           if(DEBUG.EQ.1)then
390              print*,'----------------------------- improved track coord'              print*,'----------------------------- improved track coord'
391  22222       format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222       format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
392              do ip=1,6              do ip=1,6
# Line 391  c            chi2=-chi2 Line 397  c            chi2=-chi2
397           endif           endif
398    
399  c         rchi2=chi2/dble(ndof)  c         rchi2=chi2/dble(ndof)
400           if(DEBUG)then           if(DEBUG.EQ.1)then
401              print*,' '              print*,' '
402              print*,'****** SELECTED TRACK *************'              print*,'****** SELECTED TRACK *************'
403              print*,'#         R. chi2        RIG'              print*,'#         R. chi2        RIG'
# Line 407  c         rchi2=chi2/dble(ndof) Line 413  c         rchi2=chi2/dble(ndof)
413  *     ------------- search if the track has an IMAGE -------------  *     ------------- search if the track has an IMAGE -------------
414  *     ------------- (also this is stored )           -------------  *     ------------- (also this is stored )           -------------
415           if(FIMAGE)goto 122     !>>> jump! (this is already an image)           if(FIMAGE)goto 122     !>>> jump! (this is already an image)
416  *     now search for track-image, by comparing couples IDs  
417    *     -----------------------------------------------------
418    *     first check if the track is ambiguous
419    *     -----------------------------------------------------
420    *     (modified on august 2007 by ElenaV)
421             is1=0
422             do ip=1,NPLANES
423                if(SENSOR_STORE(ip,icand).ne.0)then
424                   is1=SENSOR_STORE(ip,icand)
425                   if(ip.eq.6)is1=3-is1 !last plane inverted
426                endif
427             enddo
428             if(is1.eq.0)then
429                if(WARNING.EQ.1)print*,'** WARNING ** sensor=0'
430                goto 122            !jump
431             endif
432             do ip=1,NPLANES
433                is2 = SENSOR_STORE(ip,icand) !sensor
434                if(ip.eq.6.and.is2.ne.0)is2=3-is2 !last plane inverted
435                if(
436         $           (is1.ne.is2.and.is2.ne.0)
437         $           )goto 122      !jump (this track cannot have an image)
438             enddo
439             if(DEBUG.eq.1)print*,' >>> ambiguous track! '
440    *     ---------------------------------------------------------------
441    *     take the candidate with the greatest number of matching couples
442    *     if more than one satisfies the requirement,
443    *     choose the one with more points and lower chi2
444    *     ---------------------------------------------------------------
445    *     count the number of matching couples
446             ncpmax = 0
447             iimage   = 0           !id of candidate with better matching
448           do i=1,ntracks           do i=1,ntracks
449              iimage=i              ncp=0
450              do ip=1,nplanes              do ip=1,nplanes
451                 if(     CP_STORE(nplanes-ip+1,icand).ne.                 if(CP_STORE(nplanes-ip+1,icand).ne.0)then
452       $              -1*CP_STORE(nplanes-ip+1,i) )iimage=0                    if(
453         $                 CP_STORE(nplanes-ip+1,i).ne.0
454         $                 .and.
455         $                 CP_STORE(nplanes-ip+1,icand).eq.
456         $                 -1*CP_STORE(nplanes-ip+1,i)
457         $                 )then
458                         ncp=ncp+1  !ok
459                      elseif(
460         $                    CP_STORE(nplanes-ip+1,i).ne.0
461         $                    .and.
462         $                    CP_STORE(nplanes-ip+1,icand).ne.
463         $                    -1*CP_STORE(nplanes-ip+1,i)
464         $                    )then
465                         ncp = 0
466                         goto 117   !it is not an image candidate
467                      else
468                        
469                      endif
470                   endif
471                enddo
472     117        continue
473                trackimage(i)=ncp   !number of matching couples
474                if(ncp>ncpmax)then
475                   ncpmax=ncp
476                   iimage=i
477                endif
478             enddo
479    *     check if there are more than one image candidates
480             ngood=0
481             do i=1,ntracks
482                if( ncpmax.ne.0.and.trackimage(i).eq.ncpmax )ngood=ngood+1
483             enddo
484             if(DEBUG.eq.1)print*,' n.image-candidates : ',ngood
485    *     if there are, choose the best one
486             if(ngood.gt.0)then
487    *     -------------------------------------------------------
488    *     order track-candidates according to:
489    *     1st) decreasing n.points
490    *     2nd) increasing chi**2
491    *     -------------------------------------------------------
492                rchi2best=1000000000.
493                ndofbest=0            
494                do i=1,ntracks
495                   if( trackimage(i).eq.ncpmax )then
496                      ndof=0              
497                      do ii=1,nplanes    
498                         ndof=ndof        
499         $                    +int(xgood_store(ii,i))
500         $                    +int(ygood_store(ii,i))
501                      enddo              
502                      if(ndof.gt.ndofbest)then
503                         iimage=i
504                         rchi2best=RCHI2_STORE(i)
505                         ndofbest=ndof    
506                      elseif(ndof.eq.ndofbest)then
507                         if(RCHI2_STORE(i).lt.rchi2best.and.
508         $                    RCHI2_STORE(i).gt.0)then
509                            iimage=i
510                            rchi2best=RCHI2_STORE(i)
511                            ndofbest=ndof  
512                         endif            
513                      endif
514                   endif
515              enddo              enddo
516              if(  iimage.ne.0.and.  
517  c     $           RCHI2_STORE(i).le.CHI2MAX.and.              if(DEBUG.EQ.1)then
518  c     $           RCHI2_STORE(i).gt.0.and.                 print*,'Track candidate ',iimage
      $           .true.)then  
                if(DEBUG)print*,'Track candidate ',iimage  
519       $              ,' >>> TRACK IMAGE >>> of'       $              ,' >>> TRACK IMAGE >>> of'
520       $              ,ibest       $              ,ibest
                goto 122         !image track found  
521              endif              endif
522           enddo              
523             endif
524    
525    
526   122     continue   122     continue
527    
528    
529  *     --- and store the results --------------------------------  *     --- and store the results --------------------------------
530           ntrk = ntrk + 1                   !counter of found tracks           ntrk = ntrk + 1                   !counter of found tracks
531           if(.not.FIMAGE           if(.not.FIMAGE
# Line 434  c     $           RCHI2_STORE(i).gt.0.an Line 534  c     $           RCHI2_STORE(i).gt.0.an
534       $        .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next       $        .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next
535           if(FIMAGE)     image(ntrk)=ntrk-1 !this is the image of the previous           if(FIMAGE)     image(ntrk)=ntrk-1 !this is the image of the previous
536           call fill_level2_tracks(ntrk)     !==> good2=.true.           call fill_level2_tracks(ntrk)     !==> good2=.true.
 c         print*,'++++++++++ iimage,fimage,ntrk,image '  
 c     $        ,iimage,fimage,ntrk,image(ntrk)  
537    
538           if(ntrk.eq.NTRKMAX)then           if(ntrk.eq.NTRKMAX)then
539              if(verbose)              if(verbose.eq.1)
540       $           print*,       $           print*,
541       $           '** warning ** number of identified '//       $           '** warning ** number of identified '//
542       $           'tracks exceeds vector dimension '       $           'tracks exceeds vector dimension '
# Line 451  cc            good2=.false. Line 549  cc            good2=.false.
549              goto 1212           !>>> fit image-track              goto 1212           !>>> fit image-track
550           endif           endif
551    
 *     --- 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)then  
                print*,'***** NEW SEARCH ****'  
             endif  
             goto 11111          !try new search  
               
          endif  
 *     **********************************************  
   
   
552    
553   880     return   880     return
554        end        end
# Line 572  c     $        rchi2best.lt.15..and. Line 638  c     $        rchi2best.lt.15..and.
638    
639        real stripx,stripy        real stripx,stripy
640    
641          double precision xi,yi,zi
642          double precision xi_A,yi_A,zi_A
643          double precision xi_B,yi_B,zi_B
644        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
645        double precision xrt_A,yrt_A,zrt_A        double precision xrt_A,yrt_A,zrt_A
646        double precision xrt_B,yrt_B,zrt_B        double precision xrt_B,yrt_B,zrt_B
# Line 580  c     $        rchi2best.lt.15..and. Line 649  c     $        rchi2best.lt.15..and.
649        parameter (ndivx=30)        parameter (ndivx=30)
650    
651    
 c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy  
652                
653        resxPAM = 0        resxPAM = 0
654        resyPAM = 0        resyPAM = 0
655    
656        xPAM = 0.        xPAM = 0.D0
657        yPAM = 0.        yPAM = 0.D0
658        zPAM = 0.        zPAM = 0.D0
659        xPAM_A = 0.        xPAM_A = 0.D0
660        yPAM_A = 0.        yPAM_A = 0.D0
661        zPAM_A = 0.        zPAM_A = 0.D0
662        xPAM_B = 0.        xPAM_B = 0.D0
663        yPAM_B = 0.        yPAM_B = 0.D0
664        zPAM_B = 0.        zPAM_B = 0.D0
665  c      print*,'## xyz_PAM: ',icx,icy,sensor,PFAx,PFAy,angx,angy  
666          if(sensor.lt.1.or.sensor.gt.2)then
667             print*,'xyz_PAM   ***ERROR*** wrong input '
668             print*,'sensor ',sensor
669             icx=0
670             icy=0
671          endif
672    
673  *     -----------------  *     -----------------
674  *     CLUSTER X  *     CLUSTER X
675  *     -----------------  *     -----------------      
   
676        if(icx.ne.0)then        if(icx.ne.0)then
677    
678           viewx   = VIEW(icx)           viewx   = VIEW(icx)
679           nldx    = nld(MAXS(icx),VIEW(icx))           nldx    = nld(MAXS(icx),VIEW(icx))
680           nplx    = npl(VIEW(icx))           nplx    = npl(VIEW(icx))
681           resxPAM = RESXAV  c         resxPAM = RESXAV
682           stripx  = float(MAXS(icx))           stripx  = float(MAXS(icx))
683    
684             if(
685         $        viewx.lt.1.or.        
686         $        viewx.gt.12.or.
687         $        nldx.lt.1.or.
688         $        nldx.gt.3.or.
689         $        stripx.lt.1.or.
690         $        stripx.gt.3072.or.
691         $        .false.)then
692                print*,'xyz_PAM   ***ERROR*** wrong input '
693                print*,'icx ',icx,'view ',viewx,'nld ',nldx,'strip ',stripx
694                icx = 0
695                goto 10
696             endif
697    
698  *        --------------------------  *        --------------------------
699  *        magnetic-field corrections  *        magnetic-field corrections
700  *        --------------------------  *        --------------------------
701           angtemp  = ax           stripx  = stripx +  fieldcorr(viewx,bfy)      
702           bfytemp  = bfy           angx    = effectiveangle(ax,viewx,bfy)
 *        /////////////////////////////////  
 *        AAAAHHHHHHHH!!!!!!!!!!!!!!!!!!!!!  
 *        *grvzkkjsdgjhhhgngbn###>:(  
 *        /////////////////////////////////  
 c         if(nplx.eq.6) angtemp = -1. * ax  
 c         if(nplx.eq.6) bfytemp = -1. * bfy  
          if(viewx.eq.12) angtemp = -1. * ax  
          if(viewx.eq.12) bfytemp = -1. * bfy  
          tgtemp   = tan(angtemp*acos(-1.)/180.) + pmuH_h*bfytemp*0.00001  
          angx     = 180.*atan(tgtemp)/acos(-1.)  
          stripx   = stripx - 0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX  
 c$$$         print*,nplx,ax,bfy/10.  
 c$$$         print*,angx,0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX  
 c$$$         print*,'========================'  
 c$$$         if(bfy.ne.0.)print*,viewx,'-x- '  
 c$$$     $        ,bfy,-1*0.5*pmuH_h*bfytemp*0.00001*SiDimZ  
 *        --------------------------  
   
 c$$$         print*,'--- x-cl ---'  
 c$$$         istart = INDSTART(ICX)  
 c$$$         istop  = TOTCLLENGTH  
 c$$$         if(icx.lt.NCLSTR1)istop=INDSTART(ICX+1)-1  
 c$$$         print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)  
 c$$$         print*,(CLSIGNAL(i),i=istart,istop)  
 c$$$         print*,INDMAX(icx)  
 c$$$         print*,cog(4,icx)  
 c$$$         print*,fbad_cog(4,icx)  
703                    
704             call applypfa(PFAx,icx,angx,corr,res)
705             stripx  = stripx + corr
706             resxPAM = res
707    
708           if(PFAx.eq.'COG1')then   10   endif
709        
             stripx  = stripx  
             resxPAM = 1e-4*pitchX/sqrt(12.)!!resxPAM  
   
          elseif(PFAx.eq.'COG2')then  
   
             stripx  = stripx + cog(2,icx)              
             resxPAM = risx_cog(abs(angx))!TEMPORANEO                
             resxPAM = resxPAM*fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'COG3')then  
   
             stripx  = stripx + cog(3,icx)              
             resxPAM = risx_cog(abs(angx))!TEMPORANEO                        
             resxPAM = resxPAM*fbad_cog(3,icx)  
   
          elseif(PFAx.eq.'COG4')then  
   
             stripx  = stripx + cog(4,icx)              
             resxPAM = risx_cog(abs(angx))!TEMPORANEO                        
             resxPAM = resxPAM*fbad_cog(4,icx)  
   
          elseif(PFAx.eq.'ETA2')then  
   
             stripx  = stripx + pfaeta2(icx,angx)            
             resxPAM = risx_eta2(abs(angx))  
             resxPAM = resxPAM*fbad_cog(2,icx)  
             if(DEBUG.and.fbad_cog(2,icx).ne.1)  
      $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'ETA3')then                          
   
             stripx  = stripx + pfaeta3(icx,angx)            
             resxPAM = risx_eta3(abs(angx))                        
             resxPAM = resxPAM*fbad_cog(3,icx)                
             if(DEBUG.and.fbad_cog(3,icx).ne.1)              
      $           print*,'BAD icx >>> ',viewx,fbad_cog(3,icx)  
   
          elseif(PFAx.eq.'ETA4')then                          
   
             stripx  = stripx + pfaeta4(icx,angx)              
             resxPAM = risx_eta4(abs(angx))                        
             resxPAM = resxPAM*fbad_cog(4,icx)                
             if(DEBUG.and.fbad_cog(4,icx).ne.1)                
      $           print*,'BAD icx >>> ',viewx,fbad_cog(4,icx)  
   
          elseif(PFAx.eq.'ETA')then    
   
             stripx  = stripx + pfaeta(icx,angx)              
 c            resxPAM = riseta(icx,angx)                      
             resxPAM = riseta(viewx,angx)                      
             resxPAM = resxPAM*fbad_eta(icx,angx)              
             if(DEBUG.and.fbad_cog(2,icx).ne.1)                
      $           print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)  
   
          elseif(PFAx.eq.'COG')then            
   
             stripx  = stripx + cog(0,icx)              
             resxPAM = risx_cog(abs(angx))                      
             resxPAM = resxPAM*fbad_cog(0,icx)  
   
          else  
             if(DEBUG) print*,'*** Non valid p.f.a. (x) --> ',PFAx  
          endif  
   
   
 *     ======================================  
 *     temporary patch for saturated clusters  
 *     ======================================  
          if( nsatstrips(icx).gt.0 )then  
             stripx  = stripx + cog(4,icx)              
             resxPAM = pitchX*1e-4/sqrt(12.)  
             cc=cog(4,icx)  
 c$$$            print*,icx,' *** ',cc  
 c$$$            print*,icx,' *** ',resxPAM  
          endif  
   
       endif  
         
710  *     -----------------  *     -----------------
711  *     CLUSTER Y  *     CLUSTER Y
712  *     -----------------  *     -----------------
# Line 730  c$$$            print*,icx,' *** ',resxP Line 716  c$$$            print*,icx,' *** ',resxP
716           viewy = VIEW(icy)           viewy = VIEW(icy)
717           nldy = nld(MAXS(icy),VIEW(icy))           nldy = nld(MAXS(icy),VIEW(icy))
718           nply = npl(VIEW(icy))           nply = npl(VIEW(icy))
719           resyPAM = RESYAV  c         resyPAM = RESYAV
720           stripy = float(MAXS(icy))           stripy = float(MAXS(icy))
721    
722             if(
723         $        viewy.lt.1.or.        
724         $        viewy.gt.12.or.
725         $        nldy.lt.1.or.
726         $        nldy.gt.3.or.
727         $        stripy.lt.1.or.
728         $        stripy.gt.3072.or.
729         $        .false.)then
730                print*,'xyz_PAM   ***ERROR*** wrong input '
731                print*,'icy ',icy,'view ',viewy,'nld ',nldy,'strip ',stripy
732                icy = 0
733                goto 20
734             endif
735    
736           if(icx.ne.0.and.(nply.ne.nplx.or.nldy.ne.nldx))then           if(icx.ne.0.and.(nply.ne.nplx.or.nldy.ne.nldx))then
737              if(DEBUG) then              if(DEBUG.EQ.1) then
738                 print*,'xyz_PAM   ***ERROR*** invalid cluster couple!!! '                 print*,'xyz_PAM   ***ERROR*** invalid cluster couple!!! '
739       $              ,icx,icy       $              ,icx,icy
740              endif              endif
741              goto 100              goto 100
742           endif           endif
743    
744  *        --------------------------  *        --------------------------
745  *        magnetic-field corrections  *        magnetic-field corrections
746  *        --------------------------  *        --------------------------
747           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001                   stripy  = stripy +  fieldcorr(viewy,bfx)      
748           angy    = 180.*atan(tgtemp)/acos(-1.)           angy    = effectiveangle(ay,viewy,bfx)
          stripy = stripy + 0.5*pmuH_e*bfx*0.00001*SiDimZ/pitchY  
 c$$$         if(bfx.ne.0.)print*,viewy,'-y- '  
 c$$$     $        ,bfx,0.5*pmuH_e*bfx*0.00001*SiDimZ  
 *        --------------------------  
749                    
750  c$$$         print*,'--- y-cl ---'           call applypfa(PFAy,icy,angy,corr,res)
751  c$$$         istart = INDSTART(ICY)           stripy  = stripy + corr
752  c$$$         istop  = TOTCLLENGTH           resyPAM = res
 c$$$         if(icy.lt.NCLSTR1)istop=INDSTART(ICY+1)-1  
 c$$$         print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)  
 c$$$         print*,(CLSIGNAL(i),i=istart,istop)  
 c$$$         print*,INDMAX(icy)  
 c$$$         print*,cog(4,icy)  
 c$$$         print*,fbad_cog(4,icy)  
   
          if(PFAy.eq.'COG1')then  
   
             stripy  = stripy      
             resyPAM = 1e-4*pitchY/sqrt(12.)!resyPAM    
   
          elseif(PFAy.eq.'COG2')then  
   
             stripy  = stripy + cog(2,icy)  
             resyPAM = risy_cog(abs(angy))!TEMPORANEO  
             resyPAM = resyPAM*fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'COG3')then  
753    
754              stripy  = stripy + cog(3,icy)   20   endif
             resyPAM = risy_cog(abs(angy))!TEMPORANEO  
             resyPAM = resyPAM*fbad_cog(3,icy)  
755    
          elseif(PFAy.eq.'COG4')then  
   
             stripy  = stripy + cog(4,icy)  
             resyPAM = risy_cog(abs(angy))!TEMPORANEO  
             resyPAM = resyPAM*fbad_cog(4,icy)  
   
          elseif(PFAy.eq.'ETA2')then  
   
             stripy  = stripy + pfaeta2(icy,angy)            
             resyPAM = risy_eta2(abs(angy))                
             resyPAM = resyPAM*fbad_cog(2,icy)  
             if(DEBUG.and.fbad_cog(2,icy).ne.1)  
      $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'ETA3')then                        
   
             stripy  = stripy + pfaeta3(icy,angy)  
             resyPAM = resyPAM*fbad_cog(3,icy)    
             if(DEBUG.and.fbad_cog(3,icy).ne.1)  
      $           print*,'BAD icy >>> ',viewy,fbad_cog(3,icy)  
   
          elseif(PFAy.eq.'ETA4')then    
   
             stripy  = stripy + pfaeta4(icy,angy)  
             resyPAM = resyPAM*fbad_cog(4,icy)  
             if(DEBUG.and.fbad_cog(4,icy).ne.1)  
      $           print*,'BAD icy >>> ',viewy,fbad_cog(4,icy)  
   
          elseif(PFAy.eq.'ETA')then  
   
             stripy  = stripy + pfaeta(icy,angy)  
 c            resyPAM = riseta(icy,angy)    
             resyPAM = riseta(viewy,angy)    
             resyPAM = resyPAM*fbad_eta(icy,angy)  
             if(DEBUG.and.fbad_cog(2,icy).ne.1)  
      $           print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)  
   
          elseif(PFAy.eq.'COG')then  
   
             stripy  = stripy + cog(0,icy)              
             resyPAM = risy_cog(abs(angy))  
             resyPAM = resyPAM*fbad_cog(0,icy)  
   
          else  
             if(DEBUG) print*,'*** Non valid p.f.a. (x) --> ',PFAx  
          endif  
   
   
 *     ======================================  
 *     temporary patch for saturated clusters  
 *     ======================================  
          if( nsatstrips(icy).gt.0 )then  
             stripy  = stripy + cog(4,icy)              
             resyPAM = pitchY*1e-4/sqrt(12.)  
             cc=cog(4,icy)  
 c$$$            print*,icy,' *** ',cc  
 c$$$            print*,icy,' *** ',resyPAM  
          endif  
   
   
       endif  
   
 c$$$      print*,'## stripx,stripy ',stripx,stripy  
756    
757  c===========================================================  c===========================================================
758  C     COUPLE  C     COUPLE
# Line 851  c     (xi,yi,zi) = mechanical coordinate Line 764  c     (xi,yi,zi) = mechanical coordinate
764  c------------------------------------------------------------------------  c------------------------------------------------------------------------
765           if(((mod(int(stripx+0.5)-1,1024)+1).le.3)           if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
766       $        .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...
767              if(DEBUG) then              if(DEBUG.EQ.1) then
768                 print*,'xyz_PAM (couple):',                 print*,'xyz_PAM (couple):',
769       $              ' WARNING: false X strip: strip ',stripx       $              ' WARNING: false X strip: strip ',stripx
770              endif              endif
771           endif           endif
772           xi = acoordsi(stripx,viewx)           xi = dcoordsi(stripx,viewx)
773           yi = acoordsi(stripy,viewy)           yi = dcoordsi(stripy,viewy)
774           zi = 0.           zi = 0.D0
775                    
   
776  c------------------------------------------------------------------------  c------------------------------------------------------------------------
777  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
778  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 894  c--------------------------------------- Line 806  c---------------------------------------
806           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
807           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
808    
809           xPAM_A = 0.           xPAM_A = 0.D0
810           yPAM_A = 0.           yPAM_A = 0.D0
811           zPAM_A = 0.           zPAM_A = 0.D0
812    
813           xPAM_B = 0.           xPAM_B = 0.D0
814           yPAM_B = 0.           yPAM_B = 0.D0
815           zPAM_B = 0.           zPAM_B = 0.D0
816    
817        elseif(        elseif(
818       $        (icx.ne.0.and.icy.eq.0).or.       $        (icx.ne.0.and.icy.eq.0).or.
# Line 920  C======================================= Line 832  C=======================================
832              nldx = nldy              nldx = nldy
833              viewx = viewy + 1              viewx = viewy + 1
834    
835              yi   = acoordsi(stripy,viewy)              xi = dcoordsi(0.5*(nstrips+1),viewx) !sensor center
836                yi = dcoordsi(stripy,viewy)
837                zi = 0.D0
838    
839              xi_A = edgeY_d - SiDimX/2              xi_A = edgeY_d - SiDimX/2
840              yi_A = yi              yi_A = yi
# Line 930  C======================================= Line 844  C=======================================
844              yi_B = yi              yi_B = yi
845              zi_B = 0.              zi_B = 0.
846    
 c            print*,'Y-cl ',icy,stripy,' --> ',yi  
 c            print*,xi_A,' <--> ',xi_B  
847                            
848           elseif(icx.ne.0)then           elseif(icx.ne.0)then
849  c===========================================================  c===========================================================
# Line 942  C======================================= Line 854  C=======================================
854              nldy = nldx              nldy = nldx
855              viewy = viewx - 1              viewy = viewx - 1
856    
 c            print*,'X-singlet ',icx,nplx,nldx,viewx,stripx  
 c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...  
857              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)              if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
858       $           .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...
859                 if(DEBUG) then                 if(DEBUG.EQ.1) then
860                    print*,'xyz_PAM (X-singlet):',                    print*,'xyz_PAM (X-singlet):',
861       $                 ' WARNING: false X strip: strip ',stripx       $                 ' WARNING: false X strip: strip ',stripx
862                 endif                 endif
863              endif              endif
864              xi   = acoordsi(stripx,viewx)  
865                xi = dcoordsi(stripx,viewx)
866                yi = dcoordsi(0.5*(nstrips+1),viewy) !sensor center
867                zi = 0.D0
868    
869              xi_A = xi              xi_A = xi
870              yi_A = edgeX_d - SiDimY/2              yi_A = edgeX_d - SiDimY/2
# Line 967  c            if((stripx.le.3).or.(stripx Line 880  c            if((stripx.le.3).or.(stripx
880                 yi_B = yi                 yi_B = yi
881              endif              endif
882    
 c            print*,'X-cl ',icx,stripx,' --> ',xi  
 c            print*,yi_A,' <--> ',yi_B  
883    
884           else           else
885              if(DEBUG) then              if(DEBUG.EQ.1) then
886                 print *,'routine xyz_PAM ---> not properly used !!!'                 print *,'routine xyz_PAM ---> not properly used !!!'
887                 print *,'icx = ',icx                 print *,'icx = ',icx
888                 print *,'icy = ',icy                 print *,'icy = ',icy
# Line 1014  c     N.B. I convert angles from microra Line 925  c     N.B. I convert angles from microra
925       $        + zi_B       $        + zi_B
926       $        + dz(nplx,nldx,sensor)       $        + dz(nplx,nldx,sensor)
927    
928    
929    
930             xrt = xi
931         $        - omega(nplx,nldx,sensor)*yi
932         $        + gamma(nplx,nldx,sensor)*zi
933         $        + dx(nplx,nldx,sensor)
934            
935             yrt = omega(nplx,nldx,sensor)*xi
936         $        + yi
937         $        - beta(nplx,nldx,sensor)*zi
938         $        + dy(nplx,nldx,sensor)
939            
940             zrt = -gamma(nplx,nldx,sensor)*xi
941         $        + beta(nplx,nldx,sensor)*yi
942         $        + zi
943         $        + dz(nplx,nldx,sensor)
944    
945    
946                    
947  c      xrt = xi  c      xrt = xi
948  c      yrt = yi  c      yrt = yi
# Line 1024  c     (xPAM,yPAM,zPAM) = measured coordi Line 953  c     (xPAM,yPAM,zPAM) = measured coordi
953  c                        in PAMELA reference system  c                        in PAMELA reference system
954  c------------------------------------------------------------------------  c------------------------------------------------------------------------
955    
956           xPAM = 0.           xPAM = dcoord(xrt,viewx,nldx,sensor) / 1.d4
957           yPAM = 0.           yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
958           zPAM = 0.           zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
959    c$$$         xPAM = 0.D0
960    c$$$         yPAM = 0.D0
961    c$$$         zPAM = 0.D0
962    
963           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4           xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4
964           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4           yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4
# Line 1037  c--------------------------------------- Line 969  c---------------------------------------
969           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
970                    
971    
 c         print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'  
972    
973        else        else
974           if(DEBUG) then           if(DEBUG.EQ.1) then
975              print *,'routine xyz_PAM ---> not properly used !!!'              print *,'routine xyz_PAM ---> not properly used !!!'
976              print *,'icx = ',icx              print *,'icx = ',icx
977              print *,'icy = ',icy              print *,'icy = ',icy
# Line 1048  c         print*,'A-(',xPAM_A,yPAM_A,') Line 979  c         print*,'A-(',xPAM_A,yPAM_A,')
979        endif        endif
980                    
981    
 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  
982    
983   100  continue   100  continue
984        end        end
# Line 1084  c$$$      common/FINALPFA/PFA Line 1012  c$$$      common/FINALPFA/PFA
1012                
1013  c$$$      PFAx = 'COG4'!PFA  c$$$      PFAx = 'COG4'!PFA
1014  c$$$      PFAy = 'COG4'!PFA  c$$$      PFAy = 'COG4'!PFA
1015    
1016    
1017          if(icx.gt.nclstr1.or.icy.gt.nclstr1)then
1018                print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1019         $           ,' do not exists (n.clusters=',nclstr1,')'
1020                icx = -1*icx
1021                icy = -1*icy
1022                return
1023            
1024          endif
1025                
1026        call idtoc(pfaid,PFAx)        call idtoc(pfaid,PFAx)
1027        call idtoc(pfaid,PFAy)        call idtoc(pfaid,PFAy)
1028    
       call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)  
   
 c$$$      print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy  
1029                
1030        if(icx.ne.0.and.icy.ne.0)then        if(icx.ne.0.and.icy.ne.0)then
1031    
1032           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
1033           ipy=npl(VIEW(icy))           ipy=npl(VIEW(icy))
1034           if( (nplanes-ipx+1).ne.ip.or.(nplanes-ipy+1).ne.ip )          
1035       $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy           if( (nplanes-ipx+1).ne.ip )then
1036       $        ,' does not belong to the correct plane: ',ip,ipx,ipy              print*,'xyzpam: ***WARNING*** cluster ',icx
1037         $           ,' does not belong to plane: ',ip
1038                icx = -1*icx
1039                return
1040             endif
1041             if( (nplanes-ipy+1).ne.ip )then
1042                print*,'xyzpam: ***WARNING*** cluster ',icy
1043         $           ,' does not belong to plane: ',ip
1044                icy = -1*icy
1045                return
1046             endif
1047    
1048             call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1049    
1050           xgood(ip) = 1.           xgood(ip) = 1.
1051           ygood(ip) = 1.           ygood(ip) = 1.
# Line 1108  c$$$      print*,icx,icy,sensor,PFAx,PFA Line 1055  c$$$      print*,icx,icy,sensor,PFAx,PFA
1055           xm(ip) = xPAM           xm(ip) = xPAM
1056           ym(ip) = yPAM           ym(ip) = yPAM
1057           zm(ip) = zPAM           zm(ip) = zPAM
1058           xm_A(ip) = 0.           xm_A(ip) = 0.D0
1059           ym_A(ip) = 0.           ym_A(ip) = 0.D0
1060           xm_B(ip) = 0.           xm_B(ip) = 0.D0
1061           ym_B(ip) = 0.           ym_B(ip) = 0.D0
1062    
1063  c         zv(ip) = zPAM  c         zv(ip) = zPAM
1064    
1065        elseif(icx.eq.0.and.icy.ne.0)then        elseif(icx.eq.0.and.icy.ne.0)then
1066    
1067           ipy=npl(VIEW(icy))           ipy=npl(VIEW(icy))
1068           if((nplanes-ipy+1).ne.ip)           if( (nplanes-ipy+1).ne.ip )then
1069       $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy              print*,'xyzpam: ***WARNING*** cluster ',icy
1070       $        ,' does not belong to the correct plane: ',ip,ipx,ipy       $           ,' does not belong to plane: ',ip
1071                icy = -1*icy
1072                return
1073             endif
1074    
1075             call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1076            
1077           xgood(ip) = 0.           xgood(ip) = 0.
1078           ygood(ip) = 1.           ygood(ip) = 1.
1079           resx(ip)  = 1000.           resx(ip)  = 1000.
1080           resy(ip)  = resyPAM           resy(ip)  = resyPAM
1081    
1082           xm(ip) = -100.  c$$$         xm(ip) = -100.
1083           ym(ip) = -100.  c$$$         ym(ip) = -100.
1084           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1085             xm(ip) = xPAM
1086             ym(ip) = yPAM
1087             zm(ip) = zPAM
1088           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1089           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1090           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1140  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1095  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1095        elseif(icx.ne.0.and.icy.eq.0)then        elseif(icx.ne.0.and.icy.eq.0)then
1096    
1097           ipx=npl(VIEW(icx))           ipx=npl(VIEW(icx))
          if((nplanes-ipx+1).ne.ip)  
      $        print*,'xyzpam: ***WARNING*** clusters ',icx,icy  
      $        ,' does not belong to the correct plane: ',ip,ipx,ipy  
1098    
1099             if( (nplanes-ipx+1).ne.ip )then
1100                print*,'xyzpam: ***WARNING*** cluster ',icx
1101         $           ,' does not belong to plane: ',ip
1102                icx = -1*icx
1103                return
1104             endif
1105    
1106             call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1107          
1108           xgood(ip) = 1.           xgood(ip) = 1.
1109           ygood(ip) = 0.           ygood(ip) = 0.
1110           resx(ip)  = resxPAM           resx(ip)  = resxPAM
1111           resy(ip)  = 1000.           resy(ip)  = 1000.
1112    
1113           xm(ip) = -100.  c$$$         xm(ip) = -100.
1114           ym(ip) = -100.  c$$$         ym(ip) = -100.
1115           zm(ip) = (zPAM_A+zPAM_B)/2.  c$$$         zm(ip) = (zPAM_A+zPAM_B)/2.
1116             xm(ip) = xPAM
1117             ym(ip) = yPAM
1118             zm(ip) = zPAM
1119           xm_A(ip) = xPAM_A           xm_A(ip) = xPAM_A
1120           ym_A(ip) = yPAM_A           ym_A(ip) = yPAM_A
1121           xm_B(ip) = xPAM_B           xm_B(ip) = xPAM_B
# Line 1165  c         zv(ip) = (zPAM_A+zPAM_B)/2. Line 1129  c         zv(ip) = (zPAM_A+zPAM_B)/2.
1129           if(lad.ne.0)il=lad           if(lad.ne.0)il=lad
1130           is = 1           is = 1
1131           if(sensor.ne.0)is=sensor           if(sensor.ne.0)is=sensor
 c         print*,nplanes-ip+1,il,is  
1132    
1133           xgood(ip) = 0.           xgood(ip) = 0.
1134           ygood(ip) = 0.           ygood(ip) = 0.
# Line 1184  c         zv(ip) = z_mech_sensor(nplanes Line 1147  c         zv(ip) = z_mech_sensor(nplanes
1147    
1148        endif        endif
1149    
1150        if(DEBUG)then        if(DEBUG.EQ.1)then
 c         print*,'----------------------------- track coord'  
1151  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)  22222    format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1152           write(*,22222)ip,zm(ip),xm(ip),ym(ip)           write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1153       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)       $        ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1154       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)       $        ,xgood(ip),ygood(ip),resx(ip),resy(ip)
 c$$$         print*,'-----------------------------'  
1155        endif        endif
1156        end        end
1157    
# Line 1214  c$$$         print*,'------------------- Line 1175  c$$$         print*,'-------------------
1175  *      *    
1176  ********************************************************************************  ********************************************************************************
1177    
1178        real function distance_to(XPP,YPP)        real function distance_to(rXPP,rYPP)
1179    
1180        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
1181    
# Line 1223  c$$$         print*,'------------------- Line 1184  c$$$         print*,'-------------------
1184  *     ( i.e. distance/resolution )  *     ( i.e. distance/resolution )
1185  *     -----------------------------------  *     -----------------------------------
1186    
1187          real rXPP,rYPP
1188          double precision XPP,YPP
1189        double precision distance,RE        double precision distance,RE
1190        double precision BETA,ALFA,xmi,ymi        double precision BETA,ALFA,xmi,ymi
1191    
1192          XPP=DBLE(rXPP)
1193          YPP=DBLE(rYPP)
1194    
1195  *     ----------------------  *     ----------------------
1196        if (        if (
1197       +     xPAM.eq.0.and.  c$$$     +     xPAM.eq.0.and.
1198       +     yPAM.eq.0.and.  c$$$     +     yPAM.eq.0.and.
1199       +     zPAM.eq.0.and.  c$$$     +     zPAM.eq.0.and.
1200       +     xPAM_A.ne.0.and.       +     xPAM_A.ne.0.and.
1201       +     yPAM_A.ne.0.and.       +     yPAM_A.ne.0.and.
1202       +     zPAM_A.ne.0.and.       +     zPAM_A.ne.0.and.
# Line 1272  c$$$         print*,'------------------- Line 1238  c$$$         print*,'-------------------
1238  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2  cc     $        ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1239           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1240    
 c$$$         print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',re  
1241    
1242                    
1243  *     ----------------------  *     ----------------------
1244        elseif(        elseif(
1245       +     xPAM.ne.0.and.  c$$$     +     xPAM.ne.0.and.
1246       +     yPAM.ne.0.and.  c$$$     +     yPAM.ne.0.and.
1247       +     zPAM.ne.0.and.  c$$$     +     zPAM.ne.0.and.
1248       +     xPAM_A.eq.0.and.       +     xPAM_A.eq.0.and.
1249       +     yPAM_A.eq.0.and.       +     yPAM_A.eq.0.and.
1250       +     zPAM_A.eq.0.and.       +     zPAM_A.eq.0.and.
# Line 1302  c$$$     $        + Line 1265  c$$$     $        +
1265  c$$$     $        ((yPAM-YPP)/resyPAM)**2  c$$$     $        ((yPAM-YPP)/resyPAM)**2
1266           distance=dsqrt(distance)                               distance=dsqrt(distance)                    
1267    
 c$$$         print*,xPAM,yPAM,zPAM  
 c$$$     $        ,' --- distance_to --- ',xpp,ypp  
 c$$$         print*,' resolution ',resxPAM,resyPAM  
1268                    
1269        else        else
1270                    
 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  
1271        endif          endif  
1272    
1273        distance_to = sngl(distance)        distance_to = sngl(distance)
# Line 1352  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1307  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1307        data c1/1.,0.,0.,1./        data c1/1.,0.,0.,1./
1308        data c2/1.,-1.,-1.,1./        data c2/1.,-1.,-1.,1./
1309        data c3/1.,1.,0.,0./        data c3/1.,1.,0.,0./
1310        real*8 yvvv,xvvv        double precision yvvv,xvvv
1311        double precision xi,yi,zi        double precision xi,yi,zi
1312        double precision xrt,yrt,zrt        double precision xrt,yrt,zrt
1313        real AA,BB        real AA,BB
1314        real yvv(4),xvv(4)        double precision yvv(4),xvv(4)
1315    
1316  *     tollerance to consider the track inside the sensitive area  *     tollerance to consider the track inside the sensitive area
1317        real ptoll        real ptoll
1318        data ptoll/150./          !um        data ptoll/150./          !um
1319    
1320        external nviewx,nviewy,acoordsi,dcoord        external nviewx,nviewy,dcoordsi,dcoord
1321    
1322        nplpt = nplPAM            !plane        nplpt = nplPAM            !plane
1323        viewx = nviewx(nplpt)        viewx = nviewx(nplpt)
# Line 1377  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA Line 1332  c     $        ,xPAM_A,yPAM_A,zPAM_A,xPA
1332  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1333  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1334  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1335                 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)                 xi = dcoordsi(stripx,viewx)
1336       $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...                 yi = dcoordsi(stripy,viewy)
1337  c     if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...                 zi = 0.D0
 c                  print*,'whichsensor: ',  
 c     $                ' WARNING: false X strip: strip ',stripx  
                endif  
                xi = acoordsi(stripx,viewx)  
                yi = acoordsi(stripy,viewy)  
                zi = 0.  
1338  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1339  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame  c     (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
1340  c------------------------------------------------------------------------  c------------------------------------------------------------------------
# Line 1410  c--------------------------------------- Line 1359  c---------------------------------------
1359    
1360                 yvv(iv)=sngl(yvvv)                 yvv(iv)=sngl(yvvv)
1361                 xvv(iv)=sngl(xvvv)                 xvv(iv)=sngl(xvvv)
 c               print*,'LADDER ',il,' SENSOR ',is,' vertexes >> '  
 c     $              ,iv,xvv(iv),yvv(iv)  
1362              enddo               !end loop on sensor vertexes              enddo               !end loop on sensor vertexes
1363    
1364              dtot=0.              dtot=0.
# Line 1536  c      include 'common_analysis.f' Line 1483  c      include 'common_analysis.f'
1483        is_cp=0        is_cp=0
1484        if(id.lt.0)is_cp=1        if(id.lt.0)is_cp=1
1485        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 !!!'  
1486    
1487        return        return
1488        end        end
# Line 1635  c      include 'level1.f' Line 1581  c      include 'level1.f'
1581        integer iflag        integer iflag
1582    
1583        integer badseed,badclx,badcly        integer badseed,badclx,badcly
1584        
1585          if(DEBUG.EQ.1)print*,'cl_to_couples:'
1586    
1587    cc      if(RECOVER_SINGLETS.and..not.SECOND_SEARCH)goto 80
1588    
1589  *     init variables  *     init variables
       ncp_tot=0  
1590        do ip=1,nplanes        do ip=1,nplanes
1591           do ico=1,ncouplemax           do ico=1,ncouplemax
1592              clx(ip,ico)=0              clx(ip,ico)=0
# Line 1650  c      include 'level1.f' Line 1599  c      include 'level1.f'
1599           ncls(ip)=0           ncls(ip)=0
1600        enddo        enddo
1601        do icl=1,nclstrmax_level2        do icl=1,nclstrmax_level2
1602           cl_single(icl) = 1           cl_single(icl) = 1     !all are single
1603           cl_good(icl)   = 0           cl_good(icl)   = 0     !all are bad
1604        enddo        enddo
1605        do iv=1,nviews        do iv=1,nviews
1606           ncl_view(iv)  = 0           ncl_view(iv)  = 0
# Line 1665  c      include 'level1.f' Line 1614  c      include 'level1.f'
1614  *     mask views with too many clusters  *     mask views with too many clusters
1615        do iv=1,nviews        do iv=1,nviews
1616           if( ncl_view(iv).gt. nclusterlimit)then           if( ncl_view(iv).gt. nclusterlimit)then
1617              mask_view(iv) = 1  c            mask_view(iv) = 1
1618              if(DEBUG)print*,' * WARNING * cl_to_couple: n.clusters > '              mask_view(iv) = mask_view(iv) + 2**0
1619       $           ,nclusterlimit,' on view ', iv,' --> masked!'              if(DEBUG.EQ.1)
1620         $        print*,' * WARNING * cl_to_couple: n.clusters > '
1621         $        ,nclusterlimit,' on view ', iv,' --> masked!'
1622           endif           endif
1623        enddo        enddo
1624    
# Line 1677  c      include 'level1.f' Line 1628  c      include 'level1.f'
1628        do icx=1,nclstr1          !loop on cluster (X)        do icx=1,nclstr1          !loop on cluster (X)
1629           if(mod(VIEW(icx),2).eq.1)goto 10           if(mod(VIEW(icx),2).eq.1)goto 10
1630                    
1631             if(cl_used(icx).ne.0)goto 10
1632    
1633  *     ----------------------------------------------------  *     ----------------------------------------------------
1634  *     jump masked views (X VIEW)  *     jump masked views (X VIEW)
1635  *     ----------------------------------------------------  *     ----------------------------------------------------
# Line 1684  c      include 'level1.f' Line 1637  c      include 'level1.f'
1637  *     ----------------------------------------------------  *     ----------------------------------------------------
1638  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1639  *     ----------------------------------------------------  *     ----------------------------------------------------
1640           if(sgnl(icx).lt.dedx_x_min)then           if(sgnl(icx)/mip(VIEW(icx),LADDER(icx)).lt.dedx_x_min)then
1641              cl_single(icx)=0              cl_single(icx)=0
1642              goto 10              goto 10
1643           endif           endif
# Line 1725  c     endif Line 1678  c     endif
1678                    
1679           do icy=1,nclstr1       !loop on cluster (Y)           do icy=1,nclstr1       !loop on cluster (Y)
1680              if(mod(VIEW(icy),2).eq.0)goto 20              if(mod(VIEW(icy),2).eq.0)goto 20
1681    
1682                if(cl_used(icx).ne.0)goto 20
1683                            
1684  *     ----------------------------------------------------  *     ----------------------------------------------------
1685  *     jump masked views (Y VIEW)  *     jump masked views (Y VIEW)
# Line 1734  c     endif Line 1689  c     endif
1689  *     ----------------------------------------------------  *     ----------------------------------------------------
1690  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1691  *     ----------------------------------------------------  *     ----------------------------------------------------
1692              if(sgnl(icy).lt.dedx_y_min)then              if(sgnl(icy)/mip(VIEW(icy),LADDER(icy)) .lt.dedx_y_min)then
1693                 cl_single(icy)=0                 cl_single(icy)=0
1694                 goto 20                 goto 20
1695              endif              endif
# Line 1805  c                  cut = chcut * sch(npl Line 1760  c                  cut = chcut * sch(npl
1760                 endif                 endif
1761    
1762                 if(ncp_plane(nplx).gt.ncouplemax)then                 if(ncp_plane(nplx).gt.ncouplemax)then
1763                    if(verbose)print*,                    if(verbose.eq.1)print*,
1764       $                 '** warning ** number of identified '//       $                 '** warning ** number of identified '//
1765       $                 'couples on plane ',nplx,       $                 'couples on plane ',nplx,
1766       $                 'exceeds vector dimention '       $                 'exceeds vector dimention '
1767       $                 ,'( ',ncouplemax,' ) --> masked!'       $                 ,'( ',ncouplemax,' ) --> masked!'
1768                    mask_view(nviewx(nplx)) = 2  c                  mask_view(nviewx(nplx)) = 2
1769                    mask_view(nviewy(nply)) = 2  c                  mask_view(nviewy(nply)) = 2
1770                      mask_view(nviewx(nplx))= mask_view(nviewx(nplx))+ 2**1
1771                      mask_view(nviewy(nply))= mask_view(nviewy(nply))+ 2**1
1772                    goto 10                    goto 10
1773                 endif                 endif
1774                                
# Line 1831  c                  cut = chcut * sch(npl Line 1788  c                  cut = chcut * sch(npl
1788   10      continue   10      continue
1789        enddo                     !end loop on clusters(X)        enddo                     !end loop on clusters(X)
1790                
         
1791        do icl=1,nclstr1        do icl=1,nclstr1
1792           if(cl_single(icl).eq.1)then           if(cl_single(icl).eq.1)then
1793              ip=npl(VIEW(icl))              ip=npl(VIEW(icl))
# Line 1839  c                  cut = chcut * sch(npl Line 1795  c                  cut = chcut * sch(npl
1795              cls(ip,ncls(ip))=icl              cls(ip,ncls(ip))=icl
1796           endif           endif
1797        enddo        enddo
1798    
1799     80   continue
1800                
1801                
1802        if(DEBUG)then        if(DEBUG.EQ.1)then
1803           print*,'clusters  ',nclstr1           print*,'clusters  ',nclstr1
1804           print*,'good    ',(cl_good(i),i=1,nclstr1)           print*,'good    ',(cl_good(i),i=1,nclstr1)
1805           print*,'singles ',(cl_single(i),i=1,nclstr1)           print*,'used    ',(cl_used(i),i=1,nclstr1)
1806             print*,'singlets',(cl_single(i),i=1,nclstr1)
1807           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)           print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1808        endif        endif
1809    
1810      
1811          if(.not.RECOVER_SINGLETS)goto 81
1812    
1813    *     ////////////////////////////////////////////////
1814    *     PATCH to recover events with less than 3 couples
1815    *     ////////////////////////////////////////////////    
1816    *     loop over singlet and create "fake" couples
1817    *     (with clx=0 or cly=0)
1818    *    
1819    
1820          if(DEBUG.EQ.1)
1821         $     print*,'>>> Recover singlets '
1822         $     ,'(creates fake couples) <<<'
1823          do icl=1,nclstr1
1824             if(
1825         $        cl_single(icl).eq.1.and.
1826         $        cl_used(icl).eq.0.and.
1827         $        .true.)then
1828    *     ----------------------------------------------------
1829    *     jump masked views
1830    *     ----------------------------------------------------
1831                if( mask_view(VIEW(icl)).ne.0 ) goto 21
1832                if(mod(VIEW(icl),2).eq.0)then !=== X views
1833    *     ----------------------------------------------------
1834    *     cut on charge (X VIEW)
1835    *     ----------------------------------------------------
1836                   if(sgnl(icl).lt.dedx_x_min) goto 21
1837                  
1838                   nplx=npl(VIEW(icl))
1839    *     ------------------> (FAKE) COUPLE <-----------------
1840                   ncp_plane(nplx) = ncp_plane(nplx) + 1
1841                   clx(nplx,ncp_plane(nplx))=icl
1842                   cly(nplx,ncp_plane(nplx))=0
1843    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1844    *     ----------------------------------------------------
1845                  
1846                else                !=== Y views
1847    *     ----------------------------------------------------
1848    *     cut on charge (Y VIEW)
1849    *     ----------------------------------------------------
1850                   if(sgnl(icl).lt.dedx_y_min) goto 21
1851                  
1852                   nply=npl(VIEW(icl))
1853    *     ------------------> (FAKE) COUPLE <-----------------
1854                   ncp_plane(nply) = ncp_plane(nply) + 1
1855                   clx(nply,ncp_plane(nply))=0
1856                   cly(nply,ncp_plane(nply))=icl
1857    c$$$  cl_single(icl)=0! I leave the cluster tagged as singlet!!!
1858    *     ----------------------------------------------------
1859                  
1860                endif
1861             endif                  !end "single" condition
1862     21      continue
1863          enddo                     !end loop over clusters
1864    
1865          if(DEBUG.EQ.1)
1866         $     print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1867    
1868    
1869     81   continue
1870                
1871        do ip=1,6        ncp_tot=0
1872          do ip=1,NPLANES
1873           ncp_tot = ncp_tot + ncp_plane(ip)           ncp_tot = ncp_tot + ncp_plane(ip)
1874        enddo        enddo
1875          if(DEBUG.EQ.1)
1876         $     print*,'n.couple tot:      ',ncp_tot
1877                
1878        return        return
1879        end        end
# Line 1904  c      double precision xm3,ym3,zm3 Line 1927  c      double precision xm3,ym3,zm3
1927        real xc,zc,radius        real xc,zc,radius
1928  *     -----------------------------  *     -----------------------------
1929    
1930          if(DEBUG.EQ.1)print*,'cp_to_doubtrip:'
1931    
1932  *     --------------------------------------------  *     --------------------------------------------
1933  *     put a limit to the maximum number of couples  *     put a limit to the maximum number of couples
# Line 1912  c      double precision xm3,ym3,zm3 Line 1936  c      double precision xm3,ym3,zm3
1936  *     --------------------------------------------  *     --------------------------------------------
1937        do ip=1,nplanes        do ip=1,nplanes
1938           if(ncp_plane(ip).gt.ncouplelimit)then           if(ncp_plane(ip).gt.ncouplelimit)then
1939              mask_view(nviewx(ip)) = 8              mask_view(nviewx(ip)) = mask_view(nviewx(ip)) + 2**7
1940              mask_view(nviewy(ip)) = 8              mask_view(nviewy(ip)) = mask_view(nviewy(ip)) + 2**7
1941           endif           endif
1942        enddo        enddo
1943    
# Line 1922  c      double precision xm3,ym3,zm3 Line 1946  c      double precision xm3,ym3,zm3
1946        ntrpt=0                   !number of triplets        ntrpt=0                   !number of triplets
1947                
1948        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1        do ip1=1,(nplanes-1)      !loop on planes  - COPPIA 1
1949    c$$$         print*,'(1) ip ',ip1
1950    c$$$     $        ,mask_view(nviewx(ip1))
1951    c$$$     $        ,mask_view(nviewy(ip1))        
1952           if(  mask_view(nviewx(ip1)).ne.0 .or.           if(  mask_view(nviewx(ip1)).ne.0 .or.
1953       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane       $        mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
1954           do is1=1,2             !loop on sensors - COPPIA 1                       do is1=1,2             !loop on sensors - COPPIA 1            
1955              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1              do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
1956                 icx1=clx(ip1,icp1)                 icx1=clx(ip1,icp1)
1957                 icy1=cly(ip1,icp1)                 icy1=cly(ip1,icp1)
1958                  
1959    c$$$               print*,'(1) ip ',ip1,' icp ',icp1
1960    
1961  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)  c               call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
1962  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)  c               call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
1963                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)                 call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
1964                 xm1=xPAM                 xm1=xPAM
1965                 ym1=yPAM                 ym1=yPAM
1966                 zm1=zPAM                                   zm1=zPAM                  
 c     print*,'***',is1,xm1,ym1,zm1  
1967    
1968                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2                 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
1969    c$$$                  print*,'(2) ip ',ip2
1970    c$$$     $                 ,mask_view(nviewx(ip2))
1971    c$$$     $                 ,mask_view(nviewy(ip2))
1972                    if(  mask_view(nviewx(ip2)).ne.0 .or.                    if(  mask_view(nviewx(ip2)).ne.0 .or.
1973       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane       $                 mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
1974                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                    do is2=1,2    !loop on sensors -ndblt COPPIA 2                    
                       
1975                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2                       do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
1976                          icx2=clx(ip2,icp2)                          icx2=clx(ip2,icp2)
1977                          icy2=cly(ip2,icp2)                          icy2=cly(ip2,icp2)
1978    
1979    c$$$                        print*,'(2) ip ',ip2,' icp ',icp2
1980    
1981  c                        call xyz_PAM  c                        call xyz_PAM
1982  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)  c     $                       (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
1983  c                        call xyz_PAM  c                        call xyz_PAM
# Line 1953  c     $                       (icx2,icy2 Line 1987  c     $                       (icx2,icy2
1987                          xm2=xPAM                          xm2=xPAM
1988                          ym2=yPAM                          ym2=yPAM
1989                          zm2=zPAM                          zm2=zPAM
1990                                                    
1991    *                       ---------------------------------------------------
1992    *                       both couples must have a y-cluster
1993    *                       (condition necessary when in RECOVER_SINGLETS mode)
1994    *                       ---------------------------------------------------
1995                            if(icy1.eq.0.or.icy2.eq.0)goto 111
1996    
1997                            if(cl_used(icy1).ne.0)goto 111
1998                            if(cl_used(icy2).ne.0)goto 111
1999    
2000                            
2001  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2002  *     track parameters on Y VIEW  *     track parameters on Y VIEW
2003  *     (2 couples needed)  *     (2 couples needed)
2004  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2005                          if(ndblt.eq.ndblt_max)then                          if(ndblt.eq.ndblt_max)then
2006                             if(verbose)print*,                             if(verbose.eq.1)print*,
2007       $                          '** warning ** number of identified '//       $                          '** warning ** number of identified '//
2008       $                          'doublets exceeds vector dimention '       $                          'doublets exceeds vector dimention '
2009       $                          ,'( ',ndblt_max,' )'       $                          ,'( ',ndblt_max,' )'
2010  c                           good2=.false.  c     good2=.false.
2011  c                           goto 880 !fill ntp and go to next event  c     goto 880 !fill ntp and go to next event
2012                             do iv=1,12                             do iv=1,12
2013                                mask_view(iv) = 3  c     mask_view(iv) = 3
2014                                  mask_view(iv) = mask_view(iv)+ 2**2
2015                             enddo                             enddo
2016                             iflag=1                             iflag=1
2017                             return                             return
2018                          endif                          endif
2019                            
2020                            
2021    ccc                        print*,'<doublet> ',icp1,icp2
2022    
2023                          ndblt = ndblt + 1                          ndblt = ndblt + 1
2024  *     store doublet info  *     store doublet info
2025                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)                          cpyz1(ndblt)=id_cp(ip1,icp1,is1)
# Line 1979  c                           goto 880 !fi Line 2028  c                           goto 880 !fi
2028                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)                          alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)
2029  *     y0 (cm)  *     y0 (cm)
2030                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1                          alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1
2031                                                      
2032  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2033  ****  reject non phisical couples                    ****  ****  reject non phisical couples                    ****
2034  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2035                            if(SECOND_SEARCH)goto 111
2036                          if(                          if(
2037       $                       abs(alfayz2(ndblt)).gt.alfyz2_max       $                       abs(alfayz2(ndblt)).gt.alfyz2_max
2038       $                       .or.       $                       .or.
2039       $                       abs(alfayz1(ndblt)).gt.alfyz1_max       $                       abs(alfayz1(ndblt)).gt.alfyz1_max
2040       $                       )ndblt = ndblt-1       $                       )ndblt = ndblt-1
2041                                                    
2042  c$$$      if(iev.eq.33)then                          
2043  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$$$  
2044  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2045  *     track parameters on Y VIEW - end  *     track parameters on Y VIEW - end
2046  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2047    
2048    
2049                            if(icx1.ne.0)then
2050                               if(cl_used(icx1).ne.0)goto 31
2051                            endif
2052                            if(icx2.ne.0)then
2053                               if(cl_used(icx2).ne.0)goto 31
2054                            endif
2055    
2056                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples                          if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2057    
2058                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3                          do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2059    c$$$                           print*,'(3) ip ',ip3
2060    c$$$     $                          ,mask_view(nviewx(ip3))
2061    c$$$     $                          ,mask_view(nviewy(ip3))                          
2062                             if(  mask_view(nviewx(ip3)).ne.0 .or.                             if(  mask_view(nviewx(ip3)).ne.0 .or.
2063       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane       $                          mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2064                             do is3=1,2 !loop on sensors - COPPIA 3                             do is3=1,2 !loop on sensors - COPPIA 3
# Line 2011  c$$$ Line 2066  c$$$
2066                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3                                do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
2067                                   icx3=clx(ip3,icp3)                                   icx3=clx(ip3,icp3)
2068                                   icy3=cly(ip3,icp3)                                   icy3=cly(ip3,icp3)
2069    
2070    c$$$                                 print*,'(3) ip ',ip3,' icp ',icp3
2071    
2072    *     ---------------------------------------------------
2073    *     all three couples must have a x-cluster
2074    *     (condition necessary when in RECOVER_SINGLETS mode)
2075    *     ---------------------------------------------------
2076                                     if(
2077         $                                icx1.eq.0.or.
2078         $                                icx2.eq.0.or.
2079         $                                icx3.eq.0.or.
2080         $                                .false.)goto 29
2081                                    
2082                                     if(cl_used(icx1).ne.0)goto 29
2083                                     if(cl_used(icx2).ne.0)goto 29
2084                                     if(cl_used(icx3).ne.0)goto 29
2085    
2086  c                                 call xyz_PAM  c                                 call xyz_PAM
2087  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)  c     $                               (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2088  c                                 call xyz_PAM  c                                 call xyz_PAM
# Line 2021  c     $                               (i Line 2093  c     $                               (i
2093                                   xm3=xPAM                                   xm3=xPAM
2094                                   ym3=yPAM                                   ym3=yPAM
2095                                   zm3=zPAM                                   zm3=zPAM
2096    
2097    
2098  *     find the circle passing through the three points  *     find the circle passing through the three points
2099                                     iflag_t = DEBUG
2100                                   call tricircle(3,xp,zp,angp,resp,chi                                   call tricircle(3,xp,zp,angp,resp,chi
2101       $                                ,xc,zc,radius,iflag)       $                                ,xc,zc,radius,iflag_t)
 c     print*,xc,zc,radius  
2102  *     the circle must intersect the reference plane  *     the circle must intersect the reference plane
2103                                   if(  cc                                 if(iflag.ne.0)goto 29
2104  c     $                                 (xc.le.-1.*xclimit.or.                                   if(iflag_t.ne.0)then
2105  c     $                                 xc.ge.xclimit).and.  *     if tricircle fails, evaluate a straight line
2106       $                                radius**2.ge.(ZINI-zc)**2.and.                                      if(DEBUG.eq.1)
2107       $                                iflag.eq.0.and.       $                                   print*,'TRICIRCLE failure'
2108       $                                .true.)then       $                                   ,' >>> straight line'
2109                                                                        radius=0.
2110                                        xc=0.
2111                                        yc=0.
2112                                        
2113                                        SZZ=0.                  
2114                                        SZX=0.
2115                                        SSX=0.
2116                                        SZ=0.
2117                                        S1=0.
2118                                        X0=0.
2119                                        Ax=0.
2120                                        BX=0.
2121                                        DO I=1,3
2122                                           XX = XP(I)
2123                                           SZZ=SZZ+ZP(I)*ZP(I)
2124                                           SZX=SZX+ZP(I)*XX
2125                                           SSX=SSX+XX
2126                                           SZ=SZ+ZP(I)
2127                                           S1=S1+1.                                    
2128                                        ENDDO
2129                                        DET=SZZ*S1-SZ*SZ
2130                                        AX=(SZX*S1-SZ*SSX)/DET
2131                                        BX=(SZZ*SSX-SZX*SZ)/DET
2132                                        X0  = AX*ZINI+BX
2133                                        
2134                                     endif
2135    
2136                                     if(  .not.SECOND_SEARCH.and.
2137         $                                radius**2.lt.(ZINI-zc)**2)goto 29
2138                                                                      
2139  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2140  *     track parameters on X VIEW  *     track parameters on X VIEW
2141  *     (3 couples needed)  *     (3 couples needed)
2142  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2143                                   if(ntrpt.eq.ntrpt_max)then                                   if(ntrpt.eq.ntrpt_max)then
2144                                      if(verbose)print*,                                      if(verbose.eq.1)print*,
2145       $                     '** warning ** number of identified '//       $                                   '** warning **'//
2146       $                     'triplets exceeds vector dimention '       $                                   ' number of identified '//
2147       $                    ,'( ',ntrpt_max,' )'       $                                   'triplets exceeds'//
2148  c                                    good2=.false.       $                                   ' vector dimention '
2149  c                                    goto 880 !fill ntp and go to next event       $                                   ,'( ',ntrpt_max,' )'
2150    c     good2=.false.
2151    c     goto 880 !fill ntp and go to next event
2152                                      do iv=1,nviews                                      do iv=1,nviews
2153                                         mask_view(iv) = 4  c     mask_view(iv) = 4
2154                                           mask_view(iv) =
2155         $                                      mask_view(iv)+ 2**3
2156                                      enddo                                      enddo
2157                                      iflag=1                                      iflag=1
2158                                      return                                      return
2159                                   endif                                   endif
2160    
2161    ccc                                 print*,'<triplet> ',icp1,icp2,icp3
2162                                    
2163                                   ntrpt = ntrpt +1                                   ntrpt = ntrpt +1
2164  *     store triplet info  *     store triplet info
2165                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)                                   cpxz1(ntrpt)=id_cp(ip1,icp1,is1)
2166                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)                                   cpxz2(ntrpt)=id_cp(ip2,icp2,is2)
2167                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)                                   cpxz3(ntrpt)=id_cp(ip3,icp3,is3)
2168                                                                    
2169                                   if(xc.lt.0)then                                   if(radius.ne.0.and.xc.lt.0)then
2170  *************POSITIVE DEFLECTION  *************POSITIVE DEFLECTION
2171                alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)
2172                alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2173                alfaxz3(ntrpt) = 1/radius               alfaxz3(ntrpt) = 1/radius
2174                                   else                                  else if(radius.ne.0.and.xc.ge.0)then
2175  *************NEGATIVE DEFLECTION  *************NEGATIVE DEFLECTION
2176                alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)               alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)
2177                alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)               alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2178                alfaxz3(ntrpt) = -1/radius               alfaxz3(ntrpt) = -1/radius
2179                                   endif                                  else if(radius.eq.0)then
2180                                    *************straight fit
2181                 alfaxz1(ntrpt) = X0
2182                 alfaxz2(ntrpt) = AX
2183                 alfaxz3(ntrpt) = 0.
2184                                    endif
2185    
2186    c$$$                                print*,'alfaxz1 ', alfaxz1(ntrpt)
2187    c$$$                                print*,'alfaxz2 ', alfaxz2(ntrpt)
2188    c$$$                                print*,'alfaxz3 ', alfaxz3(ntrpt)
2189                                        
2190  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2191  ****  reject non phisical triplets                   ****  ****  reject non phisical triplets                   ****
2192  ****  -----------------------------------------------****  ****  -----------------------------------------------****
2193                                   if(                                  if(SECOND_SEARCH)goto 29
2194       $                                abs(alfaxz2(ntrpt)).gt.alfxz2_max                                  if(
2195       $                                .or.       $                               abs(alfaxz2(ntrpt)).gt.
2196       $                                abs(alfaxz1(ntrpt)).gt.alfxz1_max       $                               alfxz2_max
2197       $                                )ntrpt = ntrpt-1       $                               .or.
2198                                         $                               abs(alfaxz1(ntrpt)).gt.
2199                                         $                               alfxz1_max
2200  c     print*,alfaxz1(ntrpt),alfaxz2(ntrpt),alfaxz3(ntrpt)       $                               )ntrpt = ntrpt-1
2201                                                                    
2202  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2203  *     track parameters on X VIEW - end  *     track parameters on X VIEW - end
2204  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -  *     - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2205                                endif                                
2206     29                           continue
2207                             enddo !end loop on COPPIA 3                             enddo !end loop on COPPIA 3
2208                          enddo   !end loop on sensors - COPPIA 3                          enddo   !end loop on sensors - COPPIA 3
2209   30                     continue   30                     continue
2210                       enddo      !end loop on planes  - COPPIA 3                       enddo      !end loop on planes  - COPPIA 3
2211   31                  continue  
2212                         31                  continue                    
2213   1                enddo         !end loop on COPPIA 2   1                enddo         !end loop on COPPIA 2
2214                 enddo            !end loop on sensors - COPPIA 2                 enddo            !end loop on sensors - COPPIA 2
2215   20            continue   20            continue
2216              enddo               !end loop on planes  - COPPIA 2              enddo               !end loop on planes  - COPPIA 2
2217                
2218     11         continue
2219           enddo                  !end loop on COPPIA1           enddo                  !end loop on COPPIA1
2220        enddo                     !end loop on sensors - COPPIA 1        enddo                     !end loop on sensors - COPPIA 1
2221   10   continue   10   continue
2222        enddo                     !end loop on planes  - COPPIA 1        enddo                     !end loop on planes  - COPPIA 1
2223                
2224        if(DEBUG)then        if(DEBUG.EQ.1)then
2225           print*,'--- doublets ',ndblt           print*,'--- doublets ',ndblt
2226           print*,'--- triplets ',ntrpt           print*,'--- triplets ',ntrpt
2227        endif        endif
# Line 2146  c      include 'momanhough_init.f' Line 2268  c      include 'momanhough_init.f'
2268        integer cp_useds1(ncouplemaxtot) ! sensor 1        integer cp_useds1(ncouplemaxtot) ! sensor 1
2269        integer cp_useds2(ncouplemaxtot) ! sensor 2        integer cp_useds2(ncouplemaxtot) ! sensor 2
2270    
2271          if(DEBUG.EQ.1)print*,'doub_to_YZcloud:'
2272    
2273  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2274  *     classification of DOUBLETS  *     classification of DOUBLETS
# Line 2164  c      include 'momanhough_init.f' Line 2287  c      include 'momanhough_init.f'
2287        do idb1=1,ndblt           !loop (1) on DOUBLETS        do idb1=1,ndblt           !loop (1) on DOUBLETS
2288           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
2289                            
 c     print*,'--------------'  
 c     print*,'** ',idb1,' **'  
               
2290           do icp=1,ncp_tot           do icp=1,ncp_tot
2291              cp_useds1(icp)=0    !init              cp_useds1(icp)=0    !init
2292              cp_useds2(icp)=0    !init              cp_useds2(icp)=0    !init
# Line 2205  ccccc if(db_used(idbref).eq.1)goto 1188 Line 2325  ccccc if(db_used(idbref).eq.1)goto 1188
2325       $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2                     $              +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2              
2326                 distance = sqrt(distance)                 distance = sqrt(distance)
2327                                
 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  
2328                 if(distance.lt.cutdistyz)then                 if(distance.lt.cutdistyz)then
2329    
 c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  
2330                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1                    if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1
2331                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1                    if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1
2332                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1                    if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1
# Line 2230  c     print*,idb1,idb2,distance,' cloud Line 2342  c     print*,idb1,idb2,distance,' cloud
2342    
2343                    temp1 = temp1 + alfayz1(idb2)                    temp1 = temp1 + alfayz1(idb2)
2344                    temp2 = temp2 + alfayz2(idb2)                    temp2 = temp2 + alfayz2(idb2)
 c     print*,'*   idbref,idb2 ',idbref,idb2  
2345                 endif                               endif              
2346                                
2347   1118          continue   1118          continue
# Line 2253  c     print*,'*   idbref,idb2 ',idbref,i Line 2364  c     print*,'*   idbref,idb2 ',idbref,i
2364           enddo           enddo
2365           ncpused=0           ncpused=0
2366           do icp=1,ncp_tot           do icp=1,ncp_tot
2367              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2368         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2369         $           .true.)then
2370                 ncpused=ncpused+1                 ncpused=ncpused+1
2371                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2372                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2263  c     print*,'*   idbref,idb2 ',idbref,i Line 2376  c     print*,'*   idbref,idb2 ',idbref,i
2376           do ip=1,nplanes           do ip=1,nplanes
2377              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2378           enddo           enddo
2379  c     print*,'>>>> ',ncpused,npt,nplused          
 c         if(ncpused.lt.ncpyz_min)goto 2228 !next doublet  
          if(npt.lt.nptyz_min)goto 2228 !next doublet  
2380           if(nplused.lt.nplyz_min)goto 2228 !next doublet           if(nplused.lt.nplyz_min)goto 2228 !next doublet
2381                    
2382  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
2383  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2384    
2385           if(nclouds_yz.ge.ncloyz_max)then           if(nclouds_yz.ge.ncloyz_max)then
2386              if(verbose)print*,              if(verbose.eq.1)print*,
2387       $           '** warning ** number of identified '//       $           '** warning ** number of identified '//
2388       $           'YZ clouds exceeds vector dimention '       $           'YZ clouds exceeds vector dimention '
2389       $           ,'( ',ncloyz_max,' )'       $           ,'( ',ncloyz_max,' )'
2390  c               good2=.false.  c               good2=.false.
2391  c     goto 880         !fill ntp and go to next event  c     goto 880         !fill ntp and go to next event
2392              do iv=1,nviews              do iv=1,nviews
2393                 mask_view(iv) = 5  c               mask_view(iv) = 5
2394                   mask_view(iv) = mask_view(iv) + 2**4
2395              enddo              enddo
2396              iflag=1              iflag=1
2397              return              return
# Line 2296  c     goto 880         !fill ntp and go Line 2408  c     goto 880         !fill ntp and go
2408  c     ptcloud_yz_nt(nclouds_yz)=npt  c     ptcloud_yz_nt(nclouds_yz)=npt
2409           do ipt=1,npt           do ipt=1,npt
2410              db_cloud(npt_tot+ipt) = db_all(ipt)              db_cloud(npt_tot+ipt) = db_all(ipt)
 c     print*,'>> ',ipt,db_all(ipt)  
2411           enddo             enddo  
2412           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2413           if(DEBUG)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2414              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'              print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2415              print*,'- alfayz1 ',alfayz1_av(nclouds_yz)              print*,'- alfayz1  ',alfayz1_av(nclouds_yz)
2416              print*,'- alfayz2 ',alfayz2_av(nclouds_yz)              print*,'- alfayz2  ',alfayz2_av(nclouds_yz)
2417              print*,'cp_useds1 ',(cp_useds1(icp),icp=1,ncp_tot)              print*,'cp_useds1  ',(cp_useds1(icp),icp=1,ncp_tot)
2418              print*,'cp_useds2 ',(cp_useds2(icp),icp=1,ncp_tot)              print*,'cp_useds2  ',(cp_useds2(icp),icp=1,ncp_tot)
2419              print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)              print*,'cpcloud_yz '
2420  c$$$            print*,'nt-uple: ptcloud_yz(',nclouds_yz,') = '       $           ,(cpcloud_yz(nclouds_yz,icp),icp=1,ncp_tot)
2421  c$$$     $           ,ptcloud_yz(nclouds_yz)              print*,'hit_plane  ',(hit_plane(ip),ip=1,nplanes)
 c$$$            print*,'nt-uple: db_cloud(...) = '  
 c$$$     $           ,(db_cloud(iii),iii=npt_tot-npt+1,npt_tot)  
2422           endif           endif
2423  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2424  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2324  c$$$     $           ,(db_cloud(iii),iii Line 2432  c$$$     $           ,(db_cloud(iii),iii
2432          goto 90                          goto 90                
2433        endif                            endif                    
2434                
2435        if(DEBUG)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2436           print*,'Y-Z total clouds ',nclouds_yz           print*,'Y-Z total clouds ',nclouds_yz
          print*,' '  
2437        endif        endif
2438                
2439                
# Line 2373  c      include 'momanhough_init.f' Line 2479  c      include 'momanhough_init.f'
2479        integer cp_useds1(ncouplemaxtot) ! sensor 1        integer cp_useds1(ncouplemaxtot) ! sensor 1
2480        integer cp_useds2(ncouplemaxtot) ! sensor 2        integer cp_useds2(ncouplemaxtot) ! sensor 2
2481    
2482          if(DEBUG.EQ.1)print*,'trip_to_XZcloud:'
2483    
2484  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~  *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2485  *     classification of TRIPLETS  *     classification of TRIPLETS
2486  *     according to distance in parameter space  *     according to distance in parameter space
# Line 2388  c      include 'momanhough_init.f' Line 2496  c      include 'momanhough_init.f'
2496   91   continue                     91   continue                  
2497        do itr1=1,ntrpt           !loop (1) on TRIPLETS        do itr1=1,ntrpt           !loop (1) on TRIPLETS
2498           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,' **'  
2499                    
2500           do icp=1,ncp_tot           do icp=1,ncp_tot
2501              cp_useds1(icp)=0              cp_useds1(icp)=0
# Line 2423  c         tr_temp(1)=itr1 Line 2529  c         tr_temp(1)=itr1
2529              do itr2=1,ntrpt     !loop (2) on TRIPLETS              do itr2=1,ntrpt     !loop (2) on TRIPLETS
2530                 if(itr2.eq.itr1)goto 11188       !next triplet                 if(itr2.eq.itr1)goto 11188       !next triplet
2531                 if(tr_used(itr2).eq.1)goto 11188 !next triplet                               if(tr_used(itr2).eq.1)goto 11188 !next triplet              
2532    
2533    
2534  *     triplet distance in parameter space  *     triplet distance in parameter space
2535  *     solo i due parametri spaziali per il momemnto  *     solo i due parametri spaziali per il momemnto
2536                 distance=                 distance=
2537       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2       $              ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2
2538       $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2                     $              +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2              
2539                 distance = sqrt(distance)                 distance = sqrt(distance)
2540                  
2541                 if(distance.lt.cutdistxz)then  
2542  c     print*,idb1,idb2,distance,' cloud ',nclouds_yz  *     ------------------------------------------------------------------------
2543    *     FORCE INCLUSION OF TRIPLETS COMPOSED BY SAME COUPLES, IGNORING THE IMAGE
2544    *     ------------------------------------------------------------------------
2545    *     (added in august 2007)
2546                   istrimage=0
2547                   if(
2548         $              abs(cpxz1(itrref)).eq.abs(cpxz1(itr2)).and.
2549         $              abs(cpxz2(itrref)).eq.abs(cpxz2(itr2)).and.
2550         $              abs(cpxz3(itrref)).eq.abs(cpxz3(itr2)).and.
2551         $              .true.)istrimage=1
2552    
2553                   if(distance.lt.cutdistxz.or.istrimage.eq.1)then
2554                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1                    if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2555                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1                    if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
2556                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1                    if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1
# Line 2450  c     print*,idb1,idb2,distance,' cloud Line 2569  c     print*,idb1,idb2,distance,' cloud
2569                    temp1 = temp1 + alfaxz1(itr2)                    temp1 = temp1 + alfaxz1(itr2)
2570                    temp2 = temp2 + alfaxz2(itr2)                    temp2 = temp2 + alfaxz2(itr2)
2571                    temp3 = temp3 + alfaxz3(itr2)                    temp3 = temp3 + alfaxz3(itr2)
 c     print*,'*   itrref,itr2 ',itrref,itr2,distance  
2572                 endif                               endif              
2573                                
2574  11188          continue  11188          continue
# Line 2471  c     print*,'*   itrref,itr2 ',itrref,i Line 2589  c     print*,'*   itrref,itr2 ',itrref,i
2589  *     1bis)  *     1bis)
2590  *     2) it is not already stored  *     2) it is not already stored
2591  *     ------------------------------------------  *     ------------------------------------------
 c     print*,'check cp_used'  
2592           do ip=1,nplanes           do ip=1,nplanes
2593              hit_plane(ip)=0              hit_plane(ip)=0
2594           enddo           enddo
2595           ncpused=0           ncpused=0
2596           do icp=1,ncp_tot           do icp=1,ncp_tot
2597              if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then              if(
2598         $           (cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0).and.
2599         $           .true.)then
2600                 ncpused=ncpused+1                 ncpused=ncpused+1
2601                 ip=ip_cp(icp)                 ip=ip_cp(icp)
2602                 hit_plane(ip)=1                 hit_plane(ip)=1
# Line 2487  c     print*,'check cp_used' Line 2606  c     print*,'check cp_used'
2606           do ip=1,nplanes           do ip=1,nplanes
2607              nplused=nplused+ hit_plane(ip)              nplused=nplused+ hit_plane(ip)
2608           enddo           enddo
 c         if(ncpused.lt.ncpxz_min)goto 22288 !next triplet  
          if(npt.lt.nptxz_min)goto 22288     !next triplet  
2609           if(nplused.lt.nplxz_min)goto 22288 !next triplet           if(nplused.lt.nplxz_min)goto 22288 !next triplet
2610                    
2611  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
2612  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2613           if(nclouds_xz.ge.ncloxz_max)then           if(nclouds_xz.ge.ncloxz_max)then
2614              if(verbose)print*,              if(verbose.eq.1)print*,
2615       $           '** warning ** number of identified '//       $           '** warning ** number of identified '//
2616       $           'XZ clouds exceeds vector dimention '       $           'XZ clouds exceeds vector dimention '
2617       $           ,'( ',ncloxz_max,' )'       $           ,'( ',ncloxz_max,' )'
2618  c     good2=.false.  c     good2=.false.
2619  c     goto 880         !fill ntp and go to next event  c     goto 880         !fill ntp and go to next event
2620              do iv=1,nviews              do iv=1,nviews
2621                 mask_view(iv) = 6  c               mask_view(iv) = 6
2622                   mask_view(iv) =  mask_view(iv) + 2**5
2623              enddo              enddo
2624              iflag=1              iflag=1
2625              return              return
# Line 2520  c     goto 880         !fill ntp and go Line 2638  c     goto 880         !fill ntp and go
2638           enddo           enddo
2639           npt_tot=npt_tot+npt           npt_tot=npt_tot+npt
2640                    
2641           if(DEBUG)then           if(DEBUG.EQ.1)then
             print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'  
2642              print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'                            print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'              
2643              print*,'- alfaxz1 ',alfaxz1_av(nclouds_xz)              print*,'- alfaxz1  ',alfaxz1_av(nclouds_xz)
2644              print*,'- alfaxz2 ',alfaxz2_av(nclouds_xz)              print*,'- alfaxz2  ',alfaxz2_av(nclouds_xz)
2645              print*,'- alfaxz3 ',alfaxz3_av(nclouds_xz)              print*,'- alfaxz3  ',alfaxz3_av(nclouds_xz)
2646              print*,'cp_useds1 ',(cp_useds1(icp),icp=1,ncp_tot)              print*,'cp_useds1  ',(cp_useds1(icp),icp=1,ncp_tot)
2647              print*,'cp_useds2 ',(cp_useds2(icp),icp=1,ncp_tot)              print*,'cp_useds2  ',(cp_useds2(icp),icp=1,ncp_tot)
2648                print*,'cpcloud_xz '
2649         $           ,(cpcloud_xz(nclouds_xz,icp),icp=1,ncp_tot)
2650              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)  
2651           endif           endif
2652  *     >>> NEW CLOUD <<<  *     >>> NEW CLOUD <<<
2653  *     ~~~~~~~~~~~~~~~~~  *     ~~~~~~~~~~~~~~~~~
# Line 2545  c$$$     $           ,(tr_cloud(iii),iii Line 2660  c$$$     $           ,(tr_cloud(iii),iii
2660           goto 91                           goto 91                
2661         endif                             endif                    
2662                
2663        if(DEBUG)then        if(DEBUG.EQ.1)then
          print*,'---------------------- '  
2664           print*,'X-Z total clouds ',nclouds_xz           print*,'X-Z total clouds ',nclouds_xz
          print*,' '  
2665        endif        endif
2666                
2667                
# Line 2597  c$$$     $           ,(tr_cloud(iii),iii Line 2710  c$$$     $           ,(tr_cloud(iii),iii
2710  *     -----------------------------------------------------------  *     -----------------------------------------------------------
2711  *     variables for track fitting  *     variables for track fitting
2712        double precision AL_INI(5)        double precision AL_INI(5)
 c      double precision tath  
2713  *     -----------------------------------------------------------  *     -----------------------------------------------------------
 c      real fitz(nplanes)        !z coordinates of the planes in cm  
2714    
2715          if(DEBUG.EQ.1)print*,'clouds_to_ctrack:'
2716    
2717    
2718        ntracks=0                 !counter of track candidates        ntracks=0                 !counter of track candidates
2719                
2720        do iyz=1,nclouds_yz       !loop on YZ couds        do iyz=1,nclouds_yz       !loop on YZ clouds
2721           do ixz=1,nclouds_xz    !loop on XZ couds           do ixz=1,nclouds_xz    !loop on XZ clouds
2722                            
2723  *     --------------------------------------------------  *     --------------------------------------------------
2724  *     check of consistency of the clouds  *     check of consistency of the clouds
# Line 2615  c      real fitz(nplanes)        !z coor Line 2727  c      real fitz(nplanes)        !z coor
2727  *     of the two clouds  *     of the two clouds
2728  *     --------------------------------------------------  *     --------------------------------------------------
2729              do ip=1,nplanes              do ip=1,nplanes
2730                 hit_plane(ip)=0                 hit_plane(ip)=0  !n.matching couples (REAL couples, not SINGLETS)
2731                 ncp_match(ip)=0                 ncp_match(ip)=0  !n.matching couples per plane
2732                 do icpp=1,ncouplemax                 do icpp=1,ncouplemax
2733                    cp_match(ip,icpp)=0 !init couple list                    cp_match(ip,icpp)=0 !init couple list
2734                 enddo                 enddo
2735              enddo              enddo
2736              ncp_ok=0              ncp_ok=0            !count n.matching-couples
2737              do icp=1,ncp_tot    !loop on couples              ncpx_ok=0           !count n.matching-couples with x cluster
2738  *     get info on              ncpy_ok=0           !count n.matching-couples with y cluster
2739                 cpintersec(icp)=min(  
2740       $              cpcloud_yz(iyz,icp),  
2741       $              cpcloud_xz(ixz,icp))              do icp=1,ncp_tot    !loop over couples
2742                 if(  
2743       $    (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.                 if(.not.RECOVER_SINGLETS)then
2744       $    (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.  *     ------------------------------------------------------
2745       $              .false.)cpintersec(icp)=0  *     if NOT in RECOVER_SINGLETS mode, take the intersection
2746    *     between xz yz clouds
2747    *     ------------------------------------------------------
2748                      cpintersec(icp)=min(
2749         $                 cpcloud_yz(iyz,icp),
2750         $                 cpcloud_xz(ixz,icp))
2751    *     cpintersec is >0 if yz and xz clouds contain the same image of couple icp
2752    *     ------------------------------------------------------
2753    *     discard the couple if the sensor is in conflict
2754    *     ------------------------------------------------------
2755                      if(
2756         $       (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2757         $       (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2758         $                 .false.)cpintersec(icp)=0
2759                   else
2760    *     ------------------------------------------------------
2761    *     if RECOVER_SINGLETS take the union
2762    *     (otherwise the fake couples formed by singlets would be
2763    *     discarded)    
2764    *     ------------------------------------------------------
2765                      cpintersec(icp)=max(
2766         $                 cpcloud_yz(iyz,icp),
2767         $                 cpcloud_xz(ixz,icp))
2768    c$$$                  if(cpcloud_yz(iyz,icp).gt.0)
2769    c$$$     $                 cpintersec(icp)=cpcloud_yz(iyz,icp)
2770    *     cpintersec is >0 if either yz or xz cloud contains the couple icp
2771                   endif
2772    
2773    c$$$               print*,icp,ip_cp(icp),' -- ',cpintersec(icp)
2774    
2775                 if(cpintersec(icp).ne.0)then                 if(cpintersec(icp).ne.0)then
                   ncp_ok=ncp_ok+1    
2776                                        
2777                    ip=ip_cp(icp)                    ip=ip_cp(icp)
2778                    hit_plane(ip)=1                    hit_plane(ip)=1
2779    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).gt.0)
2780    c$$$     $                 ncp_ok=ncp_ok+1  
2781    c$$$                  if(clx(ip,icp).gt.0.and.cly(ip,icp).eq.0)
2782    c$$$     $                 ncpx_ok=ncpx_ok+1
2783    c$$$                  if(clx(ip,icp).eq.0.and.cly(ip,icp).gt.0)
2784    c$$$     $                 ncpy_ok=ncpy_ok+1
2785    
2786                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2787         $                 cpcloud_xz(ixz,icp).gt.0)
2788         $                 ncp_ok=ncp_ok+1  
2789                      if(  cpcloud_yz(iyz,icp).gt.0.and.
2790         $                 cpcloud_xz(ixz,icp).eq.0)
2791         $                 ncpy_ok=ncpy_ok+1  
2792                      if(  cpcloud_yz(iyz,icp).eq.0.and.
2793         $                 cpcloud_xz(ixz,icp).gt.0)
2794         $                 ncpx_ok=ncpx_ok+1  
2795    
2796                    if(cpintersec(icp).eq.1)then                    if(cpintersec(icp).eq.1)then
2797  *     1) only the couple image in sensor 1 matches  *     1) only the couple image in sensor 1 matches
2798                       id=-icp                       id=-icp
# Line 2662  c      real fitz(nplanes)        !z coor Line 2819  c      real fitz(nplanes)        !z coor
2819              do ip=1,nplanes              do ip=1,nplanes
2820                 nplused=nplused+ hit_plane(ip)                 nplused=nplused+ hit_plane(ip)
2821              enddo              enddo
               
 c            if(nplused.lt.nplxz_min)goto 888 !next doublet  
             if(nplused.lt.nplyz_min)goto 888 !next doublet  
             if(ncp_ok.lt.ncpok)goto 888 !next cloud  
               
             if(DEBUG)then  
                print*,'Combination ',iyz,ixz  
      $              ,' db ',ptcloud_yz(iyz)  
      $              ,' tr ',ptcloud_xz(ixz)  
      $              ,'  -----> # matching couples ',ncp_ok  
             endif  
 c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'  
 c$$$  print*,'Configurazione cluster XZ'  
 c$$$  print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))  
 c$$$  print*,'2 -- ',(clx(2,i),i=1,ncp_plane(1))  
 c$$$  print*,'3 -- ',(clx(3,i),i=1,ncp_plane(1))  
 c$$$  print*,'4 -- ',(clx(4,i),i=1,ncp_plane(1))  
 c$$$  print*,'5 -- ',(clx(5,i),i=1,ncp_plane(1))  
 c$$$  print*,'6 -- ',(clx(6,i),i=1,ncp_plane(1))  
 c$$$  print*,'Configurazione cluster YZ'  
 c$$$  print*,'1 -- ',(cly(1,i),i=1,ncp_plane(1))  
 c$$$  print*,'2 -- ',(cly(2,i),i=1,ncp_plane(1))  
 c$$$  print*,'3 -- ',(cly(3,i),i=1,ncp_plane(1))  
 c$$$  print*,'4 -- ',(cly(4,i),i=1,ncp_plane(1))  
 c$$$  print*,'5 -- ',(cly(5,i),i=1,ncp_plane(1))  
 c$$$  print*,'6 -- ',(cly(6,i),i=1,ncp_plane(1))  
 c$$$  print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'  
               
 *     -------> INITIAL GUESS <-------  
 cccc       SBAGLIATO  
 c$$$            AL_INI(1) = dreal(alfaxz1_av(ixz))  
 c$$$            AL_INI(2) = dreal(alfayz1_av(iyz))  
 c$$$            AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))  
 c$$$     $           /dreal(alfaxz2_av(ixz)))  
 c$$$            tath      = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))  
 c$$$            AL_INI(3) = tath/sqrt(1+tath**2)  
 c$$$            AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.  
 cccc       GIUSTO (ma si sua guess())  
 c$$$            AL_INI(1) = dreal(alfaxz1_av(ixz))  
 c$$$            AL_INI(2) = dreal(alfayz1_av(iyz))  
 c$$$            tath      = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))  
 c$$$            AL_INI(3) = tath/sqrt(1+tath**2)  
 c$$$            IF(alfaxz2_av(ixz).NE.0)THEN  
 c$$$            AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))  
 c$$$     $           /dreal(alfaxz2_av(ixz)))  
 c$$$            ELSE  
 c$$$               AL_INI(4) = acos(-1.)/2  
 c$$$               IF(alfayz2_av(iyz).LT.0)AL_INI(4) = AL_INI(4)+acos(-1.)  
 c$$$            ENDIF  
 c$$$            IF(alfaxz2_av(ixz).LT.0)AL_INI(4)= acos(-1.)+ AL_INI(4)  
 c$$$            AL_INI(4) = -acos(-1.) + AL_INI(4) !from incidence direction to tracking rs  
 c$$$              
 c$$$            AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.  
 c$$$              
 c$$$            if(AL_INI(5).gt.defmax)goto 888 !next cloud  
2822                                                    
2823              if(DEBUG)then              if(nplused.lt.3)goto 888 !next combination
2824    ccc            if(nplused.lt.nplxz_min)goto 888 !next combination
2825    ccc            if(nplused.lt.nplyz_min)goto 888 !next combination
2826    *     -----------------------------------------------------------
2827    *     if in RECOVER_SINGLET mode, the two clouds must have
2828    *     at least ONE intersecting real couple
2829    *     -----------------------------------------------------------
2830                if(ncp_ok.lt.1)goto 888 !next combination
2831    
2832                if(DEBUG.EQ.1)then
2833                   print*,'////////////////////////////'
2834                   print*,'Cloud combination (Y,X): ',iyz,ixz
2835                   print*,' db ',ptcloud_yz(iyz)
2836                   print*,' tr ',ptcloud_xz(ixz)
2837                   print*,'  -----> # matching couples ',ncp_ok
2838                   print*,'  -----> # fake couples (X)',ncpx_ok
2839                   print*,'  -----> # fake couples (Y)',ncpy_ok
2840                   do icp=1,ncp_tot
2841                      print*,'cp ',icp,' >'
2842         $                 ,' x ',cpcloud_xz(ixz,icp)
2843         $                 ,' y ',cpcloud_yz(iyz,icp)
2844         $                 ,' ==> ',cpintersec(icp)
2845                   enddo
2846                endif
2847                            
2848                if(DEBUG.EQ.1)then
2849                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))                 print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2850                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))                 print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2851                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))                 print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
# Line 2751  c$$$            if(AL_INI(5).gt.defmax)g Line 2878  c$$$            if(AL_INI(5).gt.defmax)g
2878                                hit_plane(6)=icp6                                hit_plane(6)=icp6
2879                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6                                if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
2880                                                                
2881                                                                if(DEBUG.eq.1)
2882         $                             print*,'combination: '
2883         $                             ,cp_match(6,icp1)
2884         $                             ,cp_match(5,icp2)
2885         $                             ,cp_match(4,icp3)
2886         $                             ,cp_match(3,icp4)
2887         $                             ,cp_match(2,icp5)
2888         $                             ,cp_match(1,icp6)
2889    
2890    
2891    *                             ---------------------------------------
2892    *                             check if this group of couples has been
2893    *                             already fitted    
2894    *                             ---------------------------------------
2895                                  do ica=1,ntracks
2896                                     isthesame=1
2897                                     do ip=1,NPLANES
2898                                        if(hit_plane(ip).ne.0)then
2899                                           if(  CP_STORE(nplanes-ip+1,ica)
2900         $                                      .ne.
2901         $                                      cp_match(ip,hit_plane(ip)) )
2902         $                                      isthesame=0
2903                                        else
2904                                           if(  CP_STORE(nplanes-ip+1,ica)
2905         $                                      .ne.
2906         $                                      0 )
2907         $                                      isthesame=0
2908                                        endif
2909                                     enddo
2910                                     if(isthesame.eq.1)then
2911                                        if(DEBUG.eq.1)
2912         $                                   print*,'(already fitted)'
2913                                        goto 666 !jump to next combination
2914                                     endif
2915                                  enddo
2916    
2917                                call track_init !init TRACK common                                call track_init !init TRACK common
2918    
2919                                do ip=1,nplanes !loop on planes                                do ip=1,nplanes !loop on planes (bottom to top)
2920                                   if(hit_plane(ip).ne.0)then                                   if(hit_plane(ip).ne.0)then
2921                                      id=cp_match(ip,hit_plane(ip))                                      id=cp_match(ip,hit_plane(ip))
2922                                      is=is_cp(id)                                      is=is_cp(id)
# Line 2774  c     $                                 Line 2936  c     $                                
2936       $                                   PFAdef,PFAdef,0.,0.,0.,0.)       $                                   PFAdef,PFAdef,0.,0.,0.,0.)
2937  *                                   *************************  *                                   *************************
2938  *                                   -----------------------------  *                                   -----------------------------
2939                                      xgood(nplanes-ip+1)=1.                                      if(icx.gt.0.and.icy.gt.0)then
2940                                      ygood(nplanes-ip+1)=1.                                         xgood(nplanes-ip+1)=1.
2941                                      xm(nplanes-ip+1)=xPAM                                         ygood(nplanes-ip+1)=1.
2942                                      ym(nplanes-ip+1)=yPAM                                         xm(nplanes-ip+1)=xPAM
2943                                      zm(nplanes-ip+1)=zPAM                                         ym(nplanes-ip+1)=yPAM
2944                                      resx(nplanes-ip+1)=resxPAM                                         zm(nplanes-ip+1)=zPAM
2945                                      resy(nplanes-ip+1)=resyPAM                                         resx(nplanes-ip+1)=resxPAM                                      
2946                                           resy(nplanes-ip+1)=resyPAM
2947                                           if(DEBUG.EQ.1)print*,'(X,Y)'
2948         $                                      ,nplanes-ip+1,xPAM,yPAM
2949                                        else
2950                                           xm_A(nplanes-ip+1) = xPAM_A
2951                                           ym_A(nplanes-ip+1) = yPAM_A
2952                                           xm_B(nplanes-ip+1) = xPAM_B
2953                                           ym_B(nplanes-ip+1) = yPAM_B
2954                                           zm(nplanes-ip+1)
2955         $                                      = (zPAM_A+zPAM_B)/2.
2956                                           resx(nplanes-ip+1) = resxPAM                                      
2957                                           resy(nplanes-ip+1) = resyPAM
2958                                           if(icx.eq.0.and.icy.gt.0)then
2959                                              xgood(nplanes-ip+1)=0.
2960                                              ygood(nplanes-ip+1)=1.
2961                                              resx(nplanes-ip+1) = 1000.
2962                                              if(DEBUG.EQ.1)print*,'(  Y)'
2963         $                                         ,nplanes-ip+1,xPAM,yPAM
2964                                           elseif(icx.gt.0.and.icy.eq.0)then
2965                                              xgood(nplanes-ip+1)=1.
2966                                              ygood(nplanes-ip+1)=0.
2967                                              if(DEBUG.EQ.1)print*,'(X  )'
2968         $                                         ,nplanes-ip+1,xPAM,yPAM
2969                                              resy(nplanes-ip+1) = 1000.
2970                                           else
2971                                              print*,'both icx=0 and icy=0'
2972         $                                         ,' ==> IMPOSSIBLE!!'
2973                                           endif
2974                                        endif
2975  *                                   -----------------------------  *                                   -----------------------------
2976                                   endif                                   endif
2977                                enddo !end loop on planes                                enddo !end loop on planes
# Line 2798  c$$$                              enddo Line 2989  c$$$                              enddo
2989                                ifail=0 !error flag in chi^2 computation                                ifail=0 !error flag in chi^2 computation
2990                                jstep=0 !number of  minimization steps                                jstep=0 !number of  minimization steps
2991                                iprint=0                                iprint=0
2992  c                              if(DEBUG)iprint=1  c                              if(DEBUG.EQ.1)iprint=1
2993                                if(DEBUG)iprint=2                                if(DEBUG.EQ.1)iprint=2
2994                                call mini2(jstep,ifail,iprint)                                call mini2(jstep,ifail,iprint)
2995                                if(ifail.ne.0) then                                if(ifail.ne.0) then
2996                                   if(DEBUG)then                                   if(DEBUG.EQ.1)then
2997                                      print *,                                      print *,
2998       $                              '*** MINIMIZATION FAILURE *** '       $                              '*** MINIMIZATION FAILURE *** '
2999       $                              //'(clouds_to_ctrack)'       $                              //'(clouds_to_ctrack)'
# Line 2821  c                                 chi2=- Line 3012  c                                 chi2=-
3012  *     **********************************************************  *     **********************************************************
3013    
3014                                if(chi2.le.0.)goto 666                                              if(chi2.le.0.)goto 666              
3015                                  if(chi2.ge.1.e08)goto 666 !OPTIMIZATION
3016                                  if(chi2.ne.chi2)goto 666  !OPTIMIZATION
3017    
3018  *     --------------------------  *     --------------------------
3019  *     STORE candidate TRACK INFO  *     STORE candidate TRACK INFO
3020  *     --------------------------  *     --------------------------
3021                                if(ntracks.eq.NTRACKSMAX)then                                if(ntracks.eq.NTRACKSMAX)then
3022                                                                    
3023                                   if(verbose)print*,                                   if(verbose.eq.1)print*,
3024       $                 '** warning ** number of candidate tracks '//       $                 '** warning ** number of candidate tracks '//
3025       $                 ' exceeds vector dimension '       $                 ' exceeds vector dimension '
3026       $                ,'( ',NTRACKSMAX,' )'       $                ,'( ',NTRACKSMAX,' )'
3027  c                                 good2=.false.  c                                 good2=.false.
3028  c                                 goto 880 !fill ntp and go to next event                      c                                 goto 880 !fill ntp and go to next event                    
3029                                   do iv=1,nviews                                   do iv=1,nviews
3030                                      mask_view(iv) = 7  c                                    mask_view(iv) = 7
3031                                        mask_view(iv) = mask_view(iv) + 2**6
3032                                   enddo                                   enddo
3033                                   iflag=1                                   iflag=1
3034                                   return                                   return
# Line 2842  c                                 goto 8 Line 3036  c                                 goto 8
3036                                                                
3037                                ntracks = ntracks + 1                                ntracks = ntracks + 1
3038                                                                
3039                                do ip=1,nplanes                                do ip=1,nplanes !top to bottom
3040    
3041                                   XV_STORE(ip,ntracks)=sngl(xv(ip))                                   XV_STORE(ip,ntracks)=sngl(xv(ip))
3042                                   YV_STORE(ip,ntracks)=sngl(yv(ip))                                   YV_STORE(ip,ntracks)=sngl(yv(ip))
# Line 2859  c                                 goto 8 Line 3053  c                                 goto 8
3053                                   AYV_STORE(ip,ntracks)=sngl(ayv(ip))                                   AYV_STORE(ip,ntracks)=sngl(ayv(ip))
3054                                   XGOOD_STORE(ip,ntracks)=sngl(xgood(ip))                                   XGOOD_STORE(ip,ntracks)=sngl(xgood(ip))
3055                                   YGOOD_STORE(ip,ntracks)=sngl(ygood(ip))                                   YGOOD_STORE(ip,ntracks)=sngl(ygood(ip))
3056    *                                NB! hit_plane is defined from bottom to top
3057                                   if(hit_plane(ip).ne.0)then                                   if(hit_plane(ip).ne.0)then
3058                                      CP_STORE(nplanes-ip+1,ntracks)=                                      CP_STORE(nplanes-ip+1,ntracks)=
3059       $                                   cp_match(ip,hit_plane(ip))       $                                   cp_match(ip,hit_plane(ip))
3060                                      SENSOR_STORE(nplanes-ip+1,ntracks)                                      SENSOR_STORE(nplanes-ip+1,ntracks)
3061       $                              = is_cp(cp_match(ip,hit_plane(ip)))       $                              = is_cp(cp_match(ip,hit_plane(ip)))
3062                                      LADDER_STORE(nplanes-ip+1,ntracks)                                      
3063       $                                   = LADDER(                                      icl=
3064       $                                   clx(ip,icp_cp(       $                                   clx(ip,icp_cp(
3065       $                                   cp_match(ip,hit_plane(ip)       $                                   cp_match(ip,hit_plane(ip)
3066       $                                   ))));       $                                   )));
3067                                        if(icl.eq.0)
3068         $                                   icl=
3069         $                                   cly(ip,icp_cp(
3070         $                                   cp_match(ip,hit_plane(ip)
3071         $                                   )));
3072    
3073                                        LADDER_STORE(nplanes-ip+1,ntracks)
3074         $                                   = LADDER(icl);
3075                                   else                                   else
3076                                      CP_STORE(nplanes-ip+1,ntracks)=0                                      CP_STORE(nplanes-ip+1,ntracks)=0
3077                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0                                      SENSOR_STORE(nplanes-ip+1,ntracks)=0
3078                                      LADDER_STORE(nplanes-ip+1,ntracks)=0                                      LADDER_STORE(nplanes-ip+1,ntracks)=0
3079                                   endif                                   endif
3080                                   BX_STORE(nplanes-ip+1,ntracks)=0!I dont need it now                                   BX_STORE(ip,ntracks)=0!I dont need it now
3081                                   BY_STORE(nplanes-ip+1,ntracks)=0!I dont need it now                                   BY_STORE(ip,ntracks)=0!I dont need it now
3082                                   CLS_STORE(nplanes-ip+1,ntracks)=0                                   CLS_STORE(ip,ntracks)=0
3083                                   do i=1,5                                   do i=1,5
3084                                      AL_STORE(i,ntracks)=sngl(AL(i))                                      AL_STORE(i,ntracks)=sngl(AL(i))
3085                                   enddo                                   enddo
# Line 2902  c                                 goto 8 Line 3105  c                                 goto 8
3105                
3106        if(ntracks.eq.0)then        if(ntracks.eq.0)then
3107           iflag=1           iflag=1
3108           return  cc         return
3109        endif        endif
3110                
3111  c$$$      if(DEBUG)then        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  
       if(DEBUG)then  
3112          print*,'****** TRACK CANDIDATES *****************'          print*,'****** TRACK CANDIDATES *****************'
3113          print*,'#         R. chi2        RIG         ndof'          print*,'#         R. chi2        RIG         ndof'
3114          do i=1,ntracks          do i=1,ntracks
# Line 2966  c$$$      endif Line 3160  c$$$      endif
3160        real xyzp(3),bxyz(3)        real xyzp(3),bxyz(3)
3161        equivalence (xp,xyzp(1)),(yp,xyzp(2)),(zp,xyzp(3))        equivalence (xp,xyzp(1)),(yp,xyzp(2)),(zp,xyzp(3))
3162    
3163          if(DEBUG.EQ.1)print*,'refine_track:'
3164  *     =================================================  *     =================================================
3165  *     new estimate of positions using ETA algorithm  *     new estimate of positions using ETA algorithm
3166  *                          and  *                          and
# Line 2974  c$$$      endif Line 3169  c$$$      endif
3169        call track_init        call track_init
3170        do ip=1,nplanes           !loop on planes        do ip=1,nplanes           !loop on planes
3171    
3172             if(DEBUG.EQ.1)print*,' ........... plane ',ip,' ........... '
3173    
3174           xP=XV_STORE(nplanes-ip+1,ibest)           xP=XV_STORE(nplanes-ip+1,ibest)
3175           yP=YV_STORE(nplanes-ip+1,ibest)           yP=YV_STORE(nplanes-ip+1,ibest)
3176           zP=ZV_STORE(nplanes-ip+1,ibest)           zP=ZV_STORE(nplanes-ip+1,ibest)
# Line 2990  c$$$         bxyz(3)=0 Line 3187  c$$$         bxyz(3)=0
3187  *     using improved PFAs  *     using improved PFAs
3188  *     -------------------------------------------------  *     -------------------------------------------------
3189  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3190           if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.  c$$$         if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
3191    c$$$     $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3192    c$$$            
3193    c$$$            id=CP_STORE(nplanes-ip+1,ibest)
3194    c$$$            
3195    c$$$            is=is_cp(id)
3196    c$$$            icp=icp_cp(id)
3197    c$$$            if(ip_cp(id).ne.ip)
3198    c$$$     $           print*,'OKKIO!!'
3199    c$$$     $           ,'id ',id,is,icp
3200    c$$$     $           ,ip_cp(id),ip
3201    c$$$            icx=clx(ip,icp)
3202    c$$$            icy=cly(ip,icp)
3203    c$$$c            call xyz_PAM(icx,icy,is,
3204    c$$$c     $           PFA,PFA,
3205    c$$$c     $           AXV_STORE(nplanes-ip+1,ibest),
3206    c$$$c     $           AYV_STORE(nplanes-ip+1,ibest))
3207    c$$$            call xyz_PAM(icx,icy,is,
3208    c$$$     $           PFA,PFA,
3209    c$$$     $           AXV_STORE(nplanes-ip+1,ibest),
3210    c$$$     $           AYV_STORE(nplanes-ip+1,ibest),
3211    c$$$     $           bxyz(1),
3212    c$$$     $           bxyz(2)
3213    c$$$     $           )
3214    c$$$
3215    c$$$            xm(nplanes-ip+1) = xPAM
3216    c$$$            ym(nplanes-ip+1) = yPAM
3217    c$$$            zm(nplanes-ip+1) = zPAM
3218    c$$$            xgood(nplanes-ip+1) = 1
3219    c$$$            ygood(nplanes-ip+1) = 1
3220    c$$$            resx(nplanes-ip+1) = resxPAM
3221    c$$$            resy(nplanes-ip+1) = resyPAM
3222    c$$$
3223    c$$$            dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3224    c$$$            dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3225             if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..or.
3226       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then       $        YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
3227                            
3228              id=CP_STORE(nplanes-ip+1,ibest)              id=CP_STORE(nplanes-ip+1,ibest)
# Line 3015  c     $           AYV_STORE(nplanes-ip+1 Line 3247  c     $           AYV_STORE(nplanes-ip+1
3247       $           bxyz(2)       $           bxyz(2)
3248       $           )       $           )
3249    
3250              xm(nplanes-ip+1) = xPAM              if(icx.gt.0.and.icy.gt.0)then
3251              ym(nplanes-ip+1) = yPAM                 xm(nplanes-ip+1) = xPAM
3252              zm(nplanes-ip+1) = zPAM                 ym(nplanes-ip+1) = yPAM
3253              xgood(nplanes-ip+1) = 1                 zm(nplanes-ip+1) = zPAM
3254              ygood(nplanes-ip+1) = 1                 xm_A(nplanes-ip+1) = 0.
3255              resx(nplanes-ip+1) = resxPAM                 ym_A(nplanes-ip+1) = 0.
3256              resy(nplanes-ip+1) = resyPAM                 xm_B(nplanes-ip+1) = 0.
3257                   ym_B(nplanes-ip+1) = 0.
3258              dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))                 xgood(nplanes-ip+1) = 1
3259              dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))                 ygood(nplanes-ip+1) = 1
3260                   resx(nplanes-ip+1) = resxPAM
3261                   resy(nplanes-ip+1) = resyPAM
3262                   dedxtrk_x(nplanes-ip+1)=
3263         $              sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3264                   dedxtrk_y(nplanes-ip+1)=
3265         $              sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3266                else
3267                   xm(nplanes-ip+1) = 0.
3268                   ym(nplanes-ip+1) = 0.
3269                   zm(nplanes-ip+1) = (zPAM_A+zPAM_B)/2.
3270                   xm_A(nplanes-ip+1) = xPAM_A
3271                   ym_A(nplanes-ip+1) = yPAM_A
3272                   xm_B(nplanes-ip+1) = xPAM_B
3273                   ym_B(nplanes-ip+1) = yPAM_B
3274                   xgood(nplanes-ip+1) = 0
3275                   ygood(nplanes-ip+1) = 0
3276                   resx(nplanes-ip+1) = 1000.!resxPAM
3277                   resy(nplanes-ip+1) = 1000.!resyPAM
3278                   dedxtrk_x(nplanes-ip+1)= 0
3279                   dedxtrk_y(nplanes-ip+1)= 0
3280                   if(icx.gt.0)then
3281                      xgood(nplanes-ip+1) = 1
3282                      resx(nplanes-ip+1) = resxPAM
3283                      dedxtrk_x(nplanes-ip+1)=
3284         $                 sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3285                   elseif(icy.gt.0)then
3286                      ygood(nplanes-ip+1) = 1
3287                      resy(nplanes-ip+1) = resyPAM
3288                      dedxtrk_y(nplanes-ip+1)=
3289         $                 sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3290                   endif
3291                endif
3292                            
3293  *     |||||||||||||||||||||||||||||||||||||||||||||||||  *     |||||||||||||||||||||||||||||||||||||||||||||||||
3294  *     -------------------------------------------------  *     -------------------------------------------------
# Line 3036  c     $           AYV_STORE(nplanes-ip+1 Line 3300  c     $           AYV_STORE(nplanes-ip+1
3300                                
3301              xgood(nplanes-ip+1)=0              xgood(nplanes-ip+1)=0
3302              ygood(nplanes-ip+1)=0              ygood(nplanes-ip+1)=0
3303    
3304                CP_STORE(nplanes-ip+1,ibest)=0 !re-init
3305                CLS_STORE(nplanes-ip+1,ibest)=0
3306    
3307                                
3308  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3309  *     determine which ladder and sensor are intersected by the track  *     determine which ladder and sensor are intersected by the track
# Line 3047  c     $           AYV_STORE(nplanes-ip+1 Line 3315  c     $           AYV_STORE(nplanes-ip+1
3315              LADDER_STORE(nplanes-ip+1,IBEST)=nldt              LADDER_STORE(nplanes-ip+1,IBEST)=nldt
3316  *     --------------------------------------------------------------  *     --------------------------------------------------------------
3317    
3318              if(DEBUG)then              if(DEBUG.EQ.1)then
3319                 print*,                 print*,
3320       $              '------ Plane ',ip,' intersected on LADDER ',nldt       $              '------ Plane ',ip,' intersected on LADDER ',nldt
3321       $              ,' SENSOR ',ist       $              ,' SENSOR ',ist
# Line 3058  c     $           AYV_STORE(nplanes-ip+1 Line 3326  c     $           AYV_STORE(nplanes-ip+1
3326  *     ===========================================  *     ===========================================
3327  *     STEP 1 >>>>>>>  try to include a new couple  *     STEP 1 >>>>>>>  try to include a new couple
3328  *     ===========================================  *     ===========================================
3329  c            if(DEBUG)print*,'>>>> try to include a new couple'              distmin=100000000.
             distmin=1000000.  
3330              xmm = 0.              xmm = 0.
3331              ymm = 0.              ymm = 0.
3332              zmm = 0.              zmm = 0.
# Line 3072  c            if(DEBUG)print*,'>>>> try t Line 3339  c            if(DEBUG)print*,'>>>> try t
3339              do icp=1,ncp_plane(ip) !loop on couples on plane icp              do icp=1,ncp_plane(ip) !loop on couples on plane icp
3340                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3341                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3342                   if(icx.eq.0.or.icy.eq.0)goto 1188!if fake couple, jump to next
3343                 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
3344  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
3345  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
3346       $              cl_used(icx).ne.0.or. !or the X cluster is already used !(3)       $              cl_used(icx).ne.0.or. !or the X cluster is already used
3347       $              cl_used(icy).ne.0.or. !or the Y cluster is already used !(3)       $              cl_used(icy).ne.0.or. !or the Y cluster is already used
3348       $              .false.)goto 1188 !then jump to next couple.       $              .false.)goto 1188 !then jump to next couple.
3349  *            *          
3350                 call xyz_PAM(icx,icy,ist,                 call xyz_PAM(icx,icy,ist,
# Line 3090  c     $              cl_used(icy).eq.1.o Line 3358  c     $              cl_used(icy).eq.1.o
3358                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3359  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3360                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3361                 if(DEBUG)print*,'( couple ',id                 if(DEBUG.EQ.1)
3362         $              print*,'( couple ',id
3363       $              ,' ) distance ',distance       $              ,' ) distance ',distance
3364                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3365                    xmm = xPAM                    xmm = xPAM
# Line 3102  c               distance = distance / RC Line 3371  c               distance = distance / RC
3371                    idm = id                                      idm = id                  
3372                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)                    dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3373                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)                    dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3374  c     QUIQUI --> non devo moltiplicare per clinc?!?!?!                    clincnewc=10*sqrt(rymm**2+rxmm**2
3375                    clincnewc=10*sqrt(rymm**2+rxmm**2 !QUIQUI       $                 +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2)))
      $                 +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2))) !QUIQUI  
3376                 endif                 endif
3377   1188          continue   1188          continue
3378              enddo               !end loop on couples on plane icp              enddo               !end loop on couples on plane icp
3379  c            if(distmin.le.clinc)then     !QUIQUI                            if(distmin.le.clincnewc)then    
             if(distmin.le.clincnewc)then     !QUIQUI                
3380  *              -----------------------------------  *              -----------------------------------
3381                 xm(nplanes-ip+1) = xmm !<<<                 xm(nplanes-ip+1) = xmm !<<<
3382                 ym(nplanes-ip+1) = ymm !<<<                 ym(nplanes-ip+1) = ymm !<<<
# Line 3122  c            if(distmin.le.clinc)then   Line 3389  c            if(distmin.le.clinc)then  
3389                 dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<                 dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<
3390  *              -----------------------------------  *              -----------------------------------
3391                 CP_STORE(nplanes-ip+1,ibest)=idm                       CP_STORE(nplanes-ip+1,ibest)=idm      
3392                 if(DEBUG)print*,'%%%% included couple ',idm                 if(DEBUG.EQ.1)print*,'%%%% included couple ',idm
3393       $              ,' (dist.= ',distmin,', cut ',clinc,' )'       $              ,' (dist.= ',distmin,', cut ',clincnewc,' )'
3394                 goto 133         !next plane                 goto 133         !next plane
3395              endif              endif
3396  *     ================================================  *     ================================================
3397  *     STEP 2 >>>>>>>  try to include a single cluster  *     STEP 2 >>>>>>>  try to include a single cluster
3398  *                     either from a couple or single  *                     either from a couple or single
3399  *     ================================================  *     ================================================
 c            if(DEBUG)print*,'>>>> try to include a new cluster'  
3400              distmin=1000000.              distmin=1000000.
3401              xmm_A = 0.          !---------------------------              xmm_A = 0.          !---------------------------
3402              ymm_A = 0.          ! init variables that              ymm_A = 0.          ! init variables that
# Line 3149  c            if(DEBUG)print*,'>>>> try t Line 3415  c            if(DEBUG)print*,'>>>> try t
3415              do icp=1,ncp_plane(ip) !loop on cluster inside couples              do icp=1,ncp_plane(ip) !loop on cluster inside couples
3416                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3417                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3418                   if(icx.eq.0.or.icy.eq.0)goto 11882!if fake couple, jump to next
3419                 id=id_cp(ip,icp,ist)                 id=id_cp(ip,icp,ist)
3420                 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
3421  *                                                !jump to the next couple  *                                                !jump to the next couple
# Line 3167  c     $              AXV_STORE(nplanes-i Line 3434  c     $              AXV_STORE(nplanes-i
3434       $              )                     $              )              
3435                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3436  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3437                 if(DEBUG)print*,'( cl-X ',icx                 if(DEBUG.EQ.1)
3438         $              print*,'( cl-X ',icx
3439       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3440                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3441                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3200  c     $              0.,AYV_STORE(nplane Line 3468  c     $              0.,AYV_STORE(nplane
3468       $              )       $              )
3469                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3470  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3471                 if(DEBUG)print*,'( cl-Y ',icy                 if(DEBUG.EQ.1)
3472         $              print*,'( cl-Y ',icy
3473       $              ,' in cp ',id,' ) distance ',distance       $              ,' in cp ',id,' ) distance ',distance
3474                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
3475                    xmm_A = xPAM_A                    xmm_A = xPAM_A
# Line 3220  c                 dedxmm = sgnl(icy)  !( Line 3489  c                 dedxmm = sgnl(icy)  !(
3489  11882          continue  11882          continue
3490              enddo               !end loop on cluster inside couples              enddo               !end loop on cluster inside couples
3491  *----- single clusters -----------------------------------------------    *----- single clusters -----------------------------------------------  
 c            print*,'## ncls(',ip,') ',ncls(ip)  
3492              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
3493                 icl=cls(ip,ic)                 icl=cls(ip,ic)
 c               if(cl_used(icl).eq.1.or.     !if the cluster is already used  
3494                 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)
3495       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match
3496       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
# Line 3245  c               if(cl_used(icl).eq.1.or. Line 3512  c               if(cl_used(icl).eq.1.or.
3512    
3513                 distance = distance_to(XP,YP)                 distance = distance_to(XP,YP)
3514  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI  c               distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3515                 if(DEBUG)print*,'( cl-s ',icl                 if(DEBUG.EQ.1)
3516       $              ,' ) distance ',distance,'<',distmin,' ?'       $              print*,'( cl-s ',icl
3517         $              ,' ) distance ',distance
3518                 if(distance.lt.distmin)then                 if(distance.lt.distmin)then
                   if(DEBUG)print*,'YES'  
3519                    xmm_A = xPAM_A                    xmm_A = xPAM_A
3520                    ymm_A = yPAM_A                    ymm_A = yPAM_A
3521                    zmm_A = zPAM_A                    zmm_A = zPAM_A
# Line 3269  c               distance = distance / RC Line 3536  c               distance = distance / RC
3536                 endif                                   endif                  
3537  18882          continue  18882          continue
3538              enddo               !end loop on single clusters              enddo               !end loop on single clusters
 c            print*,'## distmin ', distmin,' clinc ',clinc  
3539    
 c     QUIQUI------------  
 c     anche qui: non ci vuole clinc???  
3540              if(iclm.ne.0)then              if(iclm.ne.0)then
3541                 if(mod(VIEW(iclm),2).eq.0)then                 if(mod(VIEW(iclm),2).eq.0)then
3542                    clincnew=                    clincnew=
# Line 3283  c     anche qui: non ci vuole clinc??? Line 3547  c     anche qui: non ci vuole clinc???
3547       $                 10*       $                 10*
3548       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))       $                 sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))
3549                 endif                 endif
3550  c     QUIQUI------------  
3551                                 if(distmin.le.clincnew)then  
                if(distmin.le.clincnew)then   !QUIQUI  
 c     if(distmin.le.clinc)then          !QUIQUI            
3552                                        
3553                    CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<                        CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<    
3554  *     ----------------------------  *     ----------------------------
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3555                    if(mod(VIEW(iclm),2).eq.0)then                    if(mod(VIEW(iclm),2).eq.0)then
3556                       XGOOD(nplanes-ip+1)=1.                       XGOOD(nplanes-ip+1)=1.
3557                       resx(nplanes-ip+1)=rxmm                       resx(nplanes-ip+1)=rxmm
3558                       if(DEBUG)print*,'%%%% included X-cl ',iclm                       if(DEBUG.EQ.1)
3559         $                    print*,'%%%% included X-cl ',iclm
3560       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3561       $                    ,', dist.= ',distmin       $                    ,', dist.= ',distmin
3562       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3563                    else                    else
3564                       YGOOD(nplanes-ip+1)=1.                       YGOOD(nplanes-ip+1)=1.
3565                       resy(nplanes-ip+1)=rymm                       resy(nplanes-ip+1)=rymm
3566                       if(DEBUG)print*,'%%%% included Y-cl ',iclm                       if(DEBUG.EQ.1)
3567         $                    print*,'%%%% included Y-cl ',iclm
3568       $                    ,'( chi^2, ',RCHI2_STORE(ibest)       $                    ,'( chi^2, ',RCHI2_STORE(ibest)
3569       $                    ,', dist.= ', distmin       $                    ,', dist.= ', distmin
3570       $                    ,', cut ',clinc,' )'       $                    ,', cut ',clincnew,' )'
3571                    endif                    endif
 c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'  
3572  *     ----------------------------  *     ----------------------------
3573                    xm_A(nplanes-ip+1) = xmm_A                    xm_A(nplanes-ip+1) = xmm_A
3574                    ym_A(nplanes-ip+1) = ymm_A                    ym_A(nplanes-ip+1) = ymm_A
# Line 3327  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3589  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3589        return        return
3590        end        end
3591    
3592    
3593  ***************************************************  ***************************************************
3594  *                                                 *  *                                                 *
3595  *                                                 *  *                                                 *
# Line 3336  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3599  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3599  *                                                 *  *                                                 *
3600  **************************************************  **************************************************
3601  *  *
       subroutine clean_XYclouds(ibest,iflag)  
   
       include 'commontracker.f'  
       include 'level1.f'  
       include 'common_momanhough.f'  
       include 'level2.f'        
   
       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))  
                cl_used(iclx)=ntrk  !tag used clusters  
                cl_used(icly)=ntrk  !tag used clusters  
             elseif(icl.ne.0)then  
                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)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  
   
   
   
3602    
3603    
3604    
# Line 3454  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3647  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3647              DEDX_Y(IP,IT) = 0              DEDX_Y(IP,IT) = 0
3648              CLTRX(IP,IT) = 0              CLTRX(IP,IT) = 0
3649              CLTRY(IP,IT) = 0              CLTRY(IP,IT) = 0
3650                multmaxx(ip,it) = 0
3651                seedx(ip,it)    = 0
3652                xpu(ip,it)      = 0
3653                multmaxy(ip,it) = 0
3654                seedy(ip,it)    = 0
3655                ypu(ip,it)      = 0
3656           enddo           enddo
3657           do ipa=1,5           do ipa=1,5
3658              AL_nt(IPA,IT) = 0              AL_nt(IPA,IT) = 0
# Line 3473  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3672  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3672          ys(1,ip)=0          ys(1,ip)=0
3673          ys(2,ip)=0          ys(2,ip)=0
3674          sgnlys(ip)=0          sgnlys(ip)=0
3675            sxbad(ip)=0
3676            sybad(ip)=0
3677            multmaxsx(ip)=0
3678            multmaxsy(ip)=0
3679        enddo        enddo
3680        end        end
3681    
# Line 3595  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3798  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3798        integer ssensor,sladder        integer ssensor,sladder
3799        pig=acos(-1.)        pig=acos(-1.)
3800    
3801    
3802    
3803  *     -------------------------------------  *     -------------------------------------
3804        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3805        nstep_nt(ntr)       = nstep        nstep_nt(ntr)       = nstep
# Line 3633  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~ Line 3838  c     print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~
3838           zv_nt(ip,ntr)    = sngl(zv(ip))           zv_nt(ip,ntr)    = sngl(zv(ip))
3839           axv_nt(ip,ntr)   = sngl(axv(ip))           axv_nt(ip,ntr)   = sngl(axv(ip))
3840           ayv_nt(ip,ntr)   = sngl(ayv(ip))             ayv_nt(ip,ntr)   = sngl(ayv(ip))  
3841  c     l'avevo dimenticato!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!  
3842           factor = sqrt(           factor = sqrt(
3843       $        tan( acos(-1.) * sngl(axv(ip)) /180. )**2 +       $        tan( acos(-1.) * sngl(axv(ip)) /180. )**2 +
3844       $        tan( acos(-1.) * sngl(ayv(ip)) /180. )**2 +       $        tan( acos(-1.) * sngl(ayv(ip)) /180. )**2 +
3845       $        1. )       $        1. )
3846  c     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!  
3847           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)/factor)
3848           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)             dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)/factor)  
3849        
3850    
3851    ccc         print*,ip,'dedx >>> ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3852    
3853           ax   = axv_nt(ip,ntr)           ax   = axv_nt(ip,ntr)
3854           ay   = ayv_nt(ip,ntr)           ay   = ayv_nt(ip,ntr)
3855           bfx  = BX_STORE(ip,IDCAND)           bfx  = BX_STORE(ip,IDCAND)
3856           bfy  = BY_STORE(ip,IDCAND)           bfy  = BY_STORE(ip,IDCAND)
3857           if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)  c$$$         if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)
3858           if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)  c$$$         if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)
3859           tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001  c$$$         tgtemp   = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001
3860           angx     = 180.*atan(tgtemp)/acos(-1.)  c$$$         angx     = 180.*atan(tgtemp)/acos(-1.)
3861           tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001          c$$$         tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001        
3862           angy    = 180.*atan(tgtemp)/acos(-1.)  c$$$         angy    = 180.*atan(tgtemp)/acos(-1.)
3863    
3864             angx = effectiveangle(ax,2*ip,bfy)
3865             angy = effectiveangle(ay,2*ip-1,bfx)
3866            
3867                    
 c         print*,'* ',ip,bfx,bfy,angx,angy  
3868    
3869           id  = CP_STORE(ip,IDCAND) ! couple id           id  = CP_STORE(ip,IDCAND) ! couple id
3870           icl = CLS_STORE(ip,IDCAND)           icl = CLS_STORE(ip,IDCAND)
# Line 3669  c           >>> is a couple Line 3880  c           >>> is a couple
3880              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))              cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3881              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))              cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3882    
3883  c$$$            if(is_cp(id).ne.ssensor)              if(clx(nplanes-ip+1,icp_cp(id)).gt.0)then
3884  c$$$     $           print*,'ERROR is sensor assignment (couple)'  
3885  c$$$     $           ,is_cp(id),ssensor                 cl_used(cltrx(ip,ntr)) = 1 !tag used clusters          
3886  c$$$            if(LADDER(clx(nplanes-ip+1,icp_cp(id))).ne.sladder)  
3887  c$$$     $           print*,'ERROR is ladder assignment (couple)'                 xbad(ip,ntr)= nbadstrips(4,clx(nplanes-ip+1,icp_cp(id)))              
3888  c$$$     $           ,LADDER(clx(nplanes-ip+1,icp_cp(id))),sladder  
3889                               if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3890              nnnnx = npfastrips(clx(nplanes-ip+1,icp_cp(id)),PFA,angx)       $              dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3891              nnnny = npfastrips(cly(nplanes-ip+1,icp_cp(id)),PFA,angy)                            
3892              xbad(ip,ntr)= nbadstrips(nnnnx,clx(nplanes-ip+1,icp_cp(id)))                 multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3893              ybad(ip,ntr)= nbadstrips(nnnny,cly(nplanes-ip+1,icp_cp(id)))       $              +10000*mult(cltrx(ip,ntr))
3894                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3895              if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)       $              /clsigma(indmax(cltrx(ip,ntr)))
3896       $           dedx_x(ip,ntr)=-dedx_x(ip,ntr)                 call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3897              if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)                 xpu(ip,ntr)      = corr
3898       $           dedx_y(ip,ntr)=-dedx_y(ip,ntr)  
3899                endif
3900                if(cly(nplanes-ip+1,icp_cp(id)).gt.0)then
3901    
3902                   cl_used(cltry(ip,ntr)) = 1 !tag used clusters          
3903    
3904                   ybad(ip,ntr)= nbadstrips(4,cly(nplanes-ip+1,icp_cp(id)))
3905    
3906                   if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3907         $              dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3908                  
3909                   multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3910         $              +10000*mult(cltry(ip,ntr))
3911                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3912         $              /clsigma(indmax(cltry(ip,ntr)))
3913                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3914                   ypu(ip,ntr)      = corr
3915                endif
3916    
3917           elseif(icl.ne.0)then           elseif(icl.ne.0)then
3918  c           >>> is a singlet  
3919  c$$$            if(LADDER(icl).ne.sladder)              cl_used(icl) = 1    !tag used clusters          
3920  c$$$     $           print*,'ERROR is ladder assignment (single)'  
 c$$$     $           ,LADDER(icl),sladder  
3921              if(mod(VIEW(icl),2).eq.0)then              if(mod(VIEW(icl),2).eq.0)then
3922                 cltrx(ip,ntr)=icl                 cltrx(ip,ntr)=icl
3923                 nnnnn = npfastrips(icl,PFA,angx)                 xbad(ip,ntr) = nbadstrips(4,icl)
3924                 xbad(ip,ntr) = nbadstrips(nnnnn,icl)  
3925                 if(nsatstrips(icl).gt.0)dedx_x(ip,ntr)=-dedx_x(ip,ntr)                 if(nsatstrips(icl).gt.0)dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3926    
3927                   multmaxx(ip,ntr) = maxs(cltrx(ip,ntr))
3928         $                         +10000*mult(cltrx(ip,ntr))
3929                   seedx(ip,ntr)    = clsignal(indmax(cltrx(ip,ntr)))
3930         $           /clsigma(indmax(cltrx(ip,ntr)))
3931                   call applypfa(PFA,cltrx(ip,ntr),angx,corr,res)
3932                   xpu(ip,ntr)      = corr
3933    
3934              elseif(mod(VIEW(icl),2).eq.1)then              elseif(mod(VIEW(icl),2).eq.1)then
3935                 cltry(ip,ntr)=icl                 cltry(ip,ntr)=icl
3936                 nnnnn = npfastrips(icl,PFA,angy)                 ybad(ip,ntr) = nbadstrips(4,icl)
3937                 ybad(ip,ntr) = nbadstrips(nnnnn,icl)  
3938                 if(nsatstrips(icl).gt.0)dedx_y(ip,ntr)=-dedx_y(ip,ntr)                 if(nsatstrips(icl).gt.0)dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3939    
3940                   multmaxy(ip,ntr) = maxs(cltry(ip,ntr))
3941         $                         +10000*mult(cltry(ip,ntr))
3942                   seedy(ip,ntr)    = clsignal(indmax(cltry(ip,ntr)))
3943         $           /clsigma(indmax(cltry(ip,ntr)))
3944                   call applypfa(PFA,cltry(ip,ntr),angy,corr,res)
3945                   ypu(ip,ntr)      = corr
3946                  
3947              endif              endif
3948    
3949           endif                     endif          
3950    
3951        enddo        enddo
3952    
3953          if(DEBUG.eq.1)then
3954  c$$$      print*,(xgood(i),i=1,6)           print*,'> STORING TRACK ',ntr
3955  c$$$      print*,(ygood(i),i=1,6)           print*,'clusters: '
3956  c$$$      print*,(ls(i,ntr),i=1,6)           do ip=1,6
3957  c$$$      print*,(dedx_x(i,ntr),i=1,6)              print*,'> ',ip,' -- ',cltrx(ip,ntr),cltry(ip,ntr)
3958  c$$$      print*,(dedx_y(i,ntr),i=1,6)           enddo
3959  c$$$      print*,'-----------------------'           print*,'dedx: '
3960             do ip=1,6
3961                print*,'> ',ip,' -- ',dedx_x(ip,ntr),dedx_y(ip,ntr)
3962             enddo
3963          endif
3964    
3965        end        end
3966    
# Line 3736  c$$$      print*,'---------------------- Line 3984  c$$$      print*,'----------------------
3984        nclsy = 0        nclsy = 0
3985    
3986        do iv = 1,nviews        do iv = 1,nviews
3987           if( mask_view(iv).ne.0 )good2(iv) = 20+mask_view(iv)  c         if( mask_view(iv).ne.0 )good2(iv) = 20+mask_view(iv)
3988             good2(iv) = good2(iv) + mask_view(iv)*2**8
3989        enddo        enddo
3990    
3991          if(DEBUG.eq.1)then
3992             print*,'> STORING SINGLETS '
3993          endif
3994    
3995        do icl=1,nclstr1        do icl=1,nclstr1
3996    
3997             ip=nplanes-npl(VIEW(icl))+1            
3998            
3999           if(cl_used(icl).eq.0)then !cluster not included in any track           if(cl_used(icl).eq.0)then !cluster not included in any track
4000              ip=nplanes-npl(VIEW(icl))+1              
4001              if(mod(VIEW(icl),2).eq.0)then !=== X views              if(mod(VIEW(icl),2).eq.0)then !=== X views
4002    
4003                 nclsx = nclsx + 1                 nclsx = nclsx + 1
4004                 planex(nclsx) = ip                 planex(nclsx) = ip
4005                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4006                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)                 if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)
4007                 clsx(nclsx)   = icl                 clsx(nclsx)   = icl
4008                   sxbad(nclsx)  = nbadstrips(1,icl)
4009                   multmaxsx(nclsx) = maxs(icl)+10000*mult(icl)
4010                  
4011    
4012                 do is=1,2                 do is=1,2
4013  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4014  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)  c                  call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
4015                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)
4016                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2                    xs(is,nclsx) = (xPAM_A+xPAM_B)/2
4017                 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)  
4018              else                          !=== Y views              else                          !=== Y views
4019                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4020                 planey(nclsy) = ip                 planey(nclsy) = ip
4021                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))                 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
4022                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)                 if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)
4023                 clsy(nclsy)   = icl                 clsy(nclsy)   = icl
4024                   sybad(nclsy)  = nbadstrips(1,icl)
4025                   multmaxsy(nclsy) = maxs(icl)+10000*mult(icl)
4026    
4027    
4028                 do is=1,2                 do is=1,2
4029  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4030  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)  c                  call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
4031                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)
4032                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2                    ys(is,nclsy) = (yPAM_A+yPAM_B)/2
4033                 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)  
4034              endif              endif
4035           endif           endif
4036    
4037  ***** LO METTO QUI PERCHE` NON SO DOVE METTERLO  ***** LO METTO QUI PERCHE` NON SO DOVE METTERLO
4038           whichtrack(icl) = cl_used(icl)           whichtrack(icl) = cl_used(icl)
4039    *     --------------------------------------------------
4040    *     per non perdere la testa...
4041    *     whichtrack(icl) e` una variabile del common level1
4042    *     che serve solo per sapere quali cluster sono stati
4043    *     associati ad una traccia, e permettere di salvare
4044    *     solo questi nell'albero di uscita
4045    *     --------------------------------------------------
4046                    
4047        enddo        enddo
4048        end        end
4049    

Legend:
Removed from v.1.24  
changed lines
  Added in v.1.38

  ViewVC Help
Powered by ViewVC 1.1.23