!+ ! Program bmad_to_opal ! ! Example program to make an OPAL input file from a Bmad lattice ! ! Input (command line) ! bmad_to_opal_params namelist ! lat_filename lat.bmad ! ! ! Output ! lat_opal.in !- program bmad_to_opal use bmad use beam_mod use opal_interface_mod use time_tracker_mod use write_lat_file_mod implicit none type (lat_struct), target :: lat type (ele_struct), pointer :: ele(:) character(100) in_filename character(100) lat_filename, lat2_filename, lat_path, basename type (beam_init_struct) beam_init type (beam_struct) beam type (ele_struct), pointer :: ele1 character(100) opal_filename, opal_particle_filename, time_particle_filename character(40) :: r_name = 'bmad_to_opal' integer :: n_arg, n_char integer :: nmlfile, outfile, iu, ios, i logical :: write_time_particles, write_opal_particles, write_phasing_info logical :: err namelist / bmad_to_opal_params / lat_filename, lat2_filename, & write_time_particles, write_opal_particles, write_phasing_info, beam_init !------------------------------------------ !Setup !Get units for files nmlfile = lunget() outfile = lunget() !Get input file from command line n_arg = command_argument_count() if (n_arg > 1) then print *, 'Usage: bmad_to_opal ' print *, 'Default: = bmad_to_opal.in' stop endif in_filename = 'bmad_to_opal.in' !default if (n_arg == 1) call get_command_argument(1, in_filename) ! Defaults of input file lat_filename = 'lat.bmad' lat2_filename = '' write_time_particles = .false. write_opal_particles = .false. write_phasing_info = .false. beam_init%n_particle = 1 beam_init%n_bunch = 1 !read input file print *, 'Opening: ', trim(in_filename) open (nmlfile, file = in_filename, status = "old") read (nmlfile, nml = bmad_to_opal_params) close (nmlfile) !Trim filename n_char= SplitFileName(lat_filename, lat_path, basename) !Prepare OPAL file call file_suffixer (basename, opal_filename, 'opal', .true.) iu = lunget() open (iu, file = opal_filename, iostat = ios) if (ios /= 0) then call out_io (s_error$, r_name, 'CANNOT OPEN FILE: ' // trim(opal_filename)) stop endif !Print info to screen print *, '--------------------------------------' write (*, '(2a)'), 'Bmad lattice: ', lat_filename write (*, '(2a)'), 'OPAL input file = ', opal_filename print *, '--------------------------------------' !------------------------------------------ !Bmad to OPAL !Parse Lattice call bmad_parser (lat_filename, lat) !Parse additional settings if (lat2_filename /= '') then print *, 'Parsing: '//trim(lat2_filename) call bmad_parser2 (lat2_filename, lat) endif !Fudge ele => lat%ele if (write_phasing_info) then do i = 1, lat%n_ele_track write (*, '(2a, es20.7)') trim(ele(i)%name), ' entrance ref time: ', ele(i-1)%ref_time enddo endif !Finally make OPAL input file call write_opal_lattice_file(iu, lat) !------------------------------------------- !Cleanup print *, "Written: ", opal_filename !Close file close(iu) ! Stop if no particles are to be written if ( (.not. write_time_particles) .and. (.not. write_opal_particles) ) then stop endif !------------------------------------------- !Particle distribution !Write particle file if more than one particle is defined if (beam_init%n_particle > 1 ) then !set ele1 to be the init_ele ele1 => lat%ele(0) !Initialize beam call init_beam_distribution (ele1, lat%param, beam_init, beam) beam%bunch(1)%particle(:)%p0c = ele1%value(p0c_start$) call out_io (s_info$, r_name, 'Initialized bunch with p0c = \es13.3\', ele1%value(p0c_start$) ) !Prepare OPAL file call file_suffixer (basename, opal_particle_filename, 'opal_particles', .true.) call file_suffixer (basename, time_particle_filename, 'time_particles', .true.) if (write_opal_particles) then open (iu, file = opal_particle_filename, iostat = ios) if (ios /= 0) then call out_io (s_error$, r_name, 'CANNOT OPEN FILE: ' // trim(opal_particle_filename)) stop endif !Write the first bunch only call write_time_particle_distribution (iu, beam%bunch(1), ele1, style = 'OPAL') print *, beam%bunch(1)%particle(27)%vec print *, "Written: ", opal_particle_filename close(iu) endif if (write_time_particles) then open (iu, file = time_particle_filename, iostat = ios) if (ios /= 0) then call out_io (s_error$, r_name, 'CANNOT OPEN FILE: ' // trim(time_particle_filename)) stop endif !Write the first bunch only call write_time_particle_distribution (iu, beam%bunch(1), ele1) print *, beam%bunch(1)%particle(27)%vec print *, "Written: ", time_particle_filename close(iu) ! Track to the end, write to file for reference print *, beam%bunch(1)%particle(27)%vec call track_beam (lat, beam, err=err) print *, beam%bunch(1)%particle(27)%vec call file_suffixer (basename, time_particle_filename, 'end_opal_particles', .true.) open (iu, file = time_particle_filename, iostat = ios) call write_time_particle_distribution (iu, beam%bunch(1), ele1, style = 'OPAL') print *, "Written: ", time_particle_filename close(iu) endif endif end program