subroutine init_init (u, graph, in_line) use cesrv_struct use cesrv_interface use calib_file_mod implicit none type (universe_struct), pointer :: u type (graph_struct) :: graph integer i, ix, ixc, istat, tt_addr character(*) in_line character(200) line, str character(20) cmd character(200) :: switch_list(1) = ['-custom_calib'], switch = '' logical err_flag, err ! Global init bmad_com%auto_bookkeeper = .false. istat = tt_addr() ! Needed for digital_tracker IO ! get input file name if typed on the same line as the run command if (len_trim(in_line) == 0) then ! get command line arguments and process line = '' do i = 1, cesr_iargc() call cesr_getarg(i, str) line = trim(line) // ' ' // trim(str) enddo else line = in_line endif ! only allow switches from command line: do ! extract first word from 'line' and push it to 'switch': ! note that cesrv_next_switch calls string_trim call cesrv_next_switch(line, switch_list, switch, err, ix) if (err) return select case (trim(switch)) case ('') ! no more switches exit case ('-custom_calib') call read_custom_calib_files(line(:ix)) ! first word should be file name call string_trim(line(ix+1:), line, ix) ! advance to next word case default write(*,*) "I DO NOT UNDERSTAND: ", trim(switch) write(*,*) "Stopping here..." stop end select enddo ! if nothing typed then issue a query at the terminal err_flag = .false. 100 continue if (err_flag .or. line == '') then print '(a, 20(/, a))', & ' You can enter:', & ' * "READ FAKE " ! Read in fake data file', & ' * "READ O: " ! To read an orbit, 0 => latest orbit', & ' * "TAKE ORBIT" ! To take an orbit', & ' * "READ P: " ! To read a phase/coupling file, 0 => latest', & ' * "TAKE PHASE" ! To take a phase/coupling measurement', & ' * "READ E: " ! To read a dispersion data file, 0 => latest', & ' * "TAKE ETA" ! To take a dispersion MEASUREMENT' , & ' * "READ AC: " ! To read an AC dispersion data file, 0 => latest', & ' * "TAKE AC_ETA" ! To take an AC dispersion MEASUREMENT' , & ' * "READ B: " ! To read a beta data file, 0 => latest', & ' * "READ CSR " ! To read in a csr save set', & ' * "CALL " ! Use a CESRV command file', & ' * "L: " ! No data, use lattice', & ' * "L:0" ! No data, use the current lattice', & ' * "L:" ! Choose from a list of lattices', & ' * "F: " ! No data, use bmad input file ' call get_input_string ('Input:', line) endif call string_trim(line, line, ix) call str_upcase (cmd, line(:ix)) ! Now parse input line ! With a command file call cesrv_command twice: First time opens the command file ! and the second time initializes the lattice. err_flag = .true. if (ix == 0) then ! if nothing entered print *, 'ERROR: NOTHING TYPED. TRY AGAIN...' goto 100 endif if (cmd == 'TAKE') then call getlat (logic%lattice) ! lattice needed for eta measurement call init_lattice (u, .true., make_groups$) call string_trim (line(ix+1:), line, ix) if (ix == 0) then print *, 'ERROR: PHASE OR ORBIT TO MEASURE?' goto 100 endif line = 'TAKE DATA ' // line call cesrv_command (line, u, graph, err_flag) ! read as DATA if (err_flag) goto 100 else if (cmd == 'ORBMON') then logic%orbit_monitoring = .true. call cesrv_command (cmd, u, graph, err_flag) ! Start orbit monitoring else ixc = index(cmd, ':') if (ixc /= 0) cmd = cmd(1:ixc) call match_word (cmd, ['TAKE', 'CALL', 'DO ', 'L: ', 'F: ', 'READ'], ix) if (ix == 0) line = 'READ ' // line call cesrv_command (line, u, graph, err_flag) ! read as DATA if (err_flag) goto 100 ! try again on error if (cmd == 'DO' .or. cmd == 'CALL') then call get_cesrv_command ('CESRV>', line) call cesrv_command (line, u, graph, err_flag) endif if (u%ring%lattice == " ") then close (logic%iu_command_file) logic%command_file_open = .false. goto 100 endif endif ! still not initialized? if (logic%lattice(:4) == 'INIT') goto 100 ! Finalize if (logic%opt_vars == 0) then ! if not yet set call opt_vars_set (opt_steering$, .true.) call transfer ('MODEL', 'DATA', 1.0_rp, u) endif call showit ('ENERGY_SHIFT', u) end subroutine