/[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.2 by pam-fi, Tue May 30 16:30:37 2006 UTC revision 1.4 by pam-fi, Thu Sep 28 14:04:40 2006 UTC
# Line 237  c         iflag=0 Line 237  c         iflag=0
237  *     ************************** FIT *** FIT *** FIT *** FIT ***  *     ************************** FIT *** FIT *** FIT *** FIT ***
238  *     **********************************************************  *     **********************************************************
239           do i=1,5           do i=1,5
240              AL(i)=dble(AL_STORE(i,icand))              AL(i)=dble(AL_STORE(i,icand))            
241           enddo           enddo
242             IDCAND = icand         !fitted track-candidate
243           ifail=0                !error flag in chi2 computation           ifail=0                !error flag in chi2 computation
244           jstep=0                !# minimization steps           jstep=0                !# minimization steps
245    
# Line 701  c            resxPAM = resxPAM*fbad_cog( Line 702  c            resxPAM = resxPAM*fbad_cog(
702           endif           endif
703    
704        endif        endif
705    c      if(icy.eq.0.and.icx.ne.0)
706    c     $     print*,PFAx,icx,angx,stripx,resxPAM,'***'
707                
708  *     -----------------  *     -----------------
709  *     CLUSTER Y  *     CLUSTER Y
# Line 772  C======================================= Line 775  C=======================================
775  c------------------------------------------------------------------------  c------------------------------------------------------------------------
776  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
777  c------------------------------------------------------------------------  c------------------------------------------------------------------------
778             if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
779         $        .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
780                print*,'xyz_PAM (couple):',
781         $          ' WARNING: false X strip: strip ',stripx
782             endif
783           xi = acoordsi(stripx,viewx)           xi = acoordsi(stripx,viewx)
784           yi = acoordsi(stripy,viewy)           yi = acoordsi(stripy,viewy)
785           zi = 0.           zi = 0.
# Line 858  C======================================= Line 866  C=======================================
866              nldy = nldx              nldy = nldx
867              viewy = viewx - 1              viewy = viewx - 1
868    
869    c            print*,'X-singlet ',icx,nplx,nldx,viewx,stripx
870    c            if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...
871                if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
872         $           .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
873                   print*,'xyz_PAM (X-singlet):',
874         $             ' WARNING: false X strip: strip ',stripx
875                endif
876              xi   = acoordsi(stripx,viewx)              xi   = acoordsi(stripx,viewx)
877    
878              xi_A = xi              xi_A = xi
# Line 1136  c$$$         print*,' resolution ',resxP Line 1151  c$$$         print*,' resolution ',resxP
1151  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1152  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame  c     (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1153  c------------------------------------------------------------------------  c------------------------------------------------------------------------
1154                   if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
1155         $              .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
1156    c     if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...
1157                      print*,'whichsensor: ',
1158         $                ' WARNING: false X strip: strip ',stripx
1159                   endif
1160                 xi = acoordsi(stripx,viewx)                 xi = acoordsi(stripx,viewx)
1161                 yi = acoordsi(stripy,viewy)                 yi = acoordsi(stripy,viewy)
1162                 zi = 0.                 zi = 0.
# Line 1681  c      common/dbg/DEBUG Line 1702  c      common/dbg/DEBUG
1702                    
1703  *     ----------------------------------------------------  *     ----------------------------------------------------
1704  *     cut on charge (X VIEW)  *     cut on charge (X VIEW)
1705    *     ----------------------------------------------------
1706           if(dedx(icx).lt.dedx_x_min)then           if(dedx(icx).lt.dedx_x_min)then
1707              cl_single(icx)=0              cl_single(icx)=0
1708              goto 10              goto 10
1709           endif           endif
1710    *     ----------------------------------------------------
1711  *     cut BAD (X VIEW)              *     cut BAD (X VIEW)            
1712    *     ----------------------------------------------------
1713           badseed=BAD(VIEW(icx),nvk(MAXS(icx)),nst(MAXS(icx)))           badseed=BAD(VIEW(icx),nvk(MAXS(icx)),nst(MAXS(icx)))
1714           ifirst=INDSTART(icx)           ifirst=INDSTART(icx)
1715           if(icx.ne.nclstr1) then           if(icx.ne.nclstr1) then
# Line 1705  c      common/dbg/DEBUG Line 1729  c      common/dbg/DEBUG
1729              endif              endif
1730              badcl=badcl*ibad              badcl=badcl*ibad
1731           enddo           enddo
1732    *     ----------------------------------------------------
1733    *     >>> eliminato il taglio sulle BAD <<<
1734    *     ----------------------------------------------------
1735  c     if(badcl.eq.0)then  c     if(badcl.eq.0)then
1736  c     cl_single(icx)=0  c     cl_single(icx)=0
1737  c     goto 10  c     goto 10
# Line 1720  c     endif Line 1747  c     endif
1747                            
1748  *     ----------------------------------------------------  *     ----------------------------------------------------
1749  *     cut on charge (Y VIEW)  *     cut on charge (Y VIEW)
1750    *     ----------------------------------------------------
1751              if(dedx(icy).lt.dedx_y_min)then              if(dedx(icy).lt.dedx_y_min)then
1752                 cl_single(icy)=0                 cl_single(icy)=0
1753                 goto 20                 goto 20
1754              endif              endif
1755    *     ----------------------------------------------------
1756  *     cut BAD (Y VIEW)              *     cut BAD (Y VIEW)            
1757    *     ----------------------------------------------------
1758              badseed=BAD(VIEW(icy),nvk(MAXS(icy)),nst(MAXS(icy)))              badseed=BAD(VIEW(icy),nvk(MAXS(icy)),nst(MAXS(icy)))
1759              ifirst=INDSTART(icy)              ifirst=INDSTART(icy)
1760              if(icy.ne.nclstr1) then              if(icy.ne.nclstr1) then
# Line 1743  c     endif Line 1773  c     endif
1773       $              nst(MAXS(icy)+igood))       $              nst(MAXS(icy)+igood))
1774                 badcl=badcl*ibad                 badcl=badcl*ibad
1775              enddo              enddo
1776    *     ----------------------------------------------------
1777    *     >>> eliminato il taglio sulle BAD <<<
1778    *     ----------------------------------------------------
1779  c     if(badcl.eq.0)then  c     if(badcl.eq.0)then
1780  c     cl_single(icy)=0  c     cl_single(icy)=0
1781  c     goto 20  c     goto 20
1782  c     endif  c     endif
1783  *     ----------------------------------------------------  *     ----------------------------------------------------
1784                            
               
1785              cl_good(icy)=1                                cl_good(icy)=1                  
1786              nply=npl(VIEW(icy))              nply=npl(VIEW(icy))
1787              nldy=nld(MAXS(icy),VIEW(icy))              nldy=nld(MAXS(icy),VIEW(icy))
# Line 1760  c     endif Line 1792  c     endif
1792  *     geometrical consistency (same plane and ladder)  *     geometrical consistency (same plane and ladder)
1793              if(nply.eq.nplx.and.nldy.eq.nldx)then              if(nply.eq.nplx.and.nldy.eq.nldx)then
1794  *     charge correlation  *     charge correlation
1795                 ddd=(dedx(icy)  *     (modified to be applied only below saturation... obviously)
1796       $              -kch(nplx,nldx)*dedx(icx)-cch(nplx,nldx))  
1797                 ddd=ddd/sqrt(kch(nplx,nldx)**2+1)  *     -------------------------------------------------------------
1798                 cut=chcut*sch(nplx,nldx)  *     >>> eliminata (TEMPORANEAMENTE) la correlazione di carica <<<
1799                 if(abs(ddd).gt.cut)goto 20 !charge not consistent  *     -------------------------------------------------------------
1800                  c$$$               if(dedx(icy).lt.chsaty.or.dedx(icx).lt.chsatx)then
1801    c$$$                  ddd=(dedx(icy)
1802    c$$$     $                 -kch(nplx,nldx)*dedx(icx)-cch(nplx,nldx))
1803    c$$$                  ddd=ddd/sqrt(kch(nplx,nldx)**2+1)
1804    c$$$                  cut=chcut*sch(nplx,nldx)
1805    c$$$                  if(abs(ddd).gt.cut)goto 20 !charge not consistent
1806    c$$$               endif
1807                                
1808  *     ------------------> COUPLE <------------------  *     ------------------> COUPLE <------------------
1809  *     check to do not overflow vector dimentions  *     check to do not overflow vector dimentions
# Line 1781  c     goto 880   !fill ntp and go to nex Line 1819  c     goto 880   !fill ntp and go to nex
1819                    return                    return
1820                 endif                 endif
1821                                
1822                 if(ncp_plane(nplx).eq.ncouplemax)then  c$$$               if(ncp_plane(nplx).eq.ncouplemax)then
1823                    if(DEBUG)print*,  c$$$                  if(DEBUG)print*,
1824       $                 '** warning ** number of identified '//  c$$$     $                 '** warning ** number of identified '//
1825       $                 'couples on plane ',nplx,  c$$$     $                 'couples on plane ',nplx,
1826       $                 'exceeds vector dimention '  c$$$     $                 'exceeds vector dimention '
1827       $                 ,'( ',ncouplemax,' )'  c$$$     $                 ,'( ',ncouplemax,' )'
1828  c     good2=.false.  c$$$c     good2=.false.
1829  c     goto 880   !fill ntp and go to next event                      c$$$c     goto 880   !fill ntp and go to next event                    
1830                    iflag=1  c$$$                  iflag=1
1831                    return  c$$$                  return
1832                 endif  c$$$               endif
1833                                
1834                 ncp_plane(nplx) = ncp_plane(nplx) + 1                 ncp_plane(nplx) = ncp_plane(nplx) + 1
1835                 clx(nplx,ncp_plane(nplx))=icx                 clx(nplx,ncp_plane(nplx))=icx
# Line 2001  c     goto 880   !fill ntp and go to nex Line 2039  c     goto 880   !fill ntp and go to nex
2039                    return                    return
2040                 endif                 endif
2041                                
2042                 if(ncp_plane(nplx).eq.ncouplemax)then  c$$$               if(ncp_plane(nplx).eq.ncouplemax)then
2043                    if(DEBUG)print*,  c$$$                  if(DEBUG)print*,
2044       $                 '** warning ** number of identified '//  c$$$     $                 '** warning ** number of identified '//
2045       $                 'couples on plane ',nplx,  c$$$     $                 'couples on plane ',nplx,
2046       $                 'exceeds vector dimention '  c$$$     $                 'exceeds vector dimention '
2047       $                 ,'( ',ncouplemax,' )'  c$$$     $                 ,'( ',ncouplemax,' )'
2048  c     good2=.false.  c$$$c     good2=.false.
2049  c     goto 880   !fill ntp and go to next event                      c$$$c     goto 880   !fill ntp and go to next event                    
2050                    iflag=1  c$$$                  iflag=1
2051                    return  c$$$                  return
2052                 endif  c$$$               endif
2053                                
2054                 ncp_plane(nplx) = ncp_plane(nplx) + 1                 ncp_plane(nplx) = ncp_plane(nplx) + 1
2055                 clx(nplx,ncp_plane(nplx))=icx                 clx(nplx,ncp_plane(nplx))=icx
# Line 3273  c$$$  rchi2=chi2/dble(ndof) Line 3311  c$$$  rchi2=chi2/dble(ndof)
3311  c******************************************************  c******************************************************
3312  cccccc 06/10/2005 modified by elena vannuccini ---> (1)  cccccc 06/10/2005 modified by elena vannuccini ---> (1)
3313  cccccc 31/01/2006 modified by elena vannuccini ---> (2)  cccccc 31/01/2006 modified by elena vannuccini ---> (2)
3314    cccccc 12/08/2006 modified by elena vannucicni ---> (3)
3315  c******************************************************  c******************************************************
3316    
3317        include 'commontracker.f'        include 'commontracker.f'
# Line 3383  c            if(DEBUG)print*,'>>>> try t Line 3422  c            if(DEBUG)print*,'>>>> try t
3422                 icx=clx(ip,icp)                 icx=clx(ip,icp)
3423                 icy=cly(ip,icp)                 icy=cly(ip,icp)
3424                 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
3425       $              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
3426       $              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
3427         $              cl_used(icx).ne.0.or. !or the X cluster is already used !(3)
3428         $              cl_used(icy).ne.0.or. !or the Y cluster is already used !(3)
3429       $              .false.)goto 1188 !then jump to next couple.       $              .false.)goto 1188 !then jump to next couple.
3430  *            *          
3431                 call xyz_PAM(icx,icy,ist,                 call xyz_PAM(icx,icy,ist,
# Line 3456  c            if(DEBUG)print*,'>>>> try t Line 3497  c            if(DEBUG)print*,'>>>> try t
3497                 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
3498  *                                                !jump to the next couple  *                                                !jump to the next couple
3499  *----- try cluster x -----------------------------------------------  *----- try cluster x -----------------------------------------------
3500                 if(cl_used(icx).eq.1)goto 11881 !if the X cluster is already used  c               if(cl_used(icx).eq.1)goto 11881 !if the X cluster is already used
3501                   if(cl_used(icx).ne.0)goto 11881 !if the X cluster is already used  !(3)
3502  *                                              !jump to the Y cluster  *                                              !jump to the Y cluster
3503                 call xyz_PAM(icx,0,ist,                 call xyz_PAM(icx,0,ist,
3504  c     $              'ETA2','ETA2',  c     $              'ETA2','ETA2',
# Line 3483  c                  dedxmm = dedx(icx) !( Line 3525  c                  dedxmm = dedx(icx) !(
3525                 endif                                   endif                  
3526  11881          continue  11881          continue
3527  *----- try cluster y -----------------------------------------------  *----- try cluster y -----------------------------------------------
3528                 if(cl_used(icy).eq.1)goto 11882 !if the Y cluster is already used  c               if(cl_used(icy).eq.1)goto 11882 !if the Y cluster is already used
3529                   if(cl_used(icy).ne.0)goto 11882 !if the Y cluster is already used !(3)
3530  *                                              !jump to the next couple  *                                              !jump to the next couple
3531                 call xyz_PAM(0,icy,ist,                 call xyz_PAM(0,icy,ist,
3532  c     $              'ETA2','ETA2',  c     $              'ETA2','ETA2',
# Line 3512  c                 dedxmm = dedx(icy)  !( Line 3555  c                 dedxmm = dedx(icy)  !(
3555  *----- single clusters -----------------------------------------------      *----- single clusters -----------------------------------------------    
3556              do ic=1,ncls(ip)    !loop on single clusters              do ic=1,ncls(ip)    !loop on single clusters
3557                 icl=cls(ip,ic)                 icl=cls(ip,ic)
3558                 if(cl_used(icl).eq.1.or.     !if the cluster is already used  c               if(cl_used(icl).eq.1.or.     !if the cluster is already used
3559                   if(cl_used(icl).ne.0.or.     !if the cluster is already used !(3)
3560       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match       $              LADDER(icl).ne.nldt.or. !or the ladder number does not match
3561       $              .false.)goto 18882      !jump to the next singlet       $              .false.)goto 18882      !jump to the next singlet
3562                 if(mod(VIEW(icl),2).eq.0)then!<---- X view                 if(mod(VIEW(icl),2).eq.0)then!<---- X view
# Line 3596  c              dedxtrk(nplanes-ip+1) = d Line 3640  c              dedxtrk(nplanes-ip+1) = d
3640  *                                                 *  *                                                 *
3641  *                                                 *  *                                                 *
3642  **************************************************  **************************************************
3643    cccccc 12/08/2006 modified by elena ---> (1)
3644    *
3645        subroutine clean_XYclouds(ibest,iflag)        subroutine clean_XYclouds(ibest,iflag)
3646    
3647        include 'commontracker.f'        include 'commontracker.f'
3648        include 'common_momanhough.f'        include 'common_momanhough.f'
3649        include 'momanhough_init.f'        include 'momanhough_init.f'
3650          include 'level2.f'        !(1)
3651  c      include 'calib.f'  c      include 'calib.f'
3652  c      include 'level1.f'  c      include 'level1.f'
3653    
# Line 3617  c      common/dbg/DEBUG Line 3663  c      common/dbg/DEBUG
3663              if(id.ne.0)then              if(id.ne.0)then
3664                 iclx=clx(ip,icp_cp(id))                 iclx=clx(ip,icp_cp(id))
3665                 icly=cly(ip,icp_cp(id))                 icly=cly(ip,icp_cp(id))
3666                 cl_used(iclx)=1  !tag used clusters  c               cl_used(iclx)=1  !tag used clusters
3667                 cl_used(icly)=1  !tag used clusters  c               cl_used(icly)=1  !tag used clusters
3668                   cl_used(iclx)=ntrk  !tag used clusters !(1)
3669                   cl_used(icly)=ntrk  !tag used clusters !(1)
3670              elseif(icl.ne.0)then              elseif(icl.ne.0)then
3671                 cl_used(icl)=1   !tag used clusters  c               cl_used(icl)=1   !tag used clusters
3672                   cl_used(icl)=ntrk   !tag used clusters !1)
3673              endif              endif
3674                            
3675  c               if(DEBUG)then  c               if(DEBUG)then
# Line 3788  c*************************************** Line 3837  c***************************************
3837        include 'level2.f'        include 'level2.f'
3838        include 'level1.f'        include 'level1.f'
3839    
3840          do i=1,nviews
3841             good2(i)=good1(i)
3842          enddo
3843    
3844    c      good2 = 0!.false.
       good2 = 0!.false.  
3845  c$$$      nev2 = nev1  c$$$      nev2 = nev1
3846    
3847  c$$$# ifndef TEST2003  c$$$# ifndef TEST2003
# Line 3817  c*************************************** Line 3868  c***************************************
3868        do it=1,NTRKMAX!NTRACKSMAX        do it=1,NTRKMAX!NTRACKSMAX
3869           IMAGE(IT)=0           IMAGE(IT)=0
3870           CHI2_nt(IT) = -100000.           CHI2_nt(IT) = -100000.
3871           BdL(IT) = 0.  c         BdL(IT) = 0.
3872           do ip=1,nplanes           do ip=1,nplanes
3873              XM_nt(IP,IT) = 0              XM_nt(IP,IT) = 0
3874              YM_nt(IP,IT) = 0              YM_nt(IP,IT) = 0
# Line 3831  cccccc 11/9/2005 modified by david fedel Line 3882  cccccc 11/9/2005 modified by david fedel
3882              DEDX_X(IP,IT) = 0              DEDX_X(IP,IT) = 0
3883              DEDX_Y(IP,IT) = 0              DEDX_Y(IP,IT) = 0
3884  c******************************************************  c******************************************************
3885    cccccc 17/8/2006 modified by elena
3886                CLTRX(IP,IT) = 0
3887                CLTRY(IP,IT) = 0
3888           enddo           enddo
3889           do ipa=1,5           do ipa=1,5
3890              AL_nt(IPA,IT) = 0              AL_nt(IPA,IT) = 0
# Line 3882  c*************************************** Line 3936  c***************************************
3936    
3937            
3938        include 'commontracker.f'        include 'commontracker.f'
3939          include 'level1.f'
3940        include 'level2.f'        include 'level2.f'
3941        include 'common_mini_2.f'        include 'common_mini_2.f'
3942          include 'common_momanhough.f'
3943        real sinth,phi,pig        !(4)        real sinth,phi,pig        !(4)
3944        pig=acos(-1.)        pig=acos(-1.)
3945    
3946        good2=1!.true.  c      good2=1!.true.
3947        chi2_nt(ntr)        = sngl(chi2)        chi2_nt(ntr)        = sngl(chi2)
3948          nstep_nt(ntr)       = 0!nstep
3949    
3950        phi   = al(4)             !(4)        phi   = al(4)             !(4)
3951        sinth = al(3)             !(4)        sinth = al(3)             !(4)
# Line 3926  c     print*,al_nt(i,ntr) Line 3983  c     print*,al_nt(i,ntr)
3983           ayv_nt(ip,ntr)   = sngl(ayv(ip))           ayv_nt(ip,ntr)   = sngl(ayv(ip))
3984  c        dedxp(ip,ntr)    = sngl(dedxtrk(ip))   !(1)  c        dedxp(ip,ntr)    = sngl(dedxtrk(ip))   !(1)
3985           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)) !(2)           dedx_x(ip,ntr)   = sngl(dedxtrk_x(ip)) !(2)
3986           dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)) !(2)                     dedx_y(ip,ntr)   = sngl(dedxtrk_y(ip)) !(2)  
3987      
3988             id  = CP_STORE(ip,IDCAND)
3989             icl = CLS_STORE(ip,IDCAND)
3990             if(id.ne.0)then
3991                cltrx(ip,ntr)   = clx(nplanes-ip+1,icp_cp(id))
3992                cltry(ip,ntr)   = cly(nplanes-ip+1,icp_cp(id))
3993    c            print*,ip,' ',cltrx(ip,ntr),cltry(ip,ntr)
3994             elseif(icl.ne.0)then
3995                if(mod(VIEW(icl),2).eq.0)cltrx(ip,ntr)=icl
3996                if(mod(VIEW(icl),2).eq.1)cltry(ip,ntr)=icl
3997    c            print*,ip,' ',cltrx(ip,ntr),cltry(ip,ntr)
3998             endif          
3999    
4000        enddo        enddo
4001  c      call CalcBdL(100,xxxx,IFAIL)  c      call CalcBdL(100,xxxx,IFAIL)
4002  c      if(ifps(xxxx).eq.1)BdL(ntr) = xxxx  c      if(ifps(xxxx).eq.1)BdL(ntr) = xxxx
# Line 3959  c*************************************** Line 4029  c***************************************
4029        include 'common_xyzPAM.f'        include 'common_xyzPAM.f'
4030    
4031  *     count #cluster per plane not associated to any track  *     count #cluster per plane not associated to any track
4032        good2=1!.true.  c      good2=1!.true.
4033        nclsx = 0        nclsx = 0
4034        nclsy = 0        nclsy = 0
4035    
# Line 3970  c*************************************** Line 4040  c***************************************
4040                 nclsx = nclsx + 1                 nclsx = nclsx + 1
4041                 planex(nclsx) = ip                 planex(nclsx) = ip
4042                 sgnlxs(nclsx) = dedx(icl)/mip(VIEW(icl),LADDER(icl))!(2)                 sgnlxs(nclsx) = dedx(icl)/mip(VIEW(icl),LADDER(icl))!(2)
4043                   clsx(nclsx)   = icl
4044                 do is=1,2                 do is=1,2
4045  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)  c                  call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
4046                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)                    call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
# Line 3984  c$$$               print*,'xs(2,nclsx)   Line 4055  c$$$               print*,'xs(2,nclsx)  
4055                 nclsy = nclsy + 1                 nclsy = nclsy + 1
4056                 planey(nclsy) = ip                 planey(nclsy) = ip
4057                 sgnlys(nclsy) = dedx(icl)/mip(VIEW(icl),LADDER(icl))!(2)                 sgnlys(nclsy) = dedx(icl)/mip(VIEW(icl),LADDER(icl))!(2)
4058                   clsy(nclsy)   = icl
4059                 do is=1,2                 do is=1,2
4060  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)  c                  call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
4061                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)                    call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
# Line 3997  c$$$               print*,'ys(2,nclsy)   Line 4069  c$$$               print*,'ys(2,nclsy)  
4069              endif              endif
4070           endif           endif
4071  c      print*,icl,cl_used(icl),cl_good(icl),ip,VIEW(icl)!nclsx(ip),nclsy(ip)  c      print*,icl,cl_used(icl),cl_good(icl),ip,VIEW(icl)!nclsx(ip),nclsy(ip)
4072    
4073    ***** LO METTO QUI PERCHE` NON SO DOVE METTERLO
4074             whichtrack(icl) = cl_used(icl)
4075    
4076        enddo        enddo
4077        end        end
4078    
# Line 4004  c      print*,icl,cl_used(icl),cl_good(i Line 4080  c      print*,icl,cl_used(icl),cl_good(i
4080    
4081    
4082    
4083    

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.4

  ViewVC Help
Powered by ViewVC 1.1.23