! select lines from geometry file program select_lines use cesr_utils implicit none integer ix, i, j, k, l integer nargs,iargc integer lun integer num_element(10) character*140 lat_file character*120 line character*3 ans character*16 element_name, elements(10) character*16 new_word, old_word(1000) nargs = cesr_iargc() if(nargs == 1)then call cesr_getarg(1,lat_file) print *, 'Using ', trim(lat_file) else lat_file = 'geometry.dat' print '(a37,$)',' Geometry file name ? (default= geometry.dat) ' read(5,'(a)') line call string_trim(line, line, ix) lat_file = line if(ix == 0) lat_file = 'geometry.dat' print *, ' geometry = ', lat_file endif lun=lunget() open(unit=lun, file=lat_file) i=0 old_word(1:1000) = ' ' do while(.true.) read(lun,'(a)', end=199)line call string_trim(line, line, ix) new_word = line(1:ix) if(any( new_word == old_word(1:1000)))cycle i=i+1 if(i > 1000)goto 199 old_word(i) = new_word end do 199 do j=1,i/10+1 print '(10a)',old_word(10*j-9:10*j) end do close(unit=lun) lun=lunget() open(unit=lun, file=lat_file) i=0 do while(i<10) print '(a,$)', 'Select an element to read and write ' read(5,'(a)'), element_name call string_trim(element_name, element_name, ix) if(ix==0)exit i=i+1 elements(i) = element_name(1:ix) open(unit = 11+i,file = trim(element_name)//'.dat') end do num_element=0 if(i/=0)print *,' Selected elements' do j=1,i print '(a)', elements(j) end do do while(.true.) read(lun,'(a)', end=99)line do j=1,i call string_trim(elements(j),elements(j),ix) ! if(index(line,trim(elements(j)), .true.)/= 0)print '(a)', line if(index(line,trim(elements(j)))/= 0)then write(11+j,'(a)')line num_element(j) = num_element(j)+1 endif enddo end do 99 continue do j=1,i print '(a,i3)',elements(j),num_element(j) end do end