!+ ! Subroutine read_eta (data_or_ref, num_in, u, graph, err_flag, reanal) ! ! Subroutine to read in dispersion data from an input file. !- subroutine read_eta (data_or_ref, num_in, u, graph, err_flag, reanal) use cesrv_struct use cesrv_interface use sim_utils use cesr_read_data_mod implicit none type eta_data_struct real(rp) x, y logical good integer d_but(4) end type type (universe_struct), target :: u type (graph_struct) graph type (eta_data_struct) eta_(0:120) type (butns_struct) butns_le, butns_he type (but_value_struct) gain(0:120) real(rp) vec(2) real rdummy real(rp) tilt(0:120), eta_x, eta_y integer i, j, data_or_ref, num_in, ix_eta, ios, iu, file_num, det_type(120), raw(4, 120) character(140) file_name, filein character(140) eta_number character(140) gain_correction_file, gain_file logical err_flag, reanal namelist / dispersion_data / eta_ ! open and read the file... ! first thing is to construct the file name logic%use_old_in_loading = .false. call number_to_file_name (num_in, 'eta', file_name, ix_eta, err_flag) if (err_flag) return 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%eta, u) call read_orbit (data_or_ref, u%eta_params%orbit_num, u, graph, err_flag) read (iu, nml = dispersion_data) close (iu) if(reanal) then call get_gain(gain) call number_to_file_name (u%eta_params%orbit_num2, 'orbit', filein, file_num, err_flag) if (err_flag) return ! Error call read_butns_file (filein, butns_he, u%db, err_flag, .true., & logic%nonlinear_calc, logic%offset_correction, logic%gain_correction) call number_to_file_name (u%eta_params%orbit_num1, 'orbit', filein, file_num, err_flag) if (err_flag) return ! Error call read_butns_file (filein, butns_le, u%db, err_flag, .true., & logic%nonlinear_calc, logic%offset_correction, logic%gain_correction) eta_(0:120)%x = (butns_he%det(0:120)%x_orb - butns_le%det(0:120)%x_orb )/ u%eta_params%del_e_e eta_(0:120)%y = (butns_he%det(0:120)%y_orb - butns_le%det(0:120)%y_orb )/ u%eta_params%del_e_e endif if (logic%wolski_normal_mode_calc_on) then print *, 'Note: Wolski normal mode calc applied.' endif ! apply tilts, if necessary if (logic%tilt_correction) then call get_tilt(tilt) do i = lbound(tilt,1), ubound(tilt,1) ! rotate by -tilt(i); tilts are saved from fitted model in CESRv eta_x = eta_(i)%x * cos(-tilt(i)) + eta_(i)%y * sin(-tilt(i)) eta_y = -eta_(i)%x * sin(-tilt(i)) + eta_(i)%y * cos(-tilt(i)) eta_(i)%x = eta_x eta_(i)%y = eta_y enddo write(*,*) "Applying tilts from ", trim(logic%tilt_correction_file) endif !--------------------------------------------------------------------------- ! For DATA if (data_or_ref == data_file$) then u%eta%file_name = file_name u%eta%measured = .true. u%eta%ix_meas = ix_eta u%eta%x%d(:)%good_dat = .false. u%eta%y%d(:)%good_dat = .false. u%eta%x%d(:)%good_dat = eta_%good u%eta%x%d(:)%meas = eta_%x u%eta%y%d(:)%good_dat = eta_%good u%eta%y%d(:)%meas = eta_%y print *, ' ETA DATA READ IN: ', trim(file_name) ! mode eta u%mode_eta%file_name = file_name u%mode_eta%measured = .true. u%mode_eta%ix_meas = ix_eta u%mode_eta%x%d%good_dat = .false. u%mode_eta%y%d%good_dat = .false. if (logic%wolski_normal_mode_calc_on) then call number_to_file_name (u%eta_params%orbit_num, 'orbit', filein, file_num, err_flag) if (err_flag) return ! Error call butfilget (raw, filein, rdummy, det_type) do i = 0, 120 if (.not. u%eta%x%d(i)%good_dat) cycle j = i if (i == 0) j = 100 vec = matmul (u%but_to_mode(i)%mat, eta_(i)%d_but) / sum(raw(:,j)) u%mode_eta%x%d(i)%meas = vec(1) / u%eta_params%del_e_e u%mode_eta%y%d(i)%meas = vec(2) / u%eta_params%del_e_e u%mode_eta%x%d(i)%good_dat = .true. u%mode_eta%y%d(i)%good_dat = .true. enddo if (graph%top1%d2%type /= eta_data$ .and. graph%top1%d2%type /= mode_eta_data$) then call set_plot (graph%top1, u%mode_eta) call plot_data_set (graph%top1, plot_meas$) endif endif if (graph%bottom1%d2%type /= eta_data$ .and. graph%bottom1%d2%type /= mode_eta_data$) then call set_plot (graph%bottom1, u%eta) call plot_data_set (graph%bottom1, plot_meas$) endif !-------------------------------------------------------------------- ! For REF elseif (data_or_ref == ref_file$) then u%eta%x%d(:)%good_ref = .false. u%eta%y%d(:)%good_ref = .false. u%eta%x%d(:)%good_ref = eta_%good u%eta%x%d(:)%ref = eta_%x u%eta%y%d(:)%good_ref = eta_%good u%eta%y%d(:)%ref = eta_%y print *, ' REFERENCE ETA DATA READ IN: ', trim(file_name) u%eta%ref_file_name = file_name u%eta%ref_measured = .true. u%eta%ix_ref = ix_eta ! mode eta u%mode_eta%ref_file_name = file_name u%mode_eta%ref_measured = .true. u%mode_eta%ix_ref = ix_eta u%mode_eta%x%d%good_ref = .false. u%mode_eta%y%d%good_ref = .false. if (logic%wolski_normal_mode_calc_on) then do i = 0, 120 if (.not. u%eta%x%d(i)%good_dat) cycle vec = matmul (u%but_to_mode(i)%mat, eta_(i)%d_but) u%mode_eta%x%d(i)%ref = vec(1) / u%eta_params%del_e_e u%mode_eta%y%d(i)%ref = vec(2) / u%eta_params%del_e_e u%mode_eta%x%d(i)%good_ref = .true. u%mode_eta%y%d(i)%good_ref = .true. enddo endif endif err_flag = .false. end subroutine