V3FIT
ipch_dot.f
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! The @fixed_width, @begin_table, @item2 and @end_table commands are custom
3 ! defined commands in Doxygen.in. They are defined under ALIASES. For the page
4 ! created here, the 80 column limit is exceeded. Arguments of aliases are
5 ! separated by ','. If you intended ',' to be a string you must use an escaped
6 ! comma '\,'.
7 !
88 !-------------------------------------------------------------------------------
89 !*******************************************************************************
92 !
93 ! Note separating the Doxygen comment block here so detailed decription is
94 ! found in the Module not the file.
95 !
98 !*******************************************************************************
99 
100  MODULE ipch_dot
101 
102  USE stel_kinds
103  USE stel_constants
104  USE signal_dot
105 
106  IMPLICIT NONE
107 
108  CONTAINS
109 !*******************************************************************************
110 ! UTILITY SUBROUTINES
111 !*******************************************************************************
112 !-------------------------------------------------------------------------------
128 !-------------------------------------------------------------------------------
129  SUBROUTINE ipch_dot_read(ipch_file, signals, signals_created, &
130  & observed, sigma, weight, first_index, &
131  & use_polarimetry)
132  USE signal
133  USE data_parameters
134 
135  IMPLICIT NONE
136 
137 ! Declare Arguments
138  CHARACTER (len=path_length), INTENT(in) :: ipch_file
139  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
140  INTEGER, INTENT(inout) :: signals_created
141  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
142  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
143  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
144  INTEGER, INTENT(inout) :: first_index
145  LOGICAL, INTENT(out) :: use_polarimetry
146 
147 ! local parameters
148 ! n_ipchd_keyword integer - number of ipchd_keyword s.
149  INTEGER, PARAMETER :: n_ipchd_keyword = 9
150 
151 ! local variables
152 ! ipchd_keyword character array - keywords for various ipch input types
153  CHARACTER(len=data_name_length), DIMENSION(1:n_ipchd_keyword) :: &
154  & ipchd_keyword
155  TYPE(signal_dot_file) :: ipch_dot_file_ref
156  REAL (rprec) :: start_time
157 
158 ! Start of executable code
159  start_time = profiler_get_start_time()
160 
161 ! Initialize the keywords and keyword lengths
162  ipchd_keyword(1) = 'ip_chord_XYZ'
163  ipchd_keyword(2) = 'ip_chord_RPhiDegZ'
164  ipchd_keyword(3) = 'ip_chord_XYZ_int'
165  ipchd_keyword(4) = 'ip_chord_RPhiDegZ_int'
166  ipchd_keyword(5) = 'ip_chord_XYZ_pol_rad'
167  ipchd_keyword(6) = 'ip_chord_RPhiDegZ_pol_rad'
168  ipchd_keyword(7) = 'ip_chord_XYZ_pol_deg'
169  ipchd_keyword(8) = 'ip_chord_RPhiDegZ_pol_deg'
170  ipchd_keyword(9) = 'end_of_file'
171 
172 ! Open up the 'ipch.' file
173  ipch_dot_file_ref = signal_dot_open(trim(ipch_file), 'ipch')
174 
175  use_polarimetry = .false.
176 
177 ! Infinite Loop
178 ! Character variable line should be defined on entry
179  DO
180 ! Branch on the keyword
181  SELECT CASE (signal_dot_read_keyword(ipch_dot_file_ref, &
182  & ipchd_keyword))
183 
184  CASE DEFAULT ! This case should never fire.
185  EXIT ! Exit out of infinte loop.
186 
187  CASE ('end_of_file')
188  EXIT ! Exit out of infinte loop.
189 
190  CASE ('ip_chord_XYZ','ip_chord_XYZ_int')
191  CALL ipch_dot_parse_chord(ipch_dot_file_ref, &
192  & 'XYZ', 'i', .false., &
193  & signals, signals_created, &
194  & observed, sigma, weight, &
195  & first_index)
196 
197 
198  CASE ('ip_chord_RPhiDegZ','ip_chord_RPhiDegZ_int')
199  CALL ipch_dot_parse_chord(ipch_dot_file_ref, &
200  & 'RPHiDegZ', 'i', .false., &
201  & signals, signals_created, &
202  & observed, sigma, weight, &
203  & first_index)
204 
205 
206  CASE ('ip_chord_XYZ_pol_rad')
207  CALL ipch_dot_parse_chord(ipch_dot_file_ref, &
208  & 'XYZ', 'p', .false., &
209  & signals, signals_created, &
210  & observed, sigma, weight, &
211  & first_index)
212  use_polarimetry = .true.
213 
214 
215  CASE ('ip_chord_RPhiDegZ_pol_rad')
216  CALL ipch_dot_parse_chord(ipch_dot_file_ref, &
217  & 'RPHiDegZ', 'p', .false., &
218  & signals, signals_created, &
219  & observed, sigma, weight, &
220  & first_index)
221  use_polarimetry = .true.
222 
223 
224  CASE ('ip_chord_XYZ_pol_deg')
225  CALL ipch_dot_parse_chord(ipch_dot_file_ref, &
226  & 'XYZ', 'p', .true., &
227  & signals, signals_created, &
228  & observed, sigma, weight, &
229  & first_index)
230  use_polarimetry = .true.
231 
232 
233  CASE ('ip_chord_RPhiDegZ_pol_deg')
234  CALL ipch_dot_parse_chord(ipch_dot_file_ref, &
235  & 'RPHiDegZ', 'p', .true., &
236  & signals, signals_created, &
237  & observed, sigma, weight, &
238  & first_index)
239  use_polarimetry = .true.
240 
241 
242  END SELECT
243 
244  END DO
245 
246 ! Close the 'ipch.' file
247  CALL signal_dot_close(ipch_dot_file_ref)
248 
249  CALL profiler_set_stop_time('ipch_dot_read', start_time)
250 
251  END SUBROUTINE
252 
253 !*******************************************************************************
254 ! PARSING SUBROUTINES
255 !*******************************************************************************
256 !-------------------------------------------------------------------------------
283 !-------------------------------------------------------------------------------
284  SUBROUTINE ipch_dot_parse_chord(ipch_dot_file_ref, &
285  & coordinate_type, &
286  & chord_type, &
287  & inDegrees, &
288  & signals, &
289  & signals_created, &
290  & observed, sigma, weight, &
291  & first_index)
292  USE intpol
293  USE v3fit_input, only: v3fit_max_diagnostics, &
296  USE v3_utilities, only: err_fatal
297 
298  IMPLICIT NONE
299 
300 ! Declare Arguments
301  TYPE (signal_dot_file), INTENT(inout) :: ipch_dot_file_ref
302  CHARACTER (len=*), INTENT(in) :: coordinate_type
303  CHARACTER (len=1), INTENT(in) :: chord_type
304  LOGICAL, INTENT(in) :: inDegrees
305  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
306  INTEGER, INTENT(inout) :: signals_created
307  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
308  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
309  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
310  INTEGER, INTENT(inout) :: first_index
311 
312 ! local variables
313  REAL (rprec), DIMENSION(2,3) :: xcart
314  CHARACTER (len=data_name_length) :: chord_name
315  REAL (rprec) :: wavelength = 0.0
316  REAL (rprec) :: start_time
317  CHARACTER (len=6) :: units
318  class(intpol_class), POINTER :: intpol_obj
319 
320 ! Start of executable code
321  start_time = profiler_get_start_time()
322 
323 ! Check if there are two many signals.
324  IF (signals_created + 1 .gt. v3fit_max_diagnostics) THEN
325  CALL err_fatal('ipch_dot_parse_chord_new: created signals' // &
326  & ' exceeds v3fit_max_diagnostics')
327  END IF
328 
329 ! Get the start, end and name of chord.
330  CALL signal_dot_parse_chord(ipch_dot_file_ref, &
331  & coordinate_type, &
332  & chord_name, &
333  & xcart(1,:), xcart(2,:))
334 
335  IF (chord_type .eq. 'p') THEN
336  wavelength = signal_dot_parse_real(ipch_dot_file_ref, &
337  & 'Expected wavelength for polarimetry chord')
338  intpol_obj => intpol_pol_class(wavelength, indegrees, xcart)
339 
340  IF (indegrees) THEN
341  units = 'degree'
342  ELSE
343  units = 'radian'
344  END IF
345 
346  CALL signal_construct(intpol_obj, chord_name, chord_name, &
347  & units, observed(signals_created + 1), &
348  & sigma(signals_created + 1), &
349  & weight(signals_created + 1), &
350  & v3fit_input_find_scale_index(signals_created + 1), &
351  & v3fit_input_find_offset_index(signals_created + 1))
352 
353  signals(signals_created + 1)%p => intpol_obj
354  ELSE
355  intpol_obj => intpol_class(xcart)
356  CALL signal_construct(intpol_obj, chord_name, chord_name, &
357  & 'm^-2', observed(signals_created + 1), &
358  & sigma(signals_created + 1), &
359  & weight(signals_created + 1), &
360  & v3fit_input_find_scale_index(signals_created + 1), &
361  & v3fit_input_find_offset_index(signals_created + 1))
362 
363  signals(signals_created + 1)%p => intpol_obj
364  END IF
365 
366  signals_created = signals_created + 1
367 
368 ! At lease one intpol signal was made. Set the first index. This should only be
369 ! run once.
370  IF (first_index .eq. -1) THEN
371  first_index = signals_created
372  END IF
373 
374  CALL profiler_set_stop_time('ipch_dot_parse_chord', start_time)
375 
376  END SUBROUTINE
377 
378  END MODULE
intpol
Implements interferometry/polarimetry diagnostic. Defines the base class of the type intpol_class.
Definition: intpol.f:14
intpol::intpol_pol_class
Base class representing a polarimetry signal.
Definition: intpol.f:59
v3fit_input::v3fit_max_diagnostics
integer, parameter v3fit_max_diagnostics
Maximum number of diagnostic signals.
Definition: v3fit_input.f:582
v3fit_input::v3fit_input_find_scale_index
integer function v3fit_input_find_scale_index(index)
Finds the index of the scaling spec.
Definition: v3fit_input.f:1521
v3fit_input
This file contains all the variables and maximum sizes of the inputs for a v3fit namelist input file....
Definition: v3fit_input.f:570
intpol::intpol_class
Base class representing a interferometer signal.
Definition: intpol.f:40
signal_dot
Defines the base class of type signal_dot_file. This module contains common code used in parsing diag...
Definition: signal_dot.f:14
signal_dot::signal_dot_parse_real
real(rprec) function, public signal_dot_parse_real(signal_dot_file_ref, message)
Parse a single real from a diagnostic dot file.
Definition: signal_dot.f:211
ipch_dot::ipch_dot_read
subroutine ipch_dot_read(ipch_file, signals, signals_created, observed, sigma, weight, first_index, use_polarimetry)
Read an interferometry/polarimetry diagnostic dot file.
Definition: ipch_dot.f:132
ipch_dot
Module for opening and reading a 'ipch.' file. The file format for these files are documented in Inte...
Definition: ipch_dot.f:100
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
signal_dot::signal_dot_parse_chord
subroutine, public signal_dot_parse_chord(signal_dot_file_ref, coordinate_type, chord_name, xcart_i, xcart_f)
Parse a chord from a diagnostic dot file.
Definition: signal_dot.f:147
signal_dot::signal_dot_open
type(signal_dot_file) function, public signal_dot_open(file, signal_id)
Open a diagnostic dot file.
Definition: signal_dot.f:68
signal_dot::signal_dot_read_keyword
character(len=data_name_length) function, public signal_dot_read_keyword(signal_dot_file_ref, keywords)
Read a keyword from the diagnostic dot file.
Definition: signal_dot.f:412
ipch_dot::ipch_dot_parse_chord
subroutine ipch_dot_parse_chord(ipch_dot_file_ref, coordinate_type, chord_type, inDegrees, signals, signals_created, observed, sigma, weight, first_index)
Parse interferometry/polarimetry diagnostic chord.
Definition: ipch_dot.f:292
v3fit_input::v3fit_input_find_offset_index
integer function v3fit_input_find_offset_index(index)
Finds the index of the offset spec.
Definition: v3fit_input.f:1563
signal
Defines the base class of the type signal_class.
Definition: signal.f:14
signal_dot::signal_dot_close
subroutine, public signal_dot_close(signal_dot_file_ref)
Close a diagnostic dot file.
Definition: signal_dot.f:107