V3FIT
shared_data.f90
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 !
9 !*******************************************************************************
10  MODULE shared_data
11  USE stel_kinds
12  USE stel_constants
13 
14  IMPLICIT NONE
15 
16 !*******************************************************************************
17 ! shared_data module parameters
18 !*******************************************************************************
19 ! Solver parameters
21  INTEGER, PARAMETER :: ngmres_steps = 100
23  INTEGER, PARAMETER :: prediag = 1
25  INTEGER, PARAMETER :: preblock = 2
27  REAL (dp), PARAMETER :: fsq_res = 1.e-16_dp
29  REAL (dp), PARAMETER :: levm_ped = 1.e-10_dp
31  REAL (dp), PARAMETER :: mu_ped = 1.e-8_dp
33  INTEGER, PARAMETER :: gmres_peak = 2
35  INTEGER, PARAMETER :: gmres_no_peak = 1
36 
37 ! IO Parameters
39  INTEGER, PARAMETER :: unit_out = 336
40 
41 ! Force calulation flags.
43  LOGICAL, PARAMETER :: l_pedge = .true.
47  LOGICAL, PARAMETER :: l_natural = .true.
48 
49 !*******************************************************************************
50 ! shared_data module variables
51 !*******************************************************************************
52 ! Size variables.
54  INTEGER :: neqs
58  INTEGER :: ndims
60  INTEGER :: niter
62  INTEGER :: mblk_size
64  INTEGER :: nsp
65 
66 ! Solver control variables.
68  INTEGER :: nprecon
70  INTEGER :: nprecon_type
74  INTEGER :: ngmres_type = gmres_peak
81  INTEGER :: iortho = 3
83  INTEGER :: hesspass_test = -1
85  INTEGER :: in_hess_nfunct
87  INTEGER :: out_hess_nfunct
89  REAL (dp) :: mupar_test
91  REAL (dp) :: fsq_total
93  REAL (dp) :: fsq_total1
94 
95 ! Solver work variables.
97  REAL(dp), DIMENSION(:), ALLOCATABLE :: xc
99  REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET :: gc
102  REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET :: gc_sup
104  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: buv_res
106  REAL(dp), DIMENSION(:), ALLOCATABLE :: xc0
108  REAL(dp), DIMENSION(:), ALLOCATABLE :: gc0
110  REAL(dp), DIMENSION(:,:,:,:), ALLOCATABLE :: col_scale
111 
113  REAL (dp) :: fsq_gmres
115  REAL (dp) :: fsq_lin
117  REAL (dp) :: etak_tol
119  REAL (dp) :: levm_scale = 1
121  REAL (dp) :: wtotal
123  REAL (dp) :: wtotal0
125  REAL (dp) :: delta_t
127  REAL (dp) :: fsqvs
129  REAL (dp) :: fsqvu
131  REAL (dp) :: fsqvv
133  REAL (dp) :: ste(4)
135  REAL (dp) :: bs0(12)
137  REAL (dp) :: bu0(12)
139  REAL (dp) :: bsbu_ratio_s
141  REAL (dp) :: jsju_ratio_s
143  REAL (dp) :: bsbu_ratio_a
145  REAL (dp) :: jsju_ratio_a
147  REAL (dp) :: scale_s
149  REAL (dp) :: scale_u
150 
151 ! Cordinate basis.
153  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: r1_i
155  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: z1_i
157  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: ru_i
159  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: zu_i
161  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: rv_i
163  REAL(dp), DIMENSION(:,:,:), ALLOCATABLE :: zv_i
164 
165 ! Shared quantities.
167  REAL (dp) :: jsupvdota
169  REAL (dp), DIMENSION(:), ALLOCATABLE :: torflux
171  REAL (dp), DIMENSION(:), ALLOCATABLE :: polflux
173  REAL (dp), DIMENSION(:,:,:), POINTER :: asubsmnsf
176  REAL (dp), DIMENSION(:,:,:), POINTER :: asubsmncf
178  REAL (dp), DIMENSION(:,:,:), POINTER :: asubumncf
181  REAL (dp), DIMENSION(:,:,:), POINTER :: asubumnsf
183  REAL (dp), DIMENSION(:,:,:), POINTER :: asubvmncf
186  REAL (dp), DIMENSION(:,:,:), POINTER :: asubvmnsf
188  REAL (dp), DIMENSION(:,:,:), POINTER :: fsupsmnsf
190  REAL (dp), DIMENSION(:,:,:), POINTER :: fsupsmncf
192  REAL (dp), DIMENSION(:,:,:), POINTER :: fsupumncf
194  REAL (dp), DIMENSION(:,:,:), POINTER :: fsupumnsf
196  REAL (dp), DIMENSION(:,:,:), POINTER :: fsupvmncf
198  REAL (dp), DIMENSION(:,:,:), POINTER :: fsupvmnsf
199 
200 ! Flags to control evolving origin and edge.
202  LOGICAL :: l_push_edge
204  LOGICAL :: l_push_s
206  LOGICAL :: l_push_u
208  LOGICAL :: l_push_v
210  LOGICAL :: l_linearize
212  LOGICAL :: l_conjgrad
214  LOGICAL :: l_getwmhd
216  LOGICAL :: l_getfsq
218  LOGICAL :: l_applyprecon
220  LOGICAL :: l_printoriginforces = .false.
222  LOGICAL :: l_init_state
224  LOGICAL :: l_update_state = .false.
226  LOGICAL :: l_par_state
228  LOGICAL :: lcolscale
230  LOGICAL :: lasym = .false.
232  LOGICAL :: lrecon = .false.
234  LOGICAL :: lverbose = .true.
236  LOGICAL :: lequi1 = .true.
237 
239  REAL (dp) :: siesta_curtor = 0.0
240 
241  END MODULE shared_data
shared_data::l_natural
logical, parameter l_natural
Natural boundry condition flag.
Definition: shared_data.f90:47
shared_data::etak_tol
real(dp) etak_tol
FIXME: UNKNOWN.
Definition: shared_data.f90:117
shared_data::nprecon
integer nprecon
Preconditioner flag.
Definition: shared_data.f90:68
shared_data::out_hess_nfunct
integer out_hess_nfunct
FIXME UNKNOWN.
Definition: shared_data.f90:87
shared_data::r1_i
real(dp), dimension(:,:,:), allocatable r1_i
R coordinates of the computational grid.
Definition: shared_data.f90:153
shared_data::l_push_edge
logical l_push_edge
Solve u,v components at s=1.
Definition: shared_data.f90:202
shared_data::lverbose
logical lverbose
Use verbose screen output.
Definition: shared_data.f90:234
shared_data::zv_i
real(dp), dimension(:,:,:), allocatable zv_i
dZ/dv coordinates of the computational grid.
Definition: shared_data.f90:163
shared_data::l_getfsq
logical l_getfsq
Compute |F|^2.
Definition: shared_data.f90:216
shared_data::xc
real(dp), dimension(:), allocatable xc
1D array of Fourier mode displacement components.
Definition: shared_data.f90:97
shared_data::l_par_state
logical l_par_state
Parallel allocated quantities? FIXME: check this.
Definition: shared_data.f90:226
shared_data::in_hess_nfunct
integer in_hess_nfunct
FIXME UNKNOWN.
Definition: shared_data.f90:85
shared_data::l_push_u
logical l_push_u
Solve for u component at origin.
Definition: shared_data.f90:206
shared_data::iortho
integer iortho
Orthogonalization in GMRES.
Definition: shared_data.f90:81
shared_data::l_pedge
logical, parameter l_pedge
Preserve s=1 as iso-pressure surface.
Definition: shared_data.f90:43
shared_data::scale_u
real(dp) scale_u
FIXME: UNKNOWN.
Definition: shared_data.f90:149
shared_data::gc_sup
real(dp), dimension(:), allocatable, target gc_sup
1D Array of Fourier mode MHD force components, FIXME Check if this is really needed.
Definition: shared_data.f90:102
shared_data::delta_t
real(dp) delta_t
Time step.
Definition: shared_data.f90:125
shared_data::fsq_total
real(dp) fsq_total
|F|^2 WITH column scaling.
Definition: shared_data.f90:91
shared_data::l_push_s
logical l_push_s
Solve for s component at origin.
Definition: shared_data.f90:204
shared_data::bsbu_ratio_s
real(dp) bsbu_ratio_s
FIXME: UNKNOWN.
Definition: shared_data.f90:139
shared_data::l_applyprecon
logical l_applyprecon
Apply preconditioner.
Definition: shared_data.f90:218
shared_data::bu0
real(dp), dimension(12) bu0
FIXME: UNKNOWN.
Definition: shared_data.f90:137
shared_data::ngmres_type
integer ngmres_type
GMRES control flag.
Definition: shared_data.f90:74
shared_data::siesta_curtor
real(dp) siesta_curtor
Total toroidal current.
Definition: shared_data.f90:239
shared_data::torflux
real(dp), dimension(:), allocatable torflux
Toroidal flux profile.
Definition: shared_data.f90:169
shared_data::gmres_peak
integer, parameter gmres_peak
GMRES peak improvement.
Definition: shared_data.f90:33
shared_data::asubvmnsf
real(dp), dimension(:,:,:), pointer asubvmnsf
Covariant vector potential for non-stellator symmetric v component on full grid.
Definition: shared_data.f90:186
shared_data::asubumncf
real(dp), dimension(:,:,:), pointer asubumncf
Covariant vector potential for stellator symmetric u component on full grid.
Definition: shared_data.f90:178
shared_data::preblock
integer, parameter preblock
Block preconditioning flag.
Definition: shared_data.f90:25
shared_data::l_init_state
logical l_init_state
Store initial field/pressure state.
Definition: shared_data.f90:222
shared_data::fsupumncf
real(dp), dimension(:,:,:), pointer fsupumncf
Contravariant force for stellarator symmetric u component on full grid.
Definition: shared_data.f90:192
shared_data::fsq_gmres
real(dp) fsq_gmres
|F|^2 for GMRES iterations.
Definition: shared_data.f90:113
shared_data::scale_s
real(dp) scale_s
FIXME: UNKNOWN.
Definition: shared_data.f90:147
shared_data::l_printoriginforces
logical l_printoriginforces
Print forces at the origin.
Definition: shared_data.f90:220
shared_data::fsupsmnsf
real(dp), dimension(:,:,:), pointer fsupsmnsf
Contravariant force for stellarator symmetric s component on full grid.
Definition: shared_data.f90:188
shared_data::fsqvv
real(dp) fsqvv
|F|^2 for v components.
Definition: shared_data.f90:131
shared_data::jsupvdota
real(dp) jsupvdota
FIXME: UNKNOWN.
Definition: shared_data.f90:167
shared_data::lrecon
logical lrecon
Output extra information to the restart file that will be used by V3FIT.
Definition: shared_data.f90:232
shared_data::asubsmncf
real(dp), dimension(:,:,:), pointer asubsmncf
Covariant vector potential for non-stellator symmetric s component on full grid.
Definition: shared_data.f90:176
shared_data::lequi1
logical lequi1
Equilibrate matrix with col 1-norm.
Definition: shared_data.f90:236
shared_data::buv_res
real(dp), dimension(:,:,:), allocatable buv_res
Resonant magnetic field perturbation.
Definition: shared_data.f90:104
shared_data::levm_ped
real(dp), parameter levm_ped
FIXME: UNKNOWN.
Definition: shared_data.f90:29
shared_data::col_scale
real(dp), dimension(:,:,:,:), allocatable col_scale
Column scaling factors.
Definition: shared_data.f90:110
shared_data::asubsmnsf
real(dp), dimension(:,:,:), pointer asubsmnsf
Covariant vector potential for stellator symmetric s component on full grid.
Definition: shared_data.f90:173
shared_data::niter
integer niter
Total number of iteration to run.
Definition: shared_data.f90:60
shared_data::wtotal
real(dp) wtotal
MHD energy sum of magnetic and thermal.
Definition: shared_data.f90:121
shared_data::mu_ped
real(dp), parameter mu_ped
Pedestal value of levenberg/mu. Should be between 10^-5 and 10^-10.
Definition: shared_data.f90:31
shared_data::jsju_ratio_s
real(dp) jsju_ratio_s
FIXME: UNKNOWN.
Definition: shared_data.f90:141
shared_data::lcolscale
logical lcolscale
Apply column scaling to hessian.
Definition: shared_data.f90:228
shared_data::fsupumnsf
real(dp), dimension(:,:,:), pointer fsupumnsf
Contravariant force for stellarator non-symmetric u component on full grid.
Definition: shared_data.f90:194
shared_data::gmres_no_peak
integer, parameter gmres_no_peak
GMRES no_peak improvement.
Definition: shared_data.f90:35
shared_data::l_linearize
logical l_linearize
Use linearized forces.
Definition: shared_data.f90:210
shared_data::zu_i
real(dp), dimension(:,:,:), allocatable zu_i
dZ/du coordinates of the computational grid.
Definition: shared_data.f90:159
shared_data::polflux
real(dp), dimension(:), allocatable polflux
Poloidal flux profile.
Definition: shared_data.f90:171
shared_data::fsupsmncf
real(dp), dimension(:,:,:), pointer fsupsmncf
Contravariant force for stellarator non-symmetric s component on full grid.
Definition: shared_data.f90:190
shared_data::unit_out
integer, parameter unit_out
File output io unit.
Definition: shared_data.f90:39
shared_data::lasym
logical lasym
Use non-stellarator symmetry.
Definition: shared_data.f90:230
shared_data::nprecon_type
integer nprecon_type
Preconditioner type.
Definition: shared_data.f90:70
shared_data::gc
real(dp), dimension(:), allocatable, target gc
1D Array of Fourier mode MHD force components
Definition: shared_data.f90:99
shared_data::l_update_state
logical l_update_state
Update the ste array.
Definition: shared_data.f90:224
shared_data::asubvmncf
real(dp), dimension(:,:,:), pointer asubvmncf
Covariant vector potential for stellator symmetric v component on full grid.
Definition: shared_data.f90:183
shared_data::rv_i
real(dp), dimension(:,:,:), allocatable rv_i
dR/dv coordinates of the computational grid.
Definition: shared_data.f90:161
shared_data::fsq_res
real(dp), parameter fsq_res
Threshold force for turning off resistive perturbations.
Definition: shared_data.f90:27
shared_data::ste
real(dp), dimension(4) ste
Spectral Truncation RMS error,.
Definition: shared_data.f90:133
shared_data::nsp
integer nsp
Total radial grid size in the VMEC region.
Definition: shared_data.f90:64
shared_data::fsqvu
real(dp) fsqvu
|F|^2 for u components.
Definition: shared_data.f90:129
shared_data::xc0
real(dp), dimension(:), allocatable xc0
Saved fouier displacements.
Definition: shared_data.f90:106
shared_data::bs0
real(dp), dimension(12) bs0
FIXME: UNKNOWN.
Definition: shared_data.f90:135
shared_data::bsbu_ratio_a
real(dp) bsbu_ratio_a
FIXME: UNKNOWN.
Definition: shared_data.f90:143
shared_data::l_getwmhd
logical l_getwmhd
Compute MHD energy.
Definition: shared_data.f90:214
shared_data::fsq_total1
real(dp) fsq_total1
|F|^2 WITHOUT column scaling.
Definition: shared_data.f90:93
shared_data::ndims
integer ndims
Number of independent variables.
Definition: shared_data.f90:58
shared_data::fsupvmncf
real(dp), dimension(:,:,:), pointer fsupvmncf
Contravariant force for stellarator symmetric v component on full grid.
Definition: shared_data.f90:196
shared_data::mblk_size
integer mblk_size
Block size. (mpol + 1)*(2*ntor + 1)*ndims.
Definition: shared_data.f90:62
shared_data::l_conjgrad
logical l_conjgrad
FIXME: UNKNOWN.
Definition: shared_data.f90:212
shared_data::prediag
integer, parameter prediag
Diagonal preconditioning flag.
Definition: shared_data.f90:23
shared_data::levm_scale
real(dp) levm_scale
FIXME: UNKNOWN.
Definition: shared_data.f90:119
shared_data::z1_i
real(dp), dimension(:,:,:), allocatable z1_i
Z coordinates of the computational grid.
Definition: shared_data.f90:155
shared_data::jsju_ratio_a
real(dp) jsju_ratio_a
FIXME: UNKNOWN.
Definition: shared_data.f90:145
shared_data::ru_i
real(dp), dimension(:,:,:), allocatable ru_i
dR/du coordinates of the computational grid.
Definition: shared_data.f90:157
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
shared_data::fsqvs
real(dp) fsqvs
|F|^2 for s components.
Definition: shared_data.f90:127
shared_data::asubumnsf
real(dp), dimension(:,:,:), pointer asubumnsf
Covariant vector potential for non-stellator symmetric u component on full grid.
Definition: shared_data.f90:181
shared_data::hesspass_test
integer hesspass_test
Dump block and data files for testing.
Definition: shared_data.f90:83
shared_data::fsupvmnsf
real(dp), dimension(:,:,:), pointer fsupvmnsf
Contravariant force for stellarator non-symmetric v component on full grid.
Definition: shared_data.f90:198
shared_data::wtotal0
real(dp) wtotal0
Saved MHD energy sum of magnetic and thermal.
Definition: shared_data.f90:123
shared_data::fsq_lin
real(dp) fsq_lin
Linear |F|^2.
Definition: shared_data.f90:115
shared_data::neqs
integer neqs
Number of elements in the xc array.
Definition: shared_data.f90:54
shared_data::gc0
real(dp), dimension(:), allocatable gc0
Saved fouier MHD forces.
Definition: shared_data.f90:108
shared_data::ngmres_steps
integer, parameter ngmres_steps
Max number of gmres steps (10-100) should scale with ns.
Definition: shared_data.f90:21
shared_data::l_push_v
logical l_push_v
Solve for v component at origin.
Definition: shared_data.f90:208