subroutine read_field(fringe_or_inflector, map,xmin) use magfield use magfield_interface, dummy => read_field use parameters_bmad implicit none type(magfield_struct), allocatable :: position(:), map(:,:,:) type(magfield_struct) x0, xmax, xmin, dxyz(-1:1) integer iu, istat/0/, nlines, ind(3),i,j,k,l, ntot(3), ix,jx integer k1, k2 integer delta integer multiplier integer fringe_or_inflector character*140 string real(rp) b1(3), b2(3) iu = lunget() print '(a19,a)',' Open field file =', field_file%name if(field_file(fringe_or_inflector)%type == 4)then print '(a)', ' Field file name = ', field_file(fringe_or_inflector)%name,' type = ',field_file(fringe_or_inflector)%type print '(a)', 'No field map for uniform field' allocate(map(1,1,1)) xmin%x(1:3) = 0. xmax%x(1:3) = 0. return endif open(unit=iu, file = field_file(fringe_or_inflector)%name, status = 'old', action='read') nlines = 0 xmin%x=1000. xmax%x=-1000. x0%x(1:3)=0. do while(.true.) string(1:140) = ' ' read(iu, '(a140)', IOSTAT = istat ) string if(istat < 0) exit if(index(string,'#') /= 0)cycle if(string(1:10) == ' ')cycle if(field_file(fringe_or_inflector)%type == 1) read(string, *)x0%x(1:3), x0%B(1:3), x0%H if(field_file(fringe_or_inflector)%type == 2) read(string, *)x0%x(1:3), x0%B(1:3) if(field_file(fringe_or_inflector)%type == 3) read(string, *)x0%x(1:2), x0%B(1:2) xmin%x(1:3) = min(xmin%x(1:3),x0%x(1:3)) xmax%x(1:3) = max(xmax%x(1:3),x0%x(1:3)) nlines = nlines + 1 end do ! ! print *, ' nlines = ', nlines print *,' xmax ',xmax%x, 'xmin', xmin%x multiplier = 1./field_file(fringe_or_inflector)%grid_spacing ntot(1:3) = (xmax%x(1:3)-xmin%x(1:3))*multiplier + 1 ! print *, ntot allocate(map(ntot(1),ntot(2),ntot(3))) rewind(unit=iu) do while(.true.) string(1:140) = ' ' read(iu,'(a140)',IOSTAT = istat) string if(istat < 0)exit if(index(string,'#') /= 0)cycle if(string(1:10) == ' ')cycle if(field_file(fringe_or_inflector)%type == 1) read(string, *)x0%x(1:3), x0%B(1:3), x0%H if(field_file(fringe_or_inflector)%type == 2) read(string, *)x0%x(1:3), x0%B(1:3) if(field_file(fringe_or_inflector)%type == 3) read(string, *)x0%x(1:2), x0%B(1:2) ! index map from minimum to maximum value. map(1,1,1)%x = xmin%x ind(1:3) = (x0%x(1:3) - xmin%x(1:3))*multiplier + 1 map(ind(1),ind(2),ind(3))%B(1:3) = x0%B(1:3) ! if(index(field_file,'inj')/=0) & !temporary to get plot of field with fringe or inflector only ! map(ind(1),ind(2),ind(3))%B(1:3) = 0. !20140727 to zero out either inflector field or fringe map(ind(1),ind(2),ind(3))%x(1:3) = x0%x(1:3) end do return end