subroutine get_data_from_all_EndOfTracking_phase_space(tvox) use precision_def use sim_utils use random_mod 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*100 dir character*50 dir_file character*600 long_string, string character*2 time_off_char real(rp) x,x_last,xp_last, y_last, yp_last, pz, time, s real(rp) pVtx real(rp) rand logical itexists logical first/.true./ integer ix,i,n integer iz,ixx,iy integer, save :: lun1, lun2 if(first)then lun1 = lunget() open(unit=lun1, file = 'tracker_accepted_phase_space_180.dat') lun2 = lunget() open(unit=lun2, file = 'tracker_accepted_phase_space_270.dat') first=.false. endif dir_file = 'all_EndOfTracking_phase_space.dat' inquire (file=dir_file, exist = itexists) if(.not. itexists)then print *,dir_file,' does not exist' return endif print '(2a)', 'open ',dir_file open(unit=5,file=dir_file) do while(.true.) read(5,'(a)',end=99)long_string string =long_string if(index(long_string,'muon')/=0)cycle i=0 ix=0 do while (i<11) call string_trim(long_string(ix+1:), long_string, ix) i=i+1 read(long_string(1:ix),*)x if(i == 4)then x_last = x elseif(i == 5)then xp_last=x elseif(i == 6)then y_last = x elseif(i == 7)then yp_last=x elseif(i == 9)then pz=x elseif (i == 10)then time=x elseif (i == 11)then s=x endif end do iz = (s*100-1700)/10 iy = (y_last*1000+42.5)/5 ixx = (x_last*1000.+42.5)/5 if(y_last == 0. .and. x_last == 0. .and. xp_last == 0.)write (12,'(a)')dir_file if(iz < 0 .or. iz > 180)cycle pVtx = tvox(iz,ixx,iy)%pVtx call ran_uniform(rand) if(rand < pVtx)then !this counts if(s>16. .and. s < 26.)write(lun1, '(a)')trim(string) if(s>26. .and. s < 36.)write(lun2, '(a)')trim(string) endif end do 99 continue return end subroutine get_data_from_all_EndOfTracking_phase_space