V3FIT
All Classes Namespaces Files Functions Variables Enumerations Macros Pages
v3rfun_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
6 ! an escaped comma '\,'.
7 !
91 !-------------------------------------------------------------------------------
92 !*******************************************************************************
95 !
96 ! Note separating the Doxygen comment block here so detailed decription is
97 ! found in the Module not the file.
98 !
111 !*******************************************************************************
113  USE stel_kinds
114  USE vsvd0, ONLY: nigroup
115  USE profiler
116 
117  IMPLICIT NONE
118 
119 !*******************************************************************************
120 ! v3rfun input module parameters
121 !*******************************************************************************
123  INTEGER, PARAMETER :: v3rfun_file_length = 120
125  INTEGER, PARAMETER :: v3rfun_name_length = 25
126 
127 !*******************************************************************************
128 ! DERIVED-TYPE DECLARATIONS
129 ! 1) v3rfun_namelist_class
130 !
131 !*******************************************************************************
133  CHARACTER (len=v3rfun_file_length) :: name_coils_dot = ''
135  CHARACTER (len=v3rfun_file_length) :: name_diagnostic_dot = ''
136 
138  CHARACTER (len=v3rfun_name_length) :: idrfun = ''
139 
141  LOGICAL :: lstell_sym = .false.
143  LOGICAL :: l_read_coils_dot = .true.
145  LOGICAL :: use_con_shell = .false.
146 
148  INTEGER :: ir = 101
150  INTEGER :: jz = 101
152  INTEGER :: kp = 1
154  INTEGER :: kp_shell = 1
156  INTEGER :: n_field_periods_nli = 0
157 
159  REAL (rprec) :: rmin = 0.0
161  REAL (rprec) :: rmax = 0.0
163  REAL (rprec) :: zmin = 0.0
165  REAL (rprec) :: zmax = 0.0
166 
168  REAL (rprec) :: major_radius = 0.0
170  REAL (rprec) :: minor_radius = 0.0
171 
173  REAL (rprec) :: len_integrate_ddc = 0.001
174 
176  LOGICAL, DIMENSION(nigroup) :: is_super_con = .false.
177 
179  REAL (rprec), DIMENSION(nigroup,3) :: cg_shift_1 = 0.0
181  REAL (rprec), DIMENSION(nigroup,3) :: cg_shift_2 = 0.0
183  REAL (rprec), DIMENSION(nigroup,3) :: cg_rot_xcent = 0.0
185  REAL (rprec), DIMENSION(nigroup) :: cg_rot_theta = 0.0
187  REAL (rprec), DIMENSION(nigroup) :: cg_rot_phi = 0.0
191  REAL (rprec), DIMENSION(nigroup) :: cg_rot_angle = 0.0
195  LOGICAL, DIMENSION(nigroup) :: l_rot_coil_center = .true.
196 
197 ! Declare Namelist
198  NAMELIST/v3r_coils/ &
199 ! Files
201 ! Control parameters
203 ! Super conductors
204  & is_super_con, &
205 ! Grid sizes
208 ! Coil tilt and shift
211 
212  CONTAINS
213 
214 !*******************************************************************************
215 ! UTILITY SUBROUTINES
216 !*******************************************************************************
217 !-------------------------------------------------------------------------------
224 !-------------------------------------------------------------------------------
225  SUBROUTINE v3rfun_input_read_namelist(namelist_file)
226  USE safe_open_mod
227  USE v3_utilities
228 
229  IMPLICIT NONE
230 
231 ! Declare Arguments
232  CHARACTER (len=*), INTENT(in) :: namelist_file
233 
234 ! local variables
235  INTEGER :: iou_mnli
236  INTEGER :: status
237  REAL (rprec) :: start_time
238 
239 ! Start of executable code
240  start_time = profiler_get_start_time()
241 
242 ! Initalize a default value of the I\O unit. V3FIT increments from there.
243  iou_mnli = 0
244  CALL safe_open(iou_mnli, status, trim(namelist_file), &
245  & 'old', 'formatted')
246  CALL assert_eq(0, status, 'v3rfun_input_read_namelist' // &
247  & ': Safe_open of ' // trim(namelist_file) // ' failed')
248 
249 ! Read the namelist input file.
250  READ (iou_mnli,nml=v3r_coils)
251  CLOSE (iou_mnli,iostat=status)
252  CALL assert_eq(0, status, 'v3rfun_input_read_namelist' // &
253  & ': Error closing ' // trim(namelist_file) // ' failed')
254 
255  IF (l_read_coils_dot .and. name_coils_dot .eq. '') THEN
256  WRITE(*,*) 'l_read_coils_dot is TRUE, but'
257  WRITE(*,*) 'name_coils_dot = blank. '
258  WRITE(*,*) 'Setting l_read_coils_dot to FALSE'
259  l_read_coils_dot = .false.
260  END IF
261 
262  WRITE (*,*) ' *** V3RFUN namelist input read from ' // &
263  & trim(namelist_file)
264 
265  CALL profiler_set_stop_time('v3rfun_input_read_namelist', &
266  & start_time)
267 
268  END SUBROUTINE
269 
270  END MODULE
v3rfun_input::name_coils_dot
character(len=v3rfun_file_length) name_coils_dot
Filename for the field coils.
Definition: v3rfun_input.f:133
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
v3rfun_input::major_radius
real(rprec) major_radius
Shell major radius for shell grid.
Definition: v3rfun_input.f:168
v3rfun_input::cg_rot_xcent
real(rprec), dimension(nigroup, 3) cg_rot_xcent
Position of center of rotation.
Definition: v3rfun_input.f:183
v3rfun_input::cg_shift_2
real(rprec), dimension(nigroup, 3) cg_shift_2
Vector to shift all the coils after rotation.
Definition: v3rfun_input.f:181
v3_utilities::assert_eq
Definition: v3_utilities.f:62
v3rfun_input::l_rot_coil_center
logical, dimension(nigroup) l_rot_coil_center
Controls the center of rotation.
Definition: v3rfun_input.f:195
v3rfun_input::kp
integer kp
Number of toroidal grid points.
Definition: v3rfun_input.f:152
v3rfun_input::zmin
real(rprec) zmin
Minimum Z for plasma grid.
Definition: v3rfun_input.f:163
v3rfun_input::use_con_shell
logical use_con_shell
Computes the response function for a conducting shell.
Definition: v3rfun_input.f:145
v3rfun_input::name_diagnostic_dot
character(len=v3rfun_file_length) name_diagnostic_dot
Filename for the diagnostic coils.
Definition: v3rfun_input.f:135
v3rfun_input
This file contains all the variables and maximum sizes of the inputs for a V3RFUN namelist input file...
Definition: v3rfun_input.f:112
v3rfun_input::jz
integer jz
Number of vertical grid points.
Definition: v3rfun_input.f:150
v3rfun_input::minor_radius
real(rprec) minor_radius
Shell minor radius for shell grid.
Definition: v3rfun_input.f:170
v3rfun_input::is_super_con
logical, dimension(nigroup) is_super_con
Tag super conducting coils.
Definition: v3rfun_input.f:176
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
v3rfun_input::v3rfun_input_read_namelist
subroutine v3rfun_input_read_namelist(namelist_file)
Reads the namelist input file.
Definition: v3rfun_input.f:226
v3rfun_input::rmax
real(rprec) rmax
Maximum R for plasma grid.
Definition: v3rfun_input.f:161
v3rfun_input::cg_rot_angle
real(rprec), dimension(nigroup) cg_rot_angle
Angle to rotate about axis of rotation. Left hand convention. Put left thumb along axis of rotation,...
Definition: v3rfun_input.f:191
v3rfun_input::len_integrate_ddc
real(rprec) len_integrate_ddc
Integration length in meters.
Definition: v3rfun_input.f:173
v3rfun_input::v3rfun_file_length
integer, parameter v3rfun_file_length
Filename length.
Definition: v3rfun_input.f:123
v3rfun_input::zmax
real(rprec) zmax
Maximum Z for plasma grid.
Definition: v3rfun_input.f:165
v3rfun_input::n_field_periods_nli
integer n_field_periods_nli
Number of field periods.
Definition: v3rfun_input.f:156
v3rfun_input::ir
integer ir
Number of radial grid points.
Definition: v3rfun_input.f:148
v3rfun_input::cg_rot_theta
real(rprec), dimension(nigroup) cg_rot_theta
Spherical polar angle to specify axis of rotation.
Definition: v3rfun_input.f:185
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
v3rfun_input::cg_rot_phi
real(rprec), dimension(nigroup) cg_rot_phi
Spherical azimuthal angle to specify axis of rotation.
Definition: v3rfun_input.f:187
v3rfun_input::lstell_sym
logical lstell_sym
Control for stellarator symmetry.
Definition: v3rfun_input.f:141
v3rfun_input::kp_shell
integer kp_shell
Number of shell toroidal grid points.
Definition: v3rfun_input.f:154
v3rfun_input::idrfun
character(len=v3rfun_name_length) idrfun
v3rfun identification for the run.
Definition: v3rfun_input.f:138
v3rfun_input::cg_shift_1
real(rprec), dimension(nigroup, 3) cg_shift_1
Vector to shift all the coils before rotation.
Definition: v3rfun_input.f:179
v3rfun_input::rmin
real(rprec) rmin
Minimum R for plasma grid.
Definition: v3rfun_input.f:159
v3rfun_input::l_read_coils_dot
logical l_read_coils_dot
Control to ignore the coils dot file.
Definition: v3rfun_input.f:143
v3rfun_input::v3rfun_name_length
integer, parameter v3rfun_name_length
Name length.
Definition: v3rfun_input.f:125