103 & signals_created, observed, sigma, &
104 & weight, first_index)
111 CHARACTER (len=path_length),
INTENT(in) :: sxrem_ratio_file
112 TYPE (signal_pointer),
DIMENSION(:),
INTENT(inout) :: signals
113 INTEGER,
INTENT(inout) :: signals_created
114 REAL (rprec),
DIMENSION(:),
INTENT(in) :: observed
115 REAL (rprec),
DIMENSION(:),
INTENT(in) :: sigma
116 REAL (rprec),
DIMENSION(:),
INTENT(in) :: weight
117 INTEGER,
INTENT(inout) :: first_index
121 INTEGER,
PARAMETER :: n_sxrem_ratio_keyword = 3
125 CHARACTER(len=data_name_length), &
126 & DIMENSION(1:n_sxrem_ratio_keyword) :: sxrem_ratio_keyword
127 TYPE(signal_dot_file) :: sxrem_ratio_dot_file_ref
128 REAL (rprec) :: start_time
131 start_time = profiler_get_start_time()
134 sxrem_ratio_keyword(1) =
'sxrem_ratio_XYZ'
135 sxrem_ratio_keyword(2) =
'sxrem_ratio_RPhiDegZ'
136 sxrem_ratio_keyword(3) =
'end_of_file'
147 & sxrem_ratio_keyword))
155 CASE (
'sxrem_ratio_XYZ')
157 & sxrem_ratio_dot_file_ref,
'XYZ', signals, &
158 & signals_created, observed, sigma, weight, &
161 CASE (
'sxrem_ratio_RPhiDegZ')
163 & sxrem_ratio_dot_file_ref,
'RPHiDegZ', signals, &
164 & signals_created, observed, sigma, weight, &
173 CALL profiler_set_stop_time(
'sxrem_ratio_dot_read', start_time)
203 & signals, signals_created, &
204 & observed, sigma, weight, &
210 USE v3_utilities,
only: err_fatal
215 CHARACTER (len=*) :: coordinate_type
216 TYPE (signal_pointer),
DIMENSION(:),
INTENT(inout) :: signals
217 INTEGER,
INTENT(inout) :: signals_created
218 REAL (rprec),
DIMENSION(:),
INTENT(in) :: observed
219 REAL (rprec),
DIMENSION(:),
INTENT(in) :: sigma
220 REAL (rprec),
DIMENSION(:),
INTENT(in) :: weight
221 INTEGER,
INTENT(inout) :: first_index
224 REAL (rprec),
DIMENSION(3) :: xcart
225 INTEGER,
DIMENSION(2) :: indices
226 CHARACTER (len=data_short_name_length) :: point_name
228 CHARACTER (len=data_short_name_length) :: units =
''
229 REAL (rprec) :: start_time
232 start_time = profiler_get_start_time()
236 CALL err_fatal(
'sxrem_ratio_dot_parse_chord: created signals' &
237 & //
' exceeds v3fit_max_diagnostics')
247 &
'Expected sxrem profile indices')
251 CALL signal_construct(ratio_obj, point_name, point_name, units, &
252 & observed(signals_created + 1), &
253 & sigma(signals_created + 1), weight(signals_created + 1), &
257 signals(signals_created + 1)%p => ratio_obj
259 signals_created = signals_created + 1
263 IF (first_index .eq. -1)
THEN
264 first_index = signals_created
267 CALL profiler_set_stop_time(
'sxrem_ratio_dot_parse_chord', &