subroutine get_tracker_acceptance(tvox) use precision_def use sim_utils implicit none type tracker_voxel real(rp) pVtx integer nGen, nVtx end type tracker_voxel type (tracker_voxel) tvox(0:180,0:18,0:18) character*50 voxel_file,voxel_f(3) character*600 long_string real(rp) pVtx, value real(rp) x,y,z integer nGen, nVtx logical itexists logical first/.true./ integer lun integer i integer ix, ixx,iy,iz,number lun=lunget() voxel_f(1) = 'TrackerVoxel.txt' voxel_f(2) = 'TrackerVoxel_truth.txt' voxel_f(3) = 'TrackerVoxel_truthQuality.txt' print '(2(a,a3,3x),a3,3x,a,a5,3x,$)', trim(voxel_f(1)),'(1)',trim(voxel_f(2)),'(2)', 'or',trim(voxel_f(3)),'(3) ' read(5, *)number voxel_file = voxel_f(number) print '(a,a)','file = ',trim(voxel_file) inquire (file=voxel_file, exist = itexists) if(.not. itexists)then print *, voxel_file, ' does not exist' return endif open(lun,file=voxel_file) do while(.true.) read(lun,'(a)',end=99)long_string if(long_string(1:3) == ' ' .or. index(long_string,'distance')/= 0)cycle i=0 ix=0 do while(i<12) call string_trim(long_string(ix+1:), long_string, ix) i=i+1 if(index(long_string(1:ix),':')/= 0)cycle read(long_string(1:ix),*)value if(i == 2)then z = value elseif(i == 4)then x=value elseif(i == 6)then y = value elseif(i == 8)then nGen=value elseif(i == 10)then nVtx = value elseif (i == 12)then pVtx = value endif end do iz=(z-1700)/10 ixx = (x+42.5)/5 iy= (y+42.5)/5 tvox(iz,ixx,iy)%nGen=nGen tvox(iz,ixx,iy)%nVtx=nVtx tvox(iz,ixx,iy)%pVtx= pVtx end do 99 continue return end subroutine get_tracker_acceptance