V3FIT
signal_dot.f
Go to the documentation of this file.
1 !*******************************************************************************
4 !
5 ! Note separating the Doxygen comment block here so detailed decription is
6 ! found in the Module not the file.
7 !
12 !*******************************************************************************
13 
14  MODULE signal_dot
15  USE stel_kinds
16  USE stel_constants
17  USE data_parameters
18  USE profiler
19 
20  IMPLICIT NONE
21 
22 !*******************************************************************************
23 ! signal_dot module parameters
24 !*******************************************************************************
26  INTEGER, PARAMETER :: signal_dot_line_len = 200
27 
28 !*******************************************************************************
29 ! DERIVED-TYPE DECLARATIONS
30 ! 1) signal_dot_file base class
31 !
32 !*******************************************************************************
33 !-------------------------------------------------------------------------------
35 !-------------------------------------------------------------------------------
37  PRIVATE
39  INTEGER :: iou
41  INTEGER :: i_line
43  CHARACTER (len=6) :: signal_id
44  END TYPE
45 
46 !*******************************************************************************
47 ! INTERFACE BLOCKS
48 !*******************************************************************************
49  PUBLIC :: signal_dot_open, signal_dot_close, &
52  PRIVATE :: signal_dot_check_status
53 
54  CONTAINS
55 !*******************************************************************************
56 ! UTILITY SUBROUTINES
57 !*******************************************************************************
58 !-------------------------------------------------------------------------------
66 !-------------------------------------------------------------------------------
67  FUNCTION signal_dot_open(file, signal_id)
68  USE safe_open_mod
69 
70  IMPLICIT NONE
71 
72 ! Declare Arguments
74  CHARACTER (len=*), INTENT(in) :: file
75  CHARACTER (len=*), INTENT(in) :: signal_id
76 
77 ! local variables
78  INTEGER :: status
79  REAL (rprec) :: start_time
80 
81 ! local parameters
82  INTEGER, PARAMETER :: iou_0 = 32
83 
84 ! Start of executable code
85  start_time = profiler_get_start_time()
86 
87 ! Open up the file
88  signal_dot_open%iou = iou_0
89  signal_dot_open%signal_id = signal_id
90  CALL safe_open(signal_dot_open%iou, status, file, 'old', &
91  & 'formatted')
93  & 'Error opening ', ' file.')
94 
95  CALL profiler_set_stop_time('signal_dot_open', start_time)
96 
97  END FUNCTION
98 
99 !-------------------------------------------------------------------------------
105 !-------------------------------------------------------------------------------
106  SUBROUTINE signal_dot_close(signal_dot_file_ref)
107 
108  IMPLICIT NONE
109 
110 ! Declare Arguments
111  TYPE(signal_dot_file), INTENT(in) :: signal_dot_file_ref
112 
113 ! local variables
114  REAL (rprec) :: start_time
115 
116 ! Start of executable code
117  start_time = profiler_get_start_time()
118 
119 ! Close the file
120  CLOSE(signal_dot_file_ref%iou)
121 
122  CALL profiler_set_stop_time('signal_dot_close', start_time)
123 
124  END SUBROUTINE
125 
126 !-------------------------------------------------------------------------------
142 !-------------------------------------------------------------------------------
143  SUBROUTINE signal_dot_parse_chord(signal_dot_file_ref, &
144  & coordinate_type, &
145  & chord_name, &
146  & xcart_i, xcart_f)
148 
149  IMPLICIT NONE
150 
151 ! Declare Arguments
152  TYPE(signal_dot_file), INTENT(inout) :: signal_dot_file_ref
153  CHARACTER (len=*), INTENT(in) :: coordinate_type
154  CHARACTER (len=data_short_name_length), INTENT(out) :: chord_name
155  REAL(rprec), DIMENSION(3), INTENT(out) :: xcart_i
156  REAL(rprec), DIMENSION(3), OPTIONAL, INTENT(out) :: xcart_f
157 
158 ! local variables
159  INTEGER :: status
160  CHARACTER (len=signal_dot_line_len) :: line
161  REAL (rprec) :: start_time
162 
163 ! Start of executable code
164  start_time = profiler_get_start_time()
165 
166 ! Read the chord identification.
167  line = signal_dot_read_line(signal_dot_file_ref, &
168  & 'Error reading ID for ', ' chord.')
169  chord_name = trim(line)
170 
171 ! Read the start position.
172  xcart_i = signal_dot_parse_3_real(signal_dot_file_ref, &
173  & 'Error reading start ' // &
174  & 'position for chord.')
175 
176  IF (PRESENT(xcart_f)) THEN
177 ! Read the end position.
178  xcart_f = signal_dot_parse_3_real(signal_dot_file_ref, &
179  & 'Error reading end ' // &
180  & 'position for chord.')
181  END IF
182 
183 ! Done reading information for this chord. Generate the chord
184  IF (trim(coordinate_type) .eq. 'RPHiDegZ') THEN
185  xcart_i(2) = xcart_i(2)*degree ! Convert from degrees to radians.
186  xcart_i = cyl_to_cart(xcart_i)
187 
188  IF (PRESENT(xcart_f)) THEN
189  xcart_f(2) = xcart_f(2)*degree ! Convert from degrees to radians.
190  xcart_f = cyl_to_cart(xcart_f)
191  END IF
192  END IF
193 
194  CALL profiler_set_stop_time('signal_dot_parse_chord', start_time)
195 
196  END SUBROUTINE
197 
198 !-------------------------------------------------------------------------------
209 !-------------------------------------------------------------------------------
210  FUNCTION signal_dot_parse_real(signal_dot_file_ref, message)
211  IMPLICIT NONE
212 
213 ! Declare Arguments
214  REAL (rprec) :: signal_dot_parse_real
215  TYPE (signal_dot_file), INTENT(inout) :: signal_dot_file_ref
216  CHARACTER (len=*), INTENT(in) :: message
217 
218 ! local variables
219  INTEGER :: status
220  CHARACTER (len=signal_dot_line_len) :: line
221  REAL (rprec) :: start_time
222 
223 ! Start of executable code
224  start_time = profiler_get_start_time()
225 
226 ! Read the start position.
227  line = signal_dot_read_line(signal_dot_file_ref, &
228  & 'Error ', message)
229 ! Reread the line, looking for a single real
230  READ(line, *, iostat=status) signal_dot_parse_real
231  CALL signal_dot_check_status(status, signal_dot_file_ref, &
232  & 'Error ', message)
233 
234  CALL profiler_set_stop_time('signal_dot_parse_real', start_time)
235 
236  END FUNCTION
237 
238 !-------------------------------------------------------------------------------
249 !-------------------------------------------------------------------------------
250  FUNCTION signal_dot_parse_2_real(signal_dot_file_ref, message)
251 
252  IMPLICIT NONE
253 
254 ! Declare Arguments
255  REAL (rprec), DIMENSION(2) :: signal_dot_parse_2_real
256  TYPE (signal_dot_file), INTENT(inout) :: signal_dot_file_ref
257  CHARACTER (len=*), INTENT(in) :: message
258 
259 ! local variables
260  INTEGER :: status
261  CHARACTER (len=signal_dot_line_len) :: line
262  REAL (rprec) :: start_time
263 
264 ! Start of executable code
265  start_time = profiler_get_start_time()
266 
267 ! Read the start position.
268  line = signal_dot_read_line(signal_dot_file_ref, &
269  & 'Error ', message)
270 ! Reread the line, looking for three reals
271  READ(line, *, iostat=status) signal_dot_parse_2_real
272  CALL signal_dot_check_status(status, signal_dot_file_ref, &
273  & 'Error ', message)
274 
275  CALL profiler_set_stop_time('signal_dot_parse_2_real', start_time)
276 
277  END FUNCTION
278 
279 !-------------------------------------------------------------------------------
290 !-------------------------------------------------------------------------------
291  FUNCTION signal_dot_parse_3_real(signal_dot_file_ref, message)
292 
293  IMPLICIT NONE
294 
295 ! Declare Arguments
296  REAL (rprec), DIMENSION(3) :: signal_dot_parse_3_real
297  TYPE (signal_dot_file), INTENT(inout) :: signal_dot_file_ref
298  CHARACTER (len=*), INTENT(in) :: message
299 
300 ! local variables
301  INTEGER :: status
302  CHARACTER (len=signal_dot_line_len) :: line
303  REAL (rprec) :: start_time
304 
305 ! Start of executable code
306  start_time = profiler_get_start_time()
307 
308 ! Read the start position.
309  line = signal_dot_read_line(signal_dot_file_ref, &
310  & 'Error ', message)
311 ! Reread the line, looking for three reals
312  READ(line, *, iostat=status) signal_dot_parse_3_real
313  CALL signal_dot_check_status(status, signal_dot_file_ref, &
314  & 'Error ', message)
315 
316  CALL profiler_set_stop_time('signal_dot_parse_3_real', start_time)
317 
318  END FUNCTION
319 
320 !-------------------------------------------------------------------------------
331 !-------------------------------------------------------------------------------
332  FUNCTION signal_dot_parse_int(signal_dot_file_ref, message)
333  IMPLICIT NONE
334 
335 ! Declare Arguments
336  INTEGER :: signal_dot_parse_int
337  TYPE (signal_dot_file), INTENT(inout) :: signal_dot_file_ref
338  CHARACTER (len=*), INTENT(in) :: message
339 
340 ! local variables
341  INTEGER :: status
342  CHARACTER (len=signal_dot_line_len) :: line
343  REAL (rprec) :: start_time
344 
345 ! Start of executable code
346  start_time = profiler_get_start_time()
347 
348 ! Read the start position.
349  line = adjustl(signal_dot_read_line(signal_dot_file_ref, &
350  & 'Error ', message))
351 ! Reread the line, looking for a single real
352  READ(line, *, iostat=status) signal_dot_parse_int
353  CALL signal_dot_check_status(status, signal_dot_file_ref, &
354  & 'Error ', message)
355 
356  CALL profiler_set_stop_time('signal_dot_parse_int', start_time)
357 
358  END FUNCTION
359 
360 !-------------------------------------------------------------------------------
371 !-------------------------------------------------------------------------------
372  FUNCTION signal_dot_parse_2_int(signal_dot_file_ref, message)
373  IMPLICIT NONE
374 
375 ! Declare Arguments
376  INTEGER, DIMENSION(2) :: signal_dot_parse_2_int
377  TYPE (signal_dot_file), INTENT(inout) :: signal_dot_file_ref
378  CHARACTER (len=*), INTENT(in) :: message
379 
380 ! local variables
381  INTEGER :: status
382  CHARACTER (len=signal_dot_line_len) :: line
383  REAL (rprec) :: start_time
384 
385 ! Start of executable code
386  start_time = profiler_get_start_time()
387 
388 ! Read the start position.
389  line = signal_dot_read_line(signal_dot_file_ref, &
390  & 'Error ', message)
391 ! Reread the line, looking for a single real
392  READ(line, *, iostat=status) signal_dot_parse_2_int
393  CALL signal_dot_check_status(status, signal_dot_file_ref, &
394  & 'Error ', message)
395 
396  CALL profiler_set_stop_time('signal_dot_parse_2_int', start_time)
397 
398  END FUNCTION
399 
400 !-------------------------------------------------------------------------------
410 !-------------------------------------------------------------------------------
411  FUNCTION signal_dot_read_keyword(signal_dot_file_ref, keywords)
412 
413  IMPLICIT NONE
414 
415 ! Declare Arguments
416  CHARACTER (len=data_name_length) :: signal_dot_read_keyword
417  TYPE(signal_dot_file), INTENT(inout) :: signal_dot_file_ref
418  CHARACTER (len=*), DIMENSION(:), INTENT(in) :: keywords
419 
420 ! local variables
421  INTEGER :: i
422  CHARACTER (len=signal_dot_line_len) :: line
423  REAL (rprec) :: start_time
424 
425 ! Start of executable code
426  start_time = profiler_get_start_time()
427 
428 ! Contine looping until a vaild keyword is read. If the end of the file is
429 ! reached an error will kill the program.
430  DO
431  line = signal_dot_read_line(signal_dot_file_ref, &
432  & 'Failed to read ', &
433  & ' keyword before end of file.')
434  DO i = 1, SIZE(keywords)
435  IF (trim(adjustl(line)) .eq. trim(keywords(i))) THEN
436  signal_dot_read_keyword = keywords(i)
437 
438  CALL profiler_set_stop_time('signal_dot_read_keyword', &
439  & start_time)
440 
441  RETURN
442  END IF
443  END DO
444  END DO
445 
446  CALL profiler_set_stop_time('signal_dot_read_keyword', start_time)
447 
448  END FUNCTION
449 
450 !*******************************************************************************
451 ! Private Functions and Subroutines.
452 !*******************************************************************************
453 !-------------------------------------------------------------------------------
463 !-------------------------------------------------------------------------------
464  FUNCTION signal_dot_read_line(signal_dot_file_ref, &
465  & pre_message, &
466  & post_message)
467  IMPLICIT NONE
468 
469 ! Declare Arguments
470  CHARACTER (len=signal_dot_line_len) :: signal_dot_read_line
471  TYPE(signal_dot_file), INTENT(inout) :: signal_dot_file_ref
472  CHARACTER (len=*), INTENT(in) :: pre_message
473  CHARACTER (len=*), INTENT(in) :: post_message
474 
475 ! local variables
476  INTEGER :: status
477  REAL (rprec) :: start_time
478 
479 ! Start of executable code
480  start_time = profiler_get_start_time()
481 
482  READ (signal_dot_file_ref%iou, '(a)', iostat=status) &
484  signal_dot_file_ref%i_line = signal_dot_file_ref%i_line + 1
485  CALL signal_dot_check_status(status, signal_dot_file_ref, &
486  & pre_message, post_message)
487 
488  CALL profiler_set_stop_time('signal_dot_read_line', start_time)
489 
490  END FUNCTION
491 
492 !-------------------------------------------------------------------------------
507 !-------------------------------------------------------------------------------
508  SUBROUTINE signal_dot_check_status(status, &
509  & signal_dot_file_ref, &
510  & pre_message, &
511  & post_message)
512  IMPLICIT NONE
513 
514 ! Declare Arguments
515  INTEGER, INTENT(in) :: status
516  TYPE(signal_dot_file), INTENT(inout) :: signal_dot_file_ref
517  CHARACTER (len=*), INTENT(in) :: pre_message
518  CHARACTER (len=*), INTENT(in) :: post_message
519 
520 ! local variables
521  REAL (rprec) :: start_time
522 
523 ! Start of executable code
524  start_time = profiler_get_start_time()
525 
526  IF (status .ne. 0) THEN
527  WRITE(*,*) pre_message // trim(signal_dot_file_ref%signal_id) &
528  & // post_message // ' line ', &
529  & signal_dot_file_ref%i_line
530  stop
531  END IF
532 
533  CALL profiler_set_stop_time('signal_dot_check_status', start_time)
534 
535  END SUBROUTINE
536 
537  END MODULE
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
coordinate_utilities
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
Definition: coordinate_utilities.f:12
signal_dot::signal_dot_parse_int
integer function signal_dot_parse_int(signal_dot_file_ref, message)
Parse a single integer from a diagnostic dot file.
Definition: signal_dot.f:333
signal_dot::signal_dot_file
Base class representing a diagnostic dot file. This is an opaqe class.
Definition: signal_dot.f:36
signal_dot::signal_dot_parse_3_real
real(rprec) function, dimension(3) signal_dot_parse_3_real(signal_dot_file_ref, message)
Parse a three reals from a diagnostic dot file.
Definition: signal_dot.f:292
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
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
signal_dot::signal_dot_check_status
subroutine, private signal_dot_check_status(status, signal_dot_file_ref, pre_message, post_message)
Check and handle errors.
Definition: signal_dot.f:512
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
coordinate_utilities::cyl_to_cart
pure real(rprec) function, dimension(3), public cyl_to_cart(cyl)
Convert a point from cylindical coordinates to cartesian coordinates.
Definition: coordinate_utilities.f:67
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
signal_dot::signal_dot_line_len
integer, parameter signal_dot_line_len
Maximum line length.
Definition: signal_dot.f:26
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
profiler::profiler_set_stop_time
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Definition: profiler.f:121
signal_dot::signal_dot_read_line
character(len=signal_dot_line_len) function, public signal_dot_read_line(signal_dot_file_ref, pre_message, post_message)
Read line from diagnostic dot file.
Definition: signal_dot.f:467
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
signal_dot::signal_dot_close
subroutine, public signal_dot_close(signal_dot_file_ref)
Close a diagnostic dot file.
Definition: signal_dot.f:107
signal_dot::signal_dot_parse_2_real
real(rprec) function, dimension(2) signal_dot_parse_2_real(signal_dot_file_ref, message)
Parse a two reals from a diagnostic dot file.
Definition: signal_dot.f:251