subroutine read_beta (data_or_ref, num_in, u, graph, err_flag) use cesrv_struct use cesrv_interface implicit none type dq_struct real(rp) x, y end type type (dq_struct) b(0:120) type (universe_struct), target :: u type (graph_struct) graph integer data_or_ref, ios, beta_num, num_in, iu character(140) file_name logical err_flag namelist / dq_data / b ! since we are reading in beta data we set the optimization to quads logic%use_old_in_loading = .false. if (logic%opt_vars == opt_steering$) then logic%opt_vars = opt_quad$ call baseline_set (plot_design$, set_to$, graph%bottom1) endif ! read a data file... ! first construct the file name call calc_file_number ('U:[CESR.CESRV.BETA_DATA]BETA.NUMBER', num_in, & beta_num, err_flag) if (err_flag) return call form_file_name_with_number ('BETA', beta_num, file_name, err_flag) if (err_flag) return ! open the file iu = lunget() open (iu, file = file_name, status = 'old', action = 'read', iostat = ios) if (ios /= 0) then ! abort on open error print *, 'ERROR OPENING: ', trim(file_name) err_flag = .true. close (iu) return endif call read_header (iu, data_or_ref, u%beta, u) rewind (iu) b(:)%x = 0 read (iu, nml = dq_data, iostat = ios) close (iu) if (ios /= 0) then print *, 'ERROR READING dQ_DATA NAMELIST IN: ', trim(file_name) err_flag = .true. return endif !--------------------------------------------------------------------------- ! Read beta data if (data_or_ref == data_file$) then u%beta%measured = .true. u%beta%file_name = file_name u%beta%ix_meas = beta_num u%beta%x%d(:)%good_dat = .false. u%beta%y%d(:)%good_dat = .false. u%beta%x%d(:)%meas = b(:)%x u%beta%y%d(:)%meas = b(:)%y where (b(:)%x /= 0) u%beta%x%d(:)%good_dat = .true. u%beta%y%d(:)%good_dat = .true. end where print *, ' beta DATA READ IN' call set_plot (graph%bottom1, u%beta) !-------------------------------------------------------------------- ! Read beta ref elseif (data_or_ref == ref_file$) then u%beta%ix_ref = beta_num u%beta%ref_file_name = file_name u%beta%ref_measured = .true. u%beta%x%d(:)%good_dat = .false. u%beta%y%d(:)%good_dat = .false. u%beta%x%d(:)%meas = b(:)%x u%beta%y%d(:)%meas = b(:)%y where (b(:)%x /= 0) u%beta%x%d(:)%good_dat = .true. u%beta%y%d(:)%good_dat = .true. end where print *, 'REFERENCE beta DATA READ IN' call baseline_set (plot_ref$, add$, graph%bottom1, graph%top1) endif !--------------------------------------------------------------------- ! misc bookkeeping if (logic%opt_vars /= opt_custom$) & call opt_vars_set(opt_quad$, .false.) if (all(.not. u%beta%x%d(:)%good_user)) then u%beta%x%d(:)%good_user = .true. u%beta%y%d(:)%good_user = .true. call set_data_useit_opt (u%data) endif err_flag = .false. end subroutine