V3FIT
sxrem_ratio_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 !
62 !-------------------------------------------------------------------------------
63 !*******************************************************************************
66 !
67 ! Note separating the Doxygen comment block here so detailed decription is
68 ! found in the Module not the file.
69 !
72 !*******************************************************************************
74 
75  USE stel_kinds
76  USE stel_constants
77  USE signal_dot
78 
79  IMPLICIT NONE
80 
81  CONTAINS
82 !*******************************************************************************
83 ! UTILITY SUBROUTINES
84 !*******************************************************************************
85 !-------------------------------------------------------------------------------
101 !-------------------------------------------------------------------------------
102  SUBROUTINE sxrem_ratio_dot_read(sxrem_ratio_file, signals, &
103  & signals_created, observed, sigma, &
104  & weight, first_index)
105  USE signal
106  USE data_parameters
107 
108  IMPLICIT NONE
109 
110 ! Declare Arguments
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
118 
119 ! local parameters
120 ! n_thscted_keyword integer - number of thscted_keyword s.
121  INTEGER, PARAMETER :: n_sxrem_ratio_keyword = 3
122 
123 ! local variables
124 ! sxrem_ratio_keyword character array - keywords for various thscte input types
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
129 
130 ! Start of executable code
131  start_time = profiler_get_start_time()
132 
133 ! Initialize the keywords and keyword lengths
134  sxrem_ratio_keyword(1) = 'sxrem_ratio_XYZ'
135  sxrem_ratio_keyword(2) = 'sxrem_ratio_RPhiDegZ'
136  sxrem_ratio_keyword(3) = 'end_of_file'
137 
138 ! Open up the 'thscte.' file
139  sxrem_ratio_dot_file_ref = signal_dot_open(trim(sxrem_ratio_file), &
140  & 'sxrem_ratio')
141 
142 ! Infinite Loop
143 ! Character variable line should be defined on entry
144  DO
145 ! Branch on the keyword
146  SELECT CASE (signal_dot_read_keyword(sxrem_ratio_dot_file_ref, &
147  & sxrem_ratio_keyword))
148 
149  CASE DEFAULT ! This case should never fire.
150  EXIT ! Exit out of infinte loop.
151 
152  CASE ('end_of_file')
153  EXIT ! Exit out of infinte loop.
154 
155  CASE ('sxrem_ratio_XYZ')
157  & sxrem_ratio_dot_file_ref, 'XYZ', signals, &
158  & signals_created, observed, sigma, weight, &
159  & first_index)
160 
161  CASE ('sxrem_ratio_RPhiDegZ')
163  & sxrem_ratio_dot_file_ref, 'RPHiDegZ', signals, &
164  & signals_created, observed, sigma, weight, &
165  & first_index)
166  END SELECT
167 
168  END DO
169 
170 ! Close the 'thscte.' file
171  CALL signal_dot_close(sxrem_ratio_dot_file_ref)
172 
173  CALL profiler_set_stop_time('sxrem_ratio_dot_read', start_time)
174 
175  END SUBROUTINE
176 
177 !*******************************************************************************
178 ! PARSING SUBROUTINES
179 !*******************************************************************************
180 !-------------------------------------------------------------------------------
200 !-------------------------------------------------------------------------------
201  SUBROUTINE sxrem_ratio_dot_parse_chord(sxrem_ratio_dot_file_ref, &
202  & coordinate_type, &
203  & signals, signals_created, &
204  & observed, sigma, weight, &
205  & first_index)
207  USE v3fit_input, only: v3fit_max_diagnostics, &
210  USE v3_utilities, only: err_fatal
211  IMPLICIT NONE
212 
213 ! Declare Arguments
214  TYPE(signal_dot_file), INTENT(inout) :: sxrem_ratio_dot_file_ref
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
222 
223 ! local variables
224  REAL (rprec), DIMENSION(3) :: xcart
225  INTEGER, DIMENSION(2) :: indices
226  CHARACTER (len=data_short_name_length) :: point_name
227  class(sxrem_ratio_class), POINTER :: ratio_obj => null()
228  CHARACTER (len=data_short_name_length) :: units = ''
229  REAL (rprec) :: start_time
230 
231 ! Start of executable code
232  start_time = profiler_get_start_time()
233 
234 ! Check if there are two many signals.
235  IF (signals_created + 1 .gt. v3fit_max_diagnostics) THEN
236  CALL err_fatal('sxrem_ratio_dot_parse_chord: created signals' &
237  & // ' exceeds v3fit_max_diagnostics')
238  END IF
239 
240 ! Get the position and name of the point.
241  CALL signal_dot_parse_chord(sxrem_ratio_dot_file_ref, &
242  & coordinate_type, &
243  & point_name, &
244  & xcart)
245 
246  indices = signal_dot_parse_2_int(sxrem_ratio_dot_file_ref, &
247  & 'Expected sxrem profile indices')
248 
249  ratio_obj => sxrem_ratio_class(xcart, indices)
250 
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), &
254  & v3fit_input_find_scale_index(signals_created + 1), &
255  & v3fit_input_find_offset_index(signals_created + 1))
256 
257  signals(signals_created + 1)%p => ratio_obj
258 
259  signals_created = signals_created + 1
260 
261 ! At lease one sxrem_ratio signal was made. Set the first index. This should
262 ! only be run once.
263  IF (first_index .eq. -1) THEN
264  first_index = signals_created
265  END IF
266 
267  CALL profiler_set_stop_time('sxrem_ratio_dot_parse_chord', &
268  & start_time)
269 
270  END SUBROUTINE
271 
272  END MODULE
v3fit_input::v3fit_max_diagnostics
integer, parameter v3fit_max_diagnostics
Maximum number of diagnostic signals.
Definition: v3fit_input.f:582
sxrem_ratio
Defines a feedback signal based on the temperature based on the ration of the soft x-ray emissivity p...
Definition: sxrem_ratio.f:16
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
signal_dot::signal_dot_file
Base class representing a diagnostic dot file. This is an opaqe class.
Definition: signal_dot.f:36
sxrem_ratio::sxrem_ratio_class
Base class representing a sxrem_ratio signal.
Definition: sxrem_ratio.f:34
sxrem_ratio_dot
Module for opening and reading a 'sxrem_ratio.' file. The file format for these files are documented ...
Definition: sxrem_ratio_dot.f:73
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_2_int
integer function, dimension(2) signal_dot_parse_2_int(signal_dot_file_ref, message)
Parse two integers from a diagnostic dot file.
Definition: signal_dot.f:373
sxrem_ratio_dot::sxrem_ratio_dot_parse_chord
subroutine sxrem_ratio_dot_parse_chord(sxrem_ratio_dot_file_ref, coordinate_type, signals, signals_created, observed, sigma, weight, first_index)
Parse soft x-ray ratio point.
Definition: sxrem_ratio_dot.f:206
sxrem_ratio_dot::sxrem_ratio_dot_read
subroutine sxrem_ratio_dot_read(sxrem_ratio_file, signals, signals_created, observed, sigma, weight, first_index)
Read an sxrem ratio dot file.
Definition: sxrem_ratio_dot.f:105
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
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