program bmad_to_autocad use bmad use bmad_to_autocad_mod implicit none type (lat_struct) :: lat type (ele_struct), pointer :: map_ele type (ele_pointer_struct), allocatable :: eles(:) real(rp) :: CESR_IP_L3_x, CESR_IP_L3_z, CESR_IP_L3_theta real(rp) :: map_x, map_z, map_theta integer :: iu, ios, n_loc,namelist_file character(100) lat_name, in_file, ele_name, outfile_name logical :: err namelist / bmad_to_autocad_params / & lat_name, map_x, map_z, map_theta, ele_name !------------------------------------------ ! Coordinates of the center of IP-L3 in the CESR tunnel ! Ithaca, NY ! CESR_IP_L3_x = 0.8915840379E+06*12/39.3700787D+0 CESR_IP_L3_z = 0.8496528770E+06*12/39.3700787D+0 CESR_IP_L3_theta = 0.2281071935E+02*atan(1.D+0)/45.D+0 !------------------------------------------ !Defaults for namelist !lat_name = 'lat.bmad' map_x = CESR_IP_L3_x map_z = CESR_IP_L3_z map_theta = CESR_IP_L3_theta ele_name = 'IP_L3' !---Get lattice from command line if (iargc()==0) then print *,'' print *, 'Usage: bmad_to_autocad lat.bmad' print *, ' or: bmad_to_autocad bmad_to_autocad.in' print *, ' with bmad_to_autocad.in:' print *, '&bmad_to_autocad_params' print *, " lat_name='lat.bmad'" print *, " map_x = 0 ! x position in meters" print *, " map_z = 0 ! z position in meters" print *, " map_theta = 0 ! angle in radians" print *, " ele_name = 'BEGINNING' ! Match element to these coordinates" print *, '/' stop endif !Read namelist !in_file = 'test_template.in' ! Expect this if (command_argument_count() > 0) call get_command_argument(1, in_file) namelist_file = lunget() print *, 'Opening: ', trim(in_file) open (namelist_file, file = in_file, status = "old") read (namelist_file, nml = bmad_to_autocad_params, iostat=ios) if (ios > 0) then ! Error in namelist close (namelist_file) else if (ios < 0) then ! No namelist found. Use lat_name = in_file endif print *, '' print *, ' __ __ ___ __ ___ __ __ __ ' print *, '|__) |\/| /\ | \ | / \ /\ | | | / \ / ` /\ | \ ' print *, '|__) | | /~~\ |__/ ___ | \__/ ___ /~~\ \__/ | \__/ \__, /~~\ |__/ ' print *, ' ' print *, '' ! Prepare outfile_name call file_suffixer (lat_name, outfile_name, '.map_table', .true.) ! Parse lattice call bmad_parser(lat_name, lat) iu = lunget() open (iu, file = outfile_name) !---Locate reference element call lat_ele_locator (ele_name, lat, eles, n_loc, err) if (n_loc == 0 ) then print *, 'WARNING: CANNOT FIND ELEMENT: '//trim(ele_name) print *, ' WILL USE BEGINNING OF LATTICE INSTEAD' map_ele => lat%ele(0) map_x = 0 map_z = 0 map_theta = map_ele%floor%theta else if (n_loc >1 ) then map_ele => eles(1)%ele print *, 'WARNING: MULTIPLE ELEMENTS WITH NAME '//trim(ele_name)//' FOUND' print *, ' WILL USE ELE AT INDEX ', map_ele%ix_ele else map_ele => eles(1)%ele endif ! Write .map_table call write_autocad_map_table(iu, lat, map_ele, & map_x, map_z, map_theta) print *, 'Created: ', trim(outfile_name) print *, '' close (iu) end program