V3FIT
siesta_namelist.f90
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 !
85 !-------------------------------------------------------------------------------
86 !*******************************************************************************
89 !
90 ! Note separating the Doxygen comment block here so detailed decription is
91 ! found in the Module not the file.
92 !
102 !*******************************************************************************
104  USE shared_data, ONLY: ngmres_type, iortho, lcolscale, lasym, &
106  USE hessian, ONLY: levmarq_param, mupar
107  USE stel_kinds
108 
109  IMPLICIT NONE
110 
111 !*******************************************************************************
112 ! siesta_namelist input module parameters
113 !*******************************************************************************
115  INTEGER, PARAMETER :: siesta_namelist_name_length = 256
116 
117 !*******************************************************************************
118 ! DERIVED-TYPE DECLARATIONS
119 ! 1) siesta_namelist_class
120 !
121 !*******************************************************************************
122 ! Control Flags
124  LOGICAL :: ladd_pert = .true.
126  LOGICAL :: lresistive = .true.
128  LOGICAL :: lrestart = .false.
130  LOGICAL :: l_tracing = .false.
132  LOGICAL :: l_silo_output = .false.
134  LOGICAL :: l_silo3d = .false.
136  LOGICAL :: l_output_alliter = .false.
138  LOGICAL :: l_vmec_uniform
140  LOGICAL :: l_vessel = .false.
141 
142 ! Algrothim Control Variables}
144  INTEGER :: niter = 10
146  REAL(dp) :: ftol = 1.e-20_dp
148  REAL(dp) :: eta_factor = 1.e-2_dp
150  INTEGER :: nprecon = 0
151 
152 ! Island parameters
154  INTEGER, DIMENSION(20) :: mres = 0
156  REAL(dp), DIMENSION(20) :: helpert = 0.0
158  REAL(dp), DIMENSION(20) :: helperta = 0.0
159 
160 ! Grid Sizes
162  INTEGER :: nsin = 101
164  INTEGER :: nsin_ext = 0
166  INTEGER :: mpolin = 12
168  INTEGER :: ntorin = 3
171  INTEGER :: nfpin = 0
172 
173 ! Output Grid Sizes
175  INTEGER :: nphis = 2
177  INTEGER :: nrs = 200
179  INTEGER :: nzs = 200
181  INTEGER :: nvs = 150
183  INTEGER :: nus = 150
185  INTEGER :: nss = 100
186 
187 ! File Names
189  CHARACTER(LEN=siesta_namelist_name_length) :: wout_file = ''
191  CHARACTER(LEN=siesta_namelist_name_length) :: restart_ext = ''
193  CHARACTER(LEN=siesta_namelist_name_length) :: mgrid_file = ''
195  CHARACTER(LEN=siesta_namelist_name_length) :: vessel_file = ''
196 
197 ! Declare Namelist
198  NAMELIST/siesta_info/ &
199 ! Control flags
203 ! Algrothim Control Variables
204  niter, ftol, mupar, levmarq_param, eta_factor, nprecon, &
205  ngmres_type, iortho, &
206 ! Island parameters Island Parameters
207  mres, helpert, helperta, &
208 ! Input grid sizes
210 ! Output grid sizes
211  nphis, nrs, nzs, nvs, nus, nss, &
212 ! File names
214 ! Test controls
216 
217  CONTAINS
218 
219 !*******************************************************************************
220 ! UTILITY SUBROUTINES
221 !*******************************************************************************
222 !-------------------------------------------------------------------------------
228 !-------------------------------------------------------------------------------
229  SUBROUTINE siesta_namelist_read(namelist_file)
230  USE safe_open_mod
231  USE v3_utilities
232  USE hessian, ONLY: levmarq_param, mupar, levmarq_param0, mupar0
233 
234  IMPLICIT NONE
235 
236 ! Declare Arguments
237  CHARACTER (len=*), INTENT(in) :: namelist_file
238 
239 ! local variables
240  INTEGER :: iou_mnli
241  INTEGER :: status
242 
243 ! Start of executable code
244  levmarq_param = 1.e-3_dp
245  mupar = 0
246  niter = 10
247  mres = 0
248  helpert = 0
249  helperta = 0
250  lcolscale = .true.
251  mupar_test = 0
252 
253 ! Initalize a default value of the I\O unit. SIESTA increments from there.
254  iou_mnli = 0
255  CALL safe_open(iou_mnli, status, trim(namelist_file), &
256  'old', 'formatted')
257  CALL assert_eq(0, status, 'siesta_namelist_read' // &
258  ': Safe_open of ' // trim(namelist_file) // ' failed')
259 
260 ! Read the namelist input file.
261  READ (iou_mnli, nml=siesta_info)
262  CLOSE (iou_mnli, iostat=status)
263  CALL assert_eq(0, status, 'siesta_namelist_read' // &
264  ': Error closing ' // trim(namelist_file) // ' failed')
265 
266  levmarq_param0 = levmarq_param
267  mupar0 = mupar
268 
269  END SUBROUTINE
270 
271 !-------------------------------------------------------------------------------
277 !-------------------------------------------------------------------------------
278  SUBROUTINE siesta_namelist_write(namelist_file)
279  USE safe_open_mod
280  USE v3_utilities
281 
282  IMPLICIT NONE
283 
284 ! Declare Arguments
285  CHARACTER (len=*), INTENT(in) :: namelist_file
286 
287 ! local variables
288  INTEGER :: iou_mnli
289  INTEGER :: status
290 
291 ! Start of executable code
292 
293 ! Initalize a default value of the I\O unit. SIESTA increments from there.
294  iou_mnli = 0
295  CALL safe_open(iou_mnli, status, trim(namelist_file), &
296  & 'replace', 'formatted', delim_in='quote')
297  CALL assert_eq(0, status, 'siesta_namelist_write' // &
298  & ': Safe_open of ' // trim(namelist_file) // ' failed')
299 
300 ! Write the namelist input file.
301  WRITE (iou_mnli, nml=siesta_info)
302  CLOSE (iou_mnli, iostat=status)
303  CALL assert_eq(0, status, 'siesta_namelist_read' // &
304  & ': Error closing ' // trim(namelist_file) // ' failed')
305 
306  END SUBROUTINE
307 
308  END MODULE
siesta_namelist::lrestart
logical lrestart
Restart SIESTA from pervious run.
Definition: siesta_namelist.f90:128
siesta_namelist::mres
integer, dimension(20) mres
Sizes of the helical perturbation.
Definition: siesta_namelist.f90:154
siesta_namelist::mpolin
integer mpolin
Number of poloidal modes.
Definition: siesta_namelist.f90:166
shared_data::iortho
integer iortho
Orthogonalization in GMRES.
Definition: shared_data.f90:81
siesta_namelist::l_vessel
logical l_vessel
If extended grid is to be used using an available vessel file.
Definition: siesta_namelist.f90:140
siesta_namelist::helperta
real(dp), dimension(20) helperta
Sizes of the helical perturbation.
Definition: siesta_namelist.f90:158
siesta_namelist::nrs
integer nrs
Number of radial grid points.
Definition: siesta_namelist.f90:177
siesta_namelist::vessel_file
character(len=siesta_namelist_name_length) vessel_file
Name of the restart file extension.
Definition: siesta_namelist.f90:195
v3_utilities::assert_eq
Definition: v3_utilities.f:62
shared_data::ngmres_type
integer ngmres_type
GMRES control flag.
Definition: shared_data.f90:74
siesta_namelist::l_tracing
logical l_tracing
Produce output file for fieldline tracing.
Definition: siesta_namelist.f90:130
siesta_namelist::nzs
integer nzs
Number of vertical grid points.
Definition: siesta_namelist.f90:179
siesta_namelist::niter
integer niter
Maximum number of iterations after diagonal prec.
Definition: siesta_namelist.f90:144
siesta_namelist::nfpin
integer nfpin
Number of field periods to use. -1 means set this to the value in the wout file.
Definition: siesta_namelist.f90:171
siesta_namelist::ntorin
integer ntorin
Number of toroidal modes.
Definition: siesta_namelist.f90:168
siesta_namelist::mgrid_file
character(len=siesta_namelist_name_length) mgrid_file
Filename of the VMEC woutfile.
Definition: siesta_namelist.f90:193
shared_data::lrecon
logical lrecon
Output extra information to the restart file that will be used by V3FIT.
Definition: shared_data.f90:232
siesta_namelist::siesta_namelist_read
subroutine siesta_namelist_read(namelist_file)
Reads the namelist input file.
Definition: siesta_namelist.f90:230
siesta_namelist::restart_ext
character(len=siesta_namelist_name_length) restart_ext
Name of the restart file extension.
Definition: siesta_namelist.f90:191
siesta_namelist::nphis
integer nphis
Number of cylindrical phi planes.
Definition: siesta_namelist.f90:175
siesta_namelist::nvs
integer nvs
Number of flux space toroidal points.
Definition: siesta_namelist.f90:181
siesta_namelist::eta_factor
real(dp) eta_factor
Resistivity value.
Definition: siesta_namelist.f90:148
siesta_namelist::l_silo_output
logical l_silo_output
Produce silo output.
Definition: siesta_namelist.f90:132
siesta_namelist::nss
integer nss
Number of flux space radial points.
Definition: siesta_namelist.f90:185
siesta_namelist::wout_file
character(len=siesta_namelist_name_length) wout_file
Filename of the VMEC woutfile.
Definition: siesta_namelist.f90:189
shared_data::lcolscale
logical lcolscale
Apply column scaling to hessian.
Definition: shared_data.f90:228
siesta_namelist::siesta_namelist_write
subroutine siesta_namelist_write(namelist_file)
Writes the namelist input file.
Definition: siesta_namelist.f90:279
siesta_namelist::siesta_namelist_name_length
integer, parameter siesta_namelist_name_length
Input string length.
Definition: siesta_namelist.f90:115
siesta_namelist::nus
integer nus
Number of flux space poloidal points.
Definition: siesta_namelist.f90:183
shared_data::lasym
logical lasym
Use non-stellarator symmetry.
Definition: shared_data.f90:230
siesta_namelist::ftol
real(dp) ftol
Force tolarance.
Definition: siesta_namelist.f90:146
siesta_namelist::nsin
integer nsin
Radial size of the plasma grid.
Definition: siesta_namelist.f90:162
siesta_namelist::l_vmec_uniform
logical l_vmec_uniform
FIXME: Unknown.
Definition: siesta_namelist.f90:138
siesta_namelist::lresistive
logical lresistive
Use resistive perturbaton.
Definition: siesta_namelist.f90:126
siesta_namelist::helpert
real(dp), dimension(20) helpert
Sizes of the helical perturbation.
Definition: siesta_namelist.f90:156
siesta_namelist::l_silo3d
logical l_silo3d
Produce silo 3D output.
Definition: siesta_namelist.f90:134
siesta_namelist
This file contains all the variables and maximum sizes of the inputs for a SIESTA namelist input file...
Definition: siesta_namelist.f90:103
shared_data::mupar_test
real(dp) mupar_test
FIXME UNKNOWN.
Definition: shared_data.f90:89
shared_data
This file contains variables and parameters used by many modules in SIESTA.
Definition: shared_data.f90:10
siesta_namelist::nprecon
integer nprecon
Skip diagonal preconditioner if greater than zero.
Definition: siesta_namelist.f90:150
siesta_namelist::nsin_ext
integer nsin_ext
Radial size of the extended grid.
Definition: siesta_namelist.f90:164
shared_data::hesspass_test
integer hesspass_test
Dump block and data files for testing.
Definition: shared_data.f90:83
siesta_namelist::ladd_pert
logical ladd_pert
Use helical perturbation.
Definition: siesta_namelist.f90:124
siesta_namelist::l_output_alliter
logical l_output_alliter
Write output files on all iterations.
Definition: siesta_namelist.f90:136