V3FIT
vacuum_input.f
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! The @header, @table_section, @table_subsection, @item and @end_table commands
3 ! are custom defined commands in Doxygen.in. They are defined under ALIASES.
4 ! For the page created here, the 80 column limit is exceeded. Arguments of
5 ! aliases are separated by ','. If you intended ',' to be a string you must use an
6 ! escaped comma '\,'.
7 !
60 !-------------------------------------------------------------------------------
61 !*******************************************************************************
64 !
65 ! Note separating the Doxygen comment block here so detailed decription is
66 ! found in the Module not the file.
67 !
77 !*******************************************************************************
78  MODULE vacuum_input
79  USE stel_kinds
80  USE data_parameters
81  USE profiler
82 
83  IMPLICIT NONE
84 
85 !*******************************************************************************
86 ! v3fit input module parameters
87 !*******************************************************************************
89  INTEGER, PARAMETER :: vacuum_max_currents = 1000
90 
91 !*******************************************************************************
92 ! DERIVED-TYPE DECLARATIONS
93 ! 1) vacuum_namelist_class
94 !
95 !*******************************************************************************
97  CHARACTER (len=path_length) :: coils_dot_file = ''
98 
100  INTEGER :: n_extcur = 0
102  REAL (rprec), DIMENSION(vacuum_max_currents) :: extcur = 0.0
103 
104 ! Variables for shifts and rotations of coil_groups of coils_dot file
106  REAL (rprec), DIMENSION(vacuum_max_currents,3) :: &
107  & cg_shift_1 = 0.0
108 
109  REAL (rprec), DIMENSION(vacuum_max_currents) :: &
110  & cg_rot_theta = 0.0
111 
112  REAL (rprec), DIMENSION(vacuum_max_currents) :: &
113  & cg_rot_phi = 0.0
114 
117  REAL (rprec), DIMENSION(vacuum_max_currents) :: &
118  & cg_rot_angle = 0.0
119 
120  REAL (rprec), DIMENSION(vacuum_max_currents,3) :: &
121  & cg_rot_xcent = 0.0
122 
124  LOGICAL, DIMENSION(vacuum_max_currents) :: &
125  & l_rot_coil_center = .false.
126 
127  REAL (rprec), DIMENSION(vacuum_max_currents,3) :: &
128  & cg_shift_2 = 0.0
129 
130 ! Declare Namelist
131  NAMELIST/vacuum_main_nli/ &
132  & coils_dot_file, &
133 ! External currents
134  & n_extcur, extcur, &
135 ! Variables for shifts and rotations of coil_groups of coils_dot file
138 
139  CONTAINS
140 
141 !*******************************************************************************
142 ! UTILITY SUBROUTINES
143 !*******************************************************************************
144 !-------------------------------------------------------------------------------
150 !-------------------------------------------------------------------------------
151  SUBROUTINE vacuum_input_read_namelist(namelist_file)
152  USE safe_open_mod
153  USE v3_utilities
154 
155  IMPLICIT NONE
156 
157 ! Declare Arguments
158  CHARACTER (len=*), INTENT(in) :: namelist_file
159 
160 ! local variables
161  INTEGER :: iou_vacnli, status
162  REAL (rprec) :: start_time
163 
164 ! Start of executable code
165  start_time = profiler_get_start_time()
166 
167  iou_vacnli = 0
168  status = 0
169 
170  CALL safe_open(iou_vacnli, status, trim(namelist_file), &
171  & 'old', 'formatted')
172  CALL assert_eq(0, status, 'vacuum_input_read_namelist' // &
173  & ': Safe_open of ' // trim(namelist_file) // ' failed')
174 
175 ! Read the namelist input file.
176  READ (iou_vacnli, nml=vacuum_main_nli)
177  CLOSE (iou_vacnli, iostat=status)
178  CALL assert_eq(0, status, 'vacuum_input_read_namelist' // &
179  & ': Error closing ' // trim(namelist_file) // ' failed')
180 
181  CALL profiler_set_stop_time('vacuum_input_read_namelist', &
182  & start_time)
183 
184  END SUBROUTINE
185 
186 !-------------------------------------------------------------------------------
192 !-------------------------------------------------------------------------------
193  SUBROUTINE vacuum_input_write_namelist(namelist_file)
194  USE safe_open_mod
195  USE v3_utilities
196 
197  IMPLICIT NONE
198 
199 ! Declare Arguments
200  CHARACTER (len=*), INTENT(in) :: namelist_file
201 
202 ! local variables
203  INTEGER :: iou_vacnli, status
204  REAL (rprec) :: start_time
205 
206 ! Start of executable code
207  start_time = profiler_get_start_time()
208 
209  iou_vacnli = 0
210  status = 0
211 
212  CALL safe_open(iou_vacnli, status, trim(namelist_file), &
213  & 'old', 'formatted')
214  CALL assert_eq(0, status, 'vacuum_input_write_namelist' // &
215  & ': Safe_open of ' // trim(namelist_file) // ' failed')
216 
217 ! Read the namelist input file.
218  WRITE (iou_vacnli, nml=vacuum_main_nli)
219  CLOSE (iou_vacnli, iostat=status)
220  CALL assert_eq(0, status, 'vacuum_input_write_namelist' // &
221  & ': Error closing ' // trim(namelist_file) // ' failed')
222 
223  CALL profiler_set_stop_time('vacuum_input_write_namelist', &
224  & start_time)
225 
226  END SUBROUTINE
227 
228  END MODULE
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
v3_utilities::assert_eq
Definition: v3_utilities.f:62
vacuum_input::cg_rot_angle
real(rprec), dimension(vacuum_max_currents) cg_rot_angle
Angle to rotate about axis of rotation. NB - LEFT HAND convention. Put left thumb along axis of rotat...
Definition: vacuum_input.f:117
vacuum_input::cg_shift_1
real(rprec), dimension(vacuum_max_currents, 3) cg_shift_1
Vector to shift all the coils. (Before rotation)
Definition: vacuum_input.f:106
vacuum_input::cg_rot_theta
real(rprec), dimension(vacuum_max_currents) cg_rot_theta
Spherical polar angle to specify axis of rotation.
Definition: vacuum_input.f:109
vacuum_input::extcur
real(rprec), dimension(vacuum_max_currents) extcur
External currents.
Definition: vacuum_input.f:102
vacuum_input::cg_shift_2
real(rprec), dimension(vacuum_max_currents, 3) cg_shift_2
Vector to shift all the coils. (After rotation)
Definition: vacuum_input.f:127
vacuum_input::coils_dot_file
character(len=path_length) coils_dot_file
File name for vacuum namelist input.
Definition: vacuum_input.f:97
vacuum_input::cg_rot_xcent
real(rprec), dimension(vacuum_max_currents, 3) cg_rot_xcent
Position of center of rotation.
Definition: vacuum_input.f:120
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
vacuum_input::l_rot_coil_center
logical, dimension(vacuum_max_currents) l_rot_coil_center
Definition: vacuum_input.f:124
vacuum_input::cg_rot_phi
real(rprec), dimension(vacuum_max_currents) cg_rot_phi
Spherical azimuthal angle to specify axis of rotation.
Definition: vacuum_input.f:112
vacuum_input::vacuum_input_write_namelist
subroutine vacuum_input_write_namelist(namelist_file)
Writes the namelist input file.
Definition: vacuum_input.f:194
vacuum_input
This file contains all the variables and maximum sizes of the inputs for a vacuum namelist input file...
Definition: vacuum_input.f:78
vacuum_input::vacuum_input_read_namelist
subroutine vacuum_input_read_namelist(namelist_file)
Reads the namelist input file.
Definition: vacuum_input.f:152
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
vacuum_input::vacuum_max_currents
integer, parameter vacuum_max_currents
Maximum number of diagnostic signals.
Definition: vacuum_input.f:89
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
vacuum_input::n_extcur
integer n_extcur
Number of external currents.
Definition: vacuum_input.f:100