(file) Return to guout.f CVS log (file) (dir) Up to [HallC] / sane_geant_mc / SRC

Diff for /sane_geant_mc/SRC/guout.f between version 1.1 and 1.2

version 1.1, 2010/04/22 14:13:54 version 1.2, 2010/05/06 14:16:41
Line 10 
Line 10 
  
       integer changes       integer changes
       integer i,j       integer i,j
         integer iclust
  
       integer*4 cl,last_cl       integer*4 cl,last_cl
       real*4 eng,d1,d2       real*4 eng,d1,d2
Line 17 
Line 18 
       REAL*4 X_HOD(28),Y_HOD(28),Z_HOD(28),       REAL*4 X_HOD(28),Y_HOD(28),Z_HOD(28),
      ,     T_HOD(28),E_HOD(28)      ,     T_HOD(28),E_HOD(28)
       common/TEMPR/ihhit,X_HOD,Y_HOD,Z_HOD,T_HOD,E_HOD       common/TEMPR/ihhit,X_HOD,Y_HOD,Z_HOD,T_HOD,E_HOD
   c      real Eyx(5,5),xx(5,5),yy(5,5)
       real Eyx(5,5),xx(5,5),yy(5,5)       real Eyx(5,5),xx(5,5),yy(5,5)
       common/ENERGYYX/Eyx,xx,yy       common/ENERGYYX/Eyx,xx,yy
  
Line 115 
Line 117 
 C    --- Front and Lucite Hososcopes -JDM - 6/20/07 C    --- Front and Lucite Hososcopes -JDM - 6/20/07
       call digi_tracker()       call digi_tracker()
       call digi_lucite()       call digi_lucite()
   
   CCC Loop over clusters to include other particles HB,NK 04/28/10
         nclust=0
         do iclust=1,5
       call digi_cal()       call digi_cal()
               etot=0
               do i=1,5
                  do j=1,5
                     etot=etot+eyx(i,j)
                  enddo
               enddo
   
 c      write(*,*)2,part,eyx(3,3) c      write(*,*)2,part,eyx(3,3)
       if(eyx(3,3).gt.0)then           if(Eyx(3,3).gt.0.and.etot.gt.0.15)then
 c         write(*,*)eyx              nclust=nclust+1
 c         call NeuralParam(Emax,Emt,Etot9,Etot,  
 c     ,     xmomsqr,xmom,xmomsq,ymomsqr,ymom,ymomsq,  
 c     ,     ixmax,iymax,EYX,XX,YY)  
   
   
 c$$$         VectorN(1) = Emax  
 c$$$         VectorN(2) = emax/Etot  
 c$$$         VectorN(3) = Etot9  
 c$$$         VectorN(4) = Etot  
 c$$$         VectorN(5) = xmomsqr  
 c$$$         VectorN(6) = xmom  
 c$$$         VectorN(7) = xmomsq  
 c$$$         VectorN(8) = ymomsqr  
 c$$$         VectorN(9) = ymom  
 c$$$         VectorN(10) =ymomsq  
 c$$$         VectorN(11) = DBLE(ixmax)  
 c$$$         VectorN(12) =DBLE(iymax)  
 c$$$  
 c$$$  
 c$$$         call neuralx(VectorN,0)  
 c$$$         call neuraly(VectorN,0)  
 c$$$         call neurale(VectorN,0)  
 c$$$  
 c$$$         COORX2 = FixX  
 c$$$         COORY2 = FixY  
 c$$$         COORE  = FixE  
 c     call nneurale(VectorN,0)  
          VectorN(1)   = eyx(1,1)          VectorN(1)   = eyx(1,1)
          VectorN(2)   = eyx(2,1)          VectorN(2)   = eyx(2,1)
          VectorN(3)   = eyx(3,1)          VectorN(3)   = eyx(3,1)
Line 175 
Line 161 
          VectorN(26) = DBLE(ixmax)          VectorN(26) = DBLE(ixmax)
          VectorN(27) =DBLE(iymax)          VectorN(27) =DBLE(iymax)
  
 c           call neuralx(VectorN,0)  
 c           call neuraly(VectorN,0)  
 c           call neurale(VectorN,0)  
          etot=0  
          do i=1,5  
             do j=1,5  
                etot=etot+eyx(i,j)  
             enddo  
          enddo  
  
  
             COORX2 = sane_n100xye(VectorN,0)             COORX2 = sane_n100xye(VectorN,0)
Line 209 
Line 186 
          call NANcheckF(X_coor_r,5)          call NANcheckF(X_coor_r,5)
          call NANcheckF(Y_coor_r,6)          call NANcheckF(Y_coor_r,6)
          call NANcheckF(Z_coor_r,7)          call NANcheckF(Z_coor_r,7)
               cwn_x_ur(iclust)=X_coor
               cwn_y_ur(iclust)=Y_coor
               cwn_z_ur(iclust)=Z_coor
               call digi_cer(iclust)
  
 c     write(*,*) X_coor_r, c     write(*,*) X_coor_r,
 c     ,          Y_coor_r, c     ,          Y_coor_r,
Line 220 
Line 201 
      ,        Z_coor_r,      ,        Z_coor_r,
      ,        E_coor*1000,      ,        E_coor*1000,
      ,           THETA_C ,      ,           THETA_C ,
      ,        PHI_C)       ,           PHI_C,cer_h(iclust))
  
          cwn_E_r=E_coor              cwn_E_r(iclust)=E_coor
          cwn_th_r=THETA_C              cwn_th_r(iclust)=THETA_C
          cwn_ph_r=PHI_C              cwn_ph_r(iclust)=PHI_C
          cwn_x_r=X_coor_r              cwn_x_r(iclust)=X_coor_r
          cwn_y_r=Y_coor_r              cwn_y_r(iclust)=Y_coor_r
          cwn_z_r=Z_coor_r              cwn_z_r(iclust)=Z_coor_r
          cwn_x_ur=X_coor  
          cwn_y_ur=Y_coor  
          cwn_z_ur=Z_coor  
          call NANcheckF(THETA_C,8)          call NANcheckF(THETA_C,8)
          call NANcheckF(PHI_C,9)          call NANcheckF(PHI_C,9)
  
Line 243 
Line 221 
      ,        THETA_UC ,      ,        THETA_UC ,
      ,        PHI_UC)      ,        PHI_UC)
  
   c      enddo !! Finish looping over clusters
   
          call NANcheckF(THETA_UC,10)          call NANcheckF(THETA_UC,10)
          call NANcheckF(PHI_UC,11)          call NANcheckF(PHI_UC,11)
          cwn_th_ucr=THETA_UC              cwn_th_ucr(iclust)=THETA_UC
          cwn_ph_ucr=PHI_UC              cwn_ph_ucr(iclust)=PHI_UC
  
          do i=1,5          do i=1,5
             do j=1,5             do j=1,5
Line 255 
Line 235 
                YY(i,j)=0                YY(i,j)=0
             enddo             enddo
          enddo          enddo
   
            endif
         enddo !! Finish looping over clusters
   
 c     write(*,*)etot,coore,EE,etot+coorE,etot+FixE c     write(*,*)etot,coore,EE,etot+coorE,etot+FixE
  
 C     ---- JDM C     ---- JDM
Line 283 
Line 267 
                endif                endif
             enddo             enddo
          enddo          enddo
          if (.not.(Eloss(4).eq.0.and.Eloss(1).eq.0.and.  c         if (.not.(Eloss(4).eq.0.and.Eloss(1).eq.0.and.
      1        cwn_nb.eq.0.and.photCer.eq.0))then  c     1        cwn_nb.eq.0.and.photCer.eq.0))then
             if(abs(EE).gt.0)call hfnt(nt_geant)           if(nclust.gt.0)then
          endif  c            write(*,*)nclust
   c            write(*,*) '# cerenkov photons:',photCer,photGood
               call hfnt(nt_geant)
       endif       endif
            call clear_cer()
            call clear_cal()
   c         endif
  
 c      write(*,*)'Next step' c      write(*,*)'Next step'
 cccc cccc
Line 315 
Line 303 
 C C
  1101 CONTINUE  1101 CONTINUE
  111  format(2(1x,f6.3),3(1x,i2),1x,e13.5,8(f9.3,1x),5(f9.6,1x),3(i2,1x),2(f7.3,1x,f7.3,1x,f7.4,1x,f7.4,1x))  111  format(2(1x,f6.3),3(1x,i2),1x,e13.5,8(f9.3,1x),5(f9.6,1x),3(i2,1x),2(f7.3,1x,f7.3,1x,f7.4,1x,f7.4,1x))
   c      enddo
       END       END
 cccccccccccccccccccccccccccc cccccccccccccccccccccccccccc
 ccc ccc
Line 419 
Line 408 
 c$$$      include 'sane_neuraly.f' c$$$      include 'sane_neuraly.f'
       include 'sane_n100xye.f'       include 'sane_n100xye.f'
 cccccccccccccccccccccccccccccccccccccccccccccccccccc cccccccccccccccccccccccccccccccccccccccccccccccccccc
       Subroutine CORRECT_ANGLES(x,y,z,ee,th,phi)        Subroutine CORRECT_ANGLES(x,y,z,ee,th,phi,cer_stat)
       IMPLICIT NONE       IMPLICIT NONE
 c c
 c     X = X(Bigcal)-X(raster) c     X = X(Bigcal)-X(raster)
Line 436 
Line 425 
       real x,y,z       real x,y,z
       real th,phi,thr,phr,ee       real th,phi,thr,phr,ee
       real dist,SANE_BETA_OMEGA       real dist,SANE_BETA_OMEGA
         real*8 P_th(10),P_phi(10)
   
         integer cer_stat
         data P_th /
        ,     -2.199987805718,      1.312318933346,      0.644032653274,
        ,     2.001711272282  ,    4.831055345667,
        ,     0.596870277140   ,   0.237530064696 ,    -0.444891749961,
        ,     -0.668604044519  ,   -1.988327254812/
         data P_Phi /
        ,     -1.206886920591,      3.898203794202,      1.409952555564 ,
        ,     -0.737821993549,      4.693839032660,
        ,     -0.853486677346,     -3.282568717839 ,     1.891695882259,
        ,     1.158605334109 ,    -4.578605424909/
  
       dist = sqrt(x**2+y**2+z**2)       dist = sqrt(x**2+y**2+z**2)
       thr  = acos(z/dist)       thr  = acos(z/dist)
Line 446 
Line 448 
 c$$$         SANE_BETA_OMEGA = abs(theta_0 - abs(Theta_Bfield)) !! 1st attempt w/ ANN c$$$         SANE_BETA_OMEGA = abs(theta_0 - abs(Theta_Bfield)) !! 1st attempt w/ ANN
 c         SANE_BETA_OMEGA = 40!abs(theta_0 - abs(Theta_Bfield)) c         SANE_BETA_OMEGA = 40!abs(theta_0 - abs(Theta_Bfield))
 c         SANE_BETA_OMEGA = abs(theta_0 - Theta_Bfield) c         SANE_BETA_OMEGA = abs(theta_0 - Theta_Bfield)
          SANE_BETA_OMEGA = omega   !! Use same           SANE_BETA_OMEGA = omega   !! Use definition from uginit.f
 c      print*,X,Y,Z,DIST,thr,phr c      print*,X,Y,Z,DIST,thr,phr
 c      print*,SANE_BETA_OMEGA c      print*,SANE_BETA_OMEGA
         if(cer_stat.gt.0)then
   
          if(field_type.gt.0)then          if(field_type.gt.0)then
             if(SANE_BETA_OMEGA.lt.50)then             if(SANE_BETA_OMEGA.lt.50)then
       call POLYNOM_CORRECTION(SANE_TRANSFORM_MATRIX_THETA_40,       call POLYNOM_CORRECTION(SANE_TRANSFORM_MATRIX_THETA_40,
Line 470 
Line 474 
          phi=phr*180/3.14159          phi=phr*180/3.14159
          th = thr*180/3.14159          th = thr*180/3.14159
       endif       endif
         else
   c            phi=phr*180/3.14159
   c            th = thr*180/3.14159
            th  = THR*180/3.1415926+
        ,        (P_th(1)+P_th(2)*phr+P_th(3)*thr+
        ,        P_th(4)*phr**2+P_th(5)*thr**2)/EE+
        ,        (P_th(6)+P_th(7)*thr+P_th(8)*phr+
        ,        P_th(9)*phr**2+P_th(10)*thr**2)/EE**2
            phi = phR*180/3.1415926
        ,        +(P_phi(1)+P_phi(2)*phr+P_phi(3)*phr**2+
        ,        P_phi(4)*phr**3+P_phi(5)*thr+P_phi(6)*thr**2+
        ,        P_phi(7)*thr**3+P_phi(8)*phr*thr+
        ,        P_phi(9)*phr**2*thr+
        ,        P_phi(10)*phr*thr**2)
   
         endif
   
       phi=phi       phi=phi
 c      write(*,*)phr*180/3.141-90,phi,SANE_BETA_OMEGA c      write(*,*)phr*180/3.141-90,phi,SANE_BETA_OMEGA
  
Line 584 
Line 605 
          write(*,*)'CHECK NAN ',did          write(*,*)'CHECK NAN ',did
       endif       endif
       end       end
   
   c      subroutine Blockzero
   c$$$      do i=1,32
   c$$$         do j=1,56
   c$$$            Energy(i,j)=0
   c$$$         enddo
   c$$$      enddo


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

Analyzer/Replay: Mark Jones, Documents: Stephen Wood
Powered by
ViewCVS 0.9.2-cvsgraph-1.4.0