• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

gyrokinetics / gs2 / 1989146477

18 Aug 2025 10:42AM UTC coverage: 10.372% (+2.2%) from 8.184%
1989146477

push

gitlab-ci

David Dickinson
Merged in experimental/more_gs2_init_everywhere (pull request #1134)

4646 of 44794 relevant lines covered (10.37%)

124612.73 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

12.76
/src/fields.f90
1
!> FIXME : Add documentation
2
module fields
3
  use abstract_config, only: abstract_config_type, CONFIG_MAX_NAME_LEN
4
  use text_options, only: text_option
5

6
  implicit none
7

8
  private 
9

10
  public :: init_fields, finish_fields
11
  public :: read_parameters, wnml_fields, check_fields
12
  public :: advance, force_maxwell_reinit, set_init_fields
13
  public :: fields_init_response, set_dump_and_read_response, set_overrides
14
  public :: dump_response_to_file, init_fields_parameters, finish_fields_parameters
15
  public :: init_fields_level_1, init_fields_level_2
16
  public :: finish_fields_level_1, finish_fields_level_2
17
  public :: fieldopt_switch, fieldopt_implicit, fieldopt_test, fieldopt_local, fieldopt_gf_local
18

19
  !> Made public for unit tests
20
  public :: fields_pre_init
21
  public :: remove_zonal_flows_switch
22

23
  public :: fields_config_type
24
  public :: set_fields_config
25
  public :: get_fields_config
26
  
27
  ! knobs
28
  integer :: fieldopt_switch
29
  logical :: remove_zonal_flows_switch
30
  logical :: force_maxwell_reinit
31
  integer, parameter :: fieldopt_implicit = 1, fieldopt_test = 2, fieldopt_local = 3, fieldopt_gf_local = 4
32
  logical :: dump_response, read_response
33
  logical :: initialized = .false.
34
  logical :: parameters_read = .false.
35

36
  !EGH made fieldopts module level for overrides
37
  type (text_option), dimension (6), parameter :: fieldopts = &
38
       [ text_option('default', fieldopt_implicit), &
39
          text_option('implicit', fieldopt_implicit), &
40
          text_option('test', fieldopt_test),&
41
          text_option('local', fieldopt_local),&
42
          text_option('gf_local', fieldopt_gf_local),&
43
          text_option('implicit_local', fieldopt_local)]
44
  
45
  !> Used to represent the input configuration of fields
46
  type, extends(abstract_config_type) :: fields_config_type
47
     ! namelist : fields_knobs
48
     ! indexed : false
49
     !> Used with `field_option='local'`. If `true` and x/y are
50
     !> distributed then in time advance only update local part of
51
     !> field in operations like `phinew=phinew+phi` etc.
52
     logical :: do_smart_update = .false.
53
     !> Writes files containing the field response matrix after
54
     !> initialisation. This currently works for
55
     !> `field_option='implicit'` or `'local'`.  We write to netcdf
56
     !> files by default but fall back to fortran unformatted (binary)
57
     !> files (which are not really portable) in the absence of
58
     !> netcdf.
59
     logical :: dump_response = .false.
60
     !> Set to true to use an allreduce (on `mp_comm`) in field
61
     !> calculation (`field_option='local'` only) rather than a
62
     !> reduction on a sub-communicator followed by a global
63
     !> broadcast. Typically a little faster than default performance
64
     !> but may depend on MPI implementation.
65
     logical :: field_local_allreduce = .false.
66
     !> Set to `true`, along with [[field_local_allreduce]] and
67
     !> [[layouts_knobs:intspec_sub]] , to replace the allreduce used
68
     !> in the field calculation with an allreduce on a
69
     !> sub-communicator followed by a reduction on a "perpendicular"
70
     !> communicator.  Typically a bit faster than default and scales
71
     !> slightly more efficiently.  Note if this option is active only
72
     !> `proc0` has knowledge of the full field arrays. Other
73
     !> processors know the full field for any supercell (connected
74
     !> x-y domains) for which it has any of the xy indices local in
75
     !> the `g_lo` layout.
76
     logical :: field_local_allreduce_sub = .false.
77
     !> If `true` then use nonblocking collective operations in the
78
     !> [[fields_local]] field calculation. This may or may not
79
     !> improve performance.
80
     logical :: field_local_nonblocking_collectives = .false.
81
     !> Set to `true` when using `field_option='local'` to
82
     !> automatically tune and select the best performing minimum
83
     !> block size (in a single supercell) assigned to a single
84
     !> processor. This can improve performance, but is not guaranteed
85
     !> to.
86
     logical :: field_local_tuneminnrow = .false.
87
     !> The `field_option` variable controls which time-advance
88
     !> algorithm is used for the linear terms. Allowed values are:
89
     !>
90
     !> - 'implicit' Advance linear terms with Kotschenreuther's implicit algorithm.
91
     !> - 'default' Same as 'implicit'.
92
     !> - 'implicit_local' the same as 'local'.
93
     !> - 'local' Same implicit algorithm as 'implicit' but with
94
     !>   different data decomposition (typically much faster for flux
95
     !>   tube runs).
96
     !> - 'gf_local' Same as `'local'` but with `gf_lo` field
97
     !>   decomposition. To use this you also need to set
98
     !>   `gf_lo_integrate= .true.` in [[dist_fn_knobs]] and
99
     !>   `gf_local_fields = .true.` in [[layouts_knobs]].
100
     !> - 'test' Use for debugging.     
101
     character(len = 20) :: field_option = 'default'
102
     !> Set to true to use allgatherv to fetch parts of the field update
103
     !> vector calculated on other procs. When false uses a sum_allreduce
104
     !> instead. This doesn't rely on sub-communicators so should work for
105
     !> any layout and processor count.  Note: This only impacts
106
     !> `field_option='implicit'`
107
     logical :: field_subgath = .false.
108
     !> If `true` then recalculate the fields from the distribution
109
     !> function using [[get_init_field]] when restarting a
110
     !> simulation rather than using the values in the restart file.
111
     !>
112
     !> @todo Consider if this should this go into the reinit namelist.
113
     logical :: force_maxwell_reinit = .true. 
114
     !> Used with `field_option='local'` to set the minimum block size
115
     !> (in a single supercell) assigned to a single processor. Tuning
116
     !> this parameter changes the balance between work
117
     !> parallelisation and communication. As this value is lowered,
118
     !> more communication needs to be done, but more processors get
119
     !> assigned work. This may reduce the time spent in computation
120
     !> at the cost of time spent in communication. The optimal value
121
     !> is likely to depend upon the size of the problem and the
122
     !> number of processors being used. Furthermore it will affect
123
     !> intialisation and advance in different ways. Can be
124
     !> automatically tuned using [[fields_knobs:field_local_tuneminnrow]].
125
     integer :: minnrow = 16
126
     !> Reads files containing the field response matrix and uses to
127
     !> initialise GS2s response matrix rather than using the usual
128
     !> initialisation process.
129
     logical :: read_response = .false.
130
     !> Delete zonal flows at every timestep.
131
     logical :: remove_zonal_flows_switch = .false.
132
     !> Sets location in which to store/look for response dump files.
133
     !> We don't currently check that this location exists before
134
     !> attempting to use it, which could cause problems. The default
135
     !> is to save them in the working directory.
136
     character(len = 256) :: response_dir = ''
137
     !> Allows customisation of the base filename to be used for
138
     !> response files. If not set then we use `run_name` derived
139
     !> from the input file name.
140
     character(len = 256) :: response_file = ''
141
   contains
142
     procedure, public :: read => read_fields_config
143
     procedure, public :: write => write_fields_config
144
     procedure, public :: reset => reset_fields_config
145
     procedure, public :: broadcast => broadcast_fields_config
146
     procedure, public, nopass :: get_default_name => get_default_name_fields_config
147
     procedure, public, nopass :: get_default_requires_index => get_default_requires_index_fields_config
148
  end type fields_config_type
149
  
150
  type(fields_config_type) :: fields_config  
151
contains
152

153
  !> FIXME : Add documentation  
154
  subroutine check_fields(report_unit)
×
155
    use fields_local, only: do_smart_update, minNRow
156
    implicit none
157
    integer, intent(in) :: report_unit
158
    select case (fieldopt_switch)
×
159
    case (fieldopt_implicit)
160
       write (report_unit, fmt="('The field equations will be advanced in time implicitly.')")
×
161
       if(dump_response) write (report_unit, fmt="('The response matrix will be dumped to file.')")
×
162
       if(read_response) write (report_unit, fmt="('The response matrix will be read from file.')")
×
163
    case (fieldopt_test)
164
       write (report_unit, *) 
×
165
       write (report_unit, fmt="('################# WARNING #######################')")
×
166
       write (report_unit, fmt="('The field equations will only be tested.')")
×
167
       write (report_unit, fmt="('THIS IS PROBABLY AN ERROR.')") 
×
168
       write (report_unit, fmt="('################# WARNING #######################')")
×
169
       write (report_unit, *) 
×
170
    case (fieldopt_local)
171
       write (report_unit, fmt="('The field equations will be advanced in time implicitly with decomposition respecting g_lo layout.')")
×
172
       if(dump_response) write (report_unit, fmt="('The response matrix will be dumped to file.')")
×
173
       if(read_response) write (report_unit, fmt="('The response matrix will be read from file.')")
×
174
       write(report_unit, fmt="('Using a min block size of ',I0)") minNrow
×
175
       if(do_smart_update) write(report_unit, fmt="('Using optimised field update.')")
×
176
    case (fieldopt_gf_local)
177
       write (report_unit, fmt="('The field equations will be advanced in time implicitly with decomposition respecting gf_lo layout.')")
×
178
    end select
179
  end subroutine check_fields
×
180

181
  !> FIXME : Add documentation  
182
  subroutine wnml_fields(unit)
×
183
    implicit none
184
    integer, intent(in) :: unit
185
    call fields_config%write(unit)
×
186
  end subroutine wnml_fields
×
187

188
  !> FIXME : Add documentation
189
  subroutine set_overrides(opt_ov)
×
190
    use overrides, only: optimisations_overrides_type
191
    use file_utils, only: error_unit
192
    use text_options, only: get_option_value
193
    use fields_local, only: minnrow
194
    use fields_implicit, only: field_subgath
195
    use fields_local, only: do_smart_update
196
    use fields_local, only: field_local_allreduce
197
    use fields_local, only: field_local_allreduce_sub
198
    type(optimisations_overrides_type), intent(in) :: opt_ov
199
    integer :: ierr
200
    if (.not. opt_ov%is_initialised()) return
×
201
    if (opt_ov%override_field_option) then
×
202
       ierr = error_unit()
×
203
       call get_option_value &
204
            (opt_ov%field_option, fieldopts, fieldopt_switch, &
205
            ierr, "field_option in set_overrides",.true.)
×
206
    end if
207
    if (opt_ov%override_minnrow) minnrow = opt_ov%minnrow
×
208
    if (opt_ov%override_field_subgath) field_subgath = opt_ov%field_subgath
×
209
    if (opt_ov%override_do_smart_update) do_smart_update = opt_ov%do_smart_update
×
210
    if (opt_ov%override_field_local_allreduce) field_local_allreduce = &
×
211
         opt_ov%field_local_allreduce
×
212
    if (opt_ov%override_field_local_allreduce_sub) field_local_allreduce_sub = &
×
213
      opt_ov%field_local_allreduce_sub
×
214
  end subroutine set_overrides
215

216
  !> Calls all initialisations required for init_fields_implicit/local, 
217
  !! reads parameters and allocates field arrays
218
  subroutine fields_pre_init(fields_config_in)
×
219
    use unit_tests, only: debug_message
220
    use kt_grids, only: naky, ntheta0
221
    use mp, only: nproc, proc0
222
    use dist_fn, only: gf_lo_integrate
223
    implicit none
224
    type(fields_config_type), intent(in), optional :: fields_config_in    
225
    integer, parameter :: verb=3
226
    
227
    call init_fields_parameters(fields_config_in)
×
228

229
    if(nproc < ntheta0*naky .and. fieldopt_switch == fieldopt_gf_local) then
×
230
       fieldopt_switch = fieldopt_local
×
231
       gf_lo_integrate = .false.
×
232
       if(proc0) then
×
233
          write(*,*) 'gf local fields cannot be used as you are running less MPI processes than there are'
×
234
          write(*,*) 'naky*ntheta0 points.  Defaulting to local fields.  You need to use at least',naky*ntheta0
×
235
          write(*,*) 'MPI processes for this simulation'
×
236
       end if
237
    end if
238

239
    call debug_message(verb, "init_fields: allocate_arrays")
×
240
    call allocate_arrays
×
241
  end subroutine fields_pre_init
×
242

243
  !> FIXME : Add documentation  
244
  subroutine init_fields_parameters(fields_config_in)
28✔
245
    use unit_tests, only: debug_message
246
    implicit none
247
    type(fields_config_type), intent(in), optional :: fields_config_in    
248
    integer, parameter :: verb=3
249
    if (parameters_read) return
28✔
250
    call debug_message(verb, "init_fields: read_parameters")
28✔
251
    call read_parameters(fields_config_in)
28✔
252
    parameters_read = .true.
28✔
253
  end subroutine init_fields_parameters
254

255
  !> FIXME : Add documentation  
256
  subroutine finish_fields_parameters
28✔
257
    parameters_read = .false.
28✔
258
  end subroutine finish_fields_parameters
28✔
259

260
  !> FIXME : Add documentation  
261
  subroutine init_fields_level_1
×
262
    use unit_tests, only: debug_message
263
    implicit none
264
    integer, parameter :: verb=3
265
    call debug_message(verb, "init_fields: allocate_arrays")
×
266
    call allocate_arrays
×
267
  end subroutine init_fields_level_1
×
268

269
  !> FIXME : Add documentation  
270
  subroutine finish_fields_level_1
×
271
    call finish_fields
×
272
  end subroutine finish_fields_level_1
×
273

274
  !> FIXME : Add documentation  
275
  subroutine init_fields_level_2
×
276
    call init_fields
×
277
  end subroutine init_fields_level_2
×
278

279
  !> FIXME : Add documentation  
280
  subroutine finish_fields_level_2
×
281
    use fields_implicit, only: fi_reset => reset_init
282
    use fields_test, only: ft_reset => reset_init
283
    use fields_local, only: fl_reset => reset_fields_local
284
    use fields_gf_local, only: flgf_reset => reset_fields_gf_local
285
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
286
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
287
    use array_utils, only: zero_array
288
    implicit none
289
    initialized  = .false.
×
290
    call zero_array(phi) ; call zero_array(phinew)
×
291
    call zero_array(apar) ; call zero_array(aparnew)
×
292
    call zero_array(bpar) ; call zero_array(bparnew)
×
293
    if(fieldopt_switch == fieldopt_gf_local) then
×
294
       call zero_array(gf_phi) ; call zero_array(gf_phinew)
×
295
       call zero_array(gf_apar) ; call zero_array(gf_aparnew)
×
296
       call zero_array(gf_bpar) ; call zero_array(gf_bparnew)
×
297
    end if
298
    !What about apar_ext?
299
    select case (fieldopt_switch)
×
300
    case (fieldopt_implicit)
301
       call fi_reset
×
302
    case (fieldopt_test)
303
       call ft_reset
×
304
    case (fieldopt_local)
305
       call fl_reset
×
306
    case (fieldopt_gf_local)
307
       call flgf_reset
×
308
    end select
309
  end subroutine finish_fields_level_2
×
310

311
  !> FIXME : Add documentation  
312
  subroutine fields_init_response
×
313
    use fields_implicit, only: init_fields_implicit
314
    use fields_test, only: init_fields_test
315
    use fields_local, only: init_fields_local
316
    use fields_gf_local, only: init_fields_gf_local
317
    use unit_tests, only: debug_message
318
    implicit none
319
    integer, parameter :: verb=3
320
    select case (fieldopt_switch)
×
321
    case (fieldopt_implicit)
322
       call debug_message(verb, &
323
         "fields::fields_init_response init_fields_implicit")
×
324
       call init_fields_implicit
×
325
    case (fieldopt_test)
326
       call debug_message(verb, "fields::fields_init_response init_fields_test")
×
327
       call init_fields_test
×
328
    case (fieldopt_local)
329
       call debug_message(verb, &
330
         "fields::fields_init_response init_fields_local")
×
331
       call init_fields_local
×
332
    case (fieldopt_gf_local)
333
       call debug_message(verb, &
334
         "fields::fields_init_response init_fields_gf_local")
×
335
       call init_fields_gf_local
×
336
    case default
337
       !Silently ignore unsupported field options
338
    end select
339
  end subroutine fields_init_response
×
340

341
  !> FIXME : Add documentation  
342
  subroutine init_fields(fields_config_in)
×
343
    use kt_grids, only: is_box, kwork_filter
344
    implicit none
345
    type(fields_config_type), intent(in), optional :: fields_config_in    
346
    logical, parameter :: debug=.false.
347

348
    if (initialized) return
×
349
    initialized = .true.
×
350
    
351
    call fields_pre_init(fields_config_in)
×
352

353
    call fields_init_response
×
354

355
    !If running in flux tube disable evolution of ky=kx=0 mode
356
    if (is_box) kwork_filter(1,1)=.true.
×
357
  end subroutine init_fields
358

359
  !> Force the current response matrices to be written to file
360
  subroutine dump_response_to_file(suffix)
×
361
    use fields_implicit, only: dump_response_to_file_imp
362
    use fields_local, only: dump_response_to_file_local
363
    use fields_gf_local, only: dump_response_to_file_gf_local
364
    implicit none
365
    character(len=*), intent(in), optional :: suffix 
366
    !Note can pass optional straight through as long as also optional
367
    !in called routine (and not different routines combined in interface)
368
    select case (fieldopt_switch)
×
369
    case (fieldopt_implicit)
370
       call dump_response_to_file_imp(suffix)
×
371
    case (fieldopt_local)
372
       call dump_response_to_file_local(suffix)
×
373
    case (fieldopt_gf_local)
374
       call dump_response_to_file_gf_local(suffix)
×
375
    case default
376
       !Silently ignore unsupported field options
377
    end select
378
  end subroutine dump_response_to_file
×
379

380
  !> FIXME : Add documentation
381
  subroutine set_init_fields
×
382
    use fields_implicit, only: init_allfields_implicit
383
    use fields_test, only: init_phi_test
384
    use mp, only: proc0
385
    use fields_local, only: init_allfields_local
386
    use fields_gf_local, only: init_allfields_gf_local
387
    use dist_fn, only: gf_lo_integrate
388
    use gs2_layouts, only: gf_local_fields
389
    use kt_grids, only: naky, ntheta0
390
    implicit none
391
    logical, parameter :: debug=.false.
392
    if(proc0.and.debug) write(6,*) "Syncing fields with g."
393
    select case (fieldopt_switch)
×
394
    case (fieldopt_implicit)
395
       if (debug) write(6,*) "init_fields: init_allfields_implicit"
396
       call init_allfields_implicit
×
397
    case (fieldopt_test)
398
       if (debug) write(6,*) "init_fields: init_phi_test"
399
       call init_phi_test
×
400
    case (fieldopt_local)
401
       if (debug) write(6,*) "init_fields: init_allfields_local"
402
       call init_allfields_local
×
403
    case (fieldopt_gf_local)
404
       if (debug) write(6,*) "init_fields: init_allfields_gf_local"
405
       if(.not. gf_lo_integrate .or. .not. gf_local_fields) then
×
406
          if(proc0) then
×
407
             write(*,*) 'gf_lo_integrate',gf_lo_integrate,'gf_local_fields',gf_local_fields
×
408
             write(*,*) 'gf local fields cannot be used by gf_lo_integrate'
×
409
             write(*,*) 'defaulting to local fields'
×
410
             write(*,*) 'if you want to use gf local fields then set gf_lo_integrate to true in dist_fn_knobs'
×
411
             write(*,*) 'and gf_local_fields to true in layouts_knobs and make sure you are running on more MPI'
×
412
             write(*,*) 'mpi processes than naky*ntheta0.  For this simulation that is: ',naky*ntheta0
×
413
          end if
414
          fieldopt_switch = fieldopt_local
×
415
          call init_allfields_local
×
416
       else
417
          call init_allfields_gf_local
×
418
       end if
419
    end select
420
  end subroutine set_init_fields
×
421

422
  !> FIXME : Add documentation  
423
  subroutine read_parameters(fields_config_in)
28✔
424
    use file_utils, only: error_unit
425
    use text_options, only: text_option, get_option_value
426
    use fields_implicit, only: field_subgath
427
    use fields_local, only: minNRow
428
    use fields_local, only: do_smart_update, field_local_allreduce, field_local_allreduce_sub
429
    use fields_local, only: field_local_tuneminnrow,  field_local_nonblocking_collectives
430
    use fields_arrays, only: real_response_file => response_file
431
    use file_utils, only: run_name
432
    implicit none
433
    type(fields_config_type), intent(in), optional :: fields_config_in    
434
    character(20) :: field_option
435
    character(len=256) :: response_dir
436
    character(len=256) :: response_file
437
    integer :: ierr, ind_slash
438

439
    if (present(fields_config_in)) fields_config = fields_config_in
28✔
440

441
    call fields_config%init(name = 'fields_knobs', requires_index = .false.)
28✔
442

443
    ! Copy out internal values into module level parameters
444
    associate(self => fields_config)
445
#include "fields_copy_out_auto_gen.inc"
446
    end associate
447

448
    ierr = error_unit()
28✔
449
    call get_option_value &
450
         (field_option, fieldopts, fieldopt_switch, &
451
         ierr, "field_option in fields_knobs",.true.)
28✔
452

453
    if (trim(response_file) == '') then
28✔
454
       response_file = trim(run_name)
28✔
455
    end if
456

457
    if(trim(response_dir)=='')then
28✔
458
       write(real_response_file,'(A)') trim(response_file)
28✔
459
    else
460
       ! Need to check if resopnse_file has a directory path in it
461
       ! to ensure we merge with response_dir correctly. For example,
462
       ! consider response_file = '../../run/input' and response_dir = 'resp'.
463
       ! We want to form response_file = '../../run/resp/input' and not
464
       ! 'resp/../../run/input' as would happen if just concatenate.
465
       ! Check for index of last '/'
466
       ind_slash = index(response_file, "/", back = .true.)
×
467
       if (ind_slash == 0) then
×
468
          write(real_response_file,'(A,"/",A)') trim(response_dir),trim(response_file)
×
469
       else
470
          write(real_response_file,'(A,A,"/",A)') &
471
               response_file(1:ind_slash), &
×
472
               trim(response_dir), &
×
473
               trim(response_file(ind_slash+1:))
×
474
       end if
475
    endif
476

477
    !Set the solve type specific flags
478
    call set_dump_and_read_response(dump_response, read_response)
28✔
479
  end subroutine read_parameters
28✔
480

481
  !> FIXME : Add documentation  
482
  subroutine set_dump_and_read_response(dump_flag, read_flag)
28✔
483
    use fields_implicit, only: dump_response_imp => dump_response, read_response_imp=>read_response
484
    use fields_local, only: dump_response_loc => dump_response, read_response_loc=>read_response
485
    use fields_gf_local, only: dump_response_gf => dump_response, read_response_gf=>read_response
486
    implicit none
487
    logical, intent(in) :: dump_flag, read_flag
488
    select case (fieldopt_switch)
28✔
489
    case (fieldopt_implicit)
490
       dump_response_imp=dump_flag
28✔
491
       read_response_imp=read_flag
28✔
492
    case (fieldopt_local)
493
       dump_response_loc=dump_flag
×
494
       read_response_loc=read_flag
×
495
    case (fieldopt_gf_local)
496
       dump_response_gf=dump_flag
×
497
       read_response_gf=read_flag
28✔
498
    case default
499
       !Silently ignore unsupported field types
500
    end select
501
  end subroutine set_dump_and_read_response
28✔
502

503
  !> FIXME : Add documentation  
504
  subroutine allocate_arrays
×
505
    use theta_grid, only: ntgrid
506
    use kt_grids, only: naky, ntheta0
507
    use antenna, only: no_driver
508
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew, apar_ext
509
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
510
    use unit_tests, only: debug_message
511
    use array_utils, only: zero_array
512
    implicit none
513
    integer, parameter :: verb=3
514

515
    if (.not. allocated(phi)) then
×
516
       call debug_message(verb, 'fields::allocate_arrays allocating')
×
517
       allocate (     phi (-ntgrid:ntgrid,ntheta0,naky))
×
518
       allocate (    apar (-ntgrid:ntgrid,ntheta0,naky))
×
519
       allocate (   bpar (-ntgrid:ntgrid,ntheta0,naky))
×
520
       allocate (  phinew (-ntgrid:ntgrid,ntheta0,naky))
×
521
       allocate ( aparnew (-ntgrid:ntgrid,ntheta0,naky))
×
522
       allocate (bparnew (-ntgrid:ntgrid,ntheta0,naky))
×
523
       if(fieldopt_switch == fieldopt_gf_local) then
×
524
          !AJ It should be possible to reduce the size of these by only allocating them
525
          !AJ the extend of it and ik in gf_lo.  However, it would need to be done carefully 
526
          !AJ to ensure the proc0 has the full space if we are still reducing data to proc0 
527
          !AJ for diagnostics.
528
          !AJ With some careful thought it should also be possible to remove this all together and 
529
          !AJ simply use the arrays above, but that would need checking
530
          allocate (    gf_phi (-ntgrid:ntgrid,ntheta0,naky))
×
531
          allocate (   gf_apar (-ntgrid:ntgrid,ntheta0,naky))
×
532
          allocate (   gf_bpar (-ntgrid:ntgrid,ntheta0,naky))          
×
533
          allocate ( gf_phinew (-ntgrid:ntgrid,ntheta0,naky))
×
534
          allocate (gf_aparnew (-ntgrid:ntgrid,ntheta0,naky))
×
535
          allocate (gf_bparnew (-ntgrid:ntgrid,ntheta0,naky))          
×
536
       end if
537
    endif
538
    !AJ This shouldn't be necessary as it is done in the fields code....
539
    call zero_array(phi) ; call zero_array(phinew)
×
540
    call zero_array(apar) ; call zero_array(aparnew)
×
541
    call zero_array(bpar) ; call zero_array(bparnew)
×
542
    if(fieldopt_switch == fieldopt_gf_local) then
×
543
       call zero_array(gf_phi) ; call zero_array(gf_phinew)
×
544
       call zero_array(gf_apar) ; call zero_array(gf_aparnew)
×
545
       call zero_array(gf_bpar) ; call zero_array(gf_bparnew)
×
546
    end if
547
    if(.not.allocated(apar_ext).and.(.not.no_driver))then
×
548
       allocate (apar_ext (-ntgrid:ntgrid,ntheta0,naky))
×
549
       call zero_array(apar_ext)
×
550
    endif
551
  end subroutine allocate_arrays
×
552

553
  !> FIXME : Add documentation  
554
  subroutine advance (istep)
×
555
    use fields_implicit, only: advance_implicit
556
    use fields_test, only: advance_test
557
    use fields_local, only: advance_local
558
    use fields_gf_local, only: advance_gf_local
559

560
    implicit none
561
    integer, intent (in) :: istep
562

563
    select case (fieldopt_switch)
×
564
    case (fieldopt_implicit)
565
       call advance_implicit (istep, remove_zonal_flows_switch)
×
566
    case (fieldopt_test)
567
       call advance_test (istep)
×
568
    case (fieldopt_local)
569
       call advance_local (istep, remove_zonal_flows_switch)
×
570
    case (fieldopt_gf_local)
571
       call advance_gf_local (istep, remove_zonal_flows_switch)
×
572
    end select
573
  end subroutine advance
×
574

575
  !> FIXME : Add documentation  
576
  subroutine finish_fields
×
577
    use fields_implicit, only: finish_fields_implicit
578
    use fields_test, only: test_reset => reset_init
579
    use fields_local, only: finish_fields_local
580
    use fields_gf_local, only: finish_fields_gf_local
581
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
582
    use fields_arrays, only: apar_ext, gf_phi, gf_apar, gf_bpar
583
    use fields_arrays, only: apar_ext, gf_phinew, gf_aparnew, gf_bparnew
584
    use unit_tests, only: debug_message
585
    use array_utils, only: zero_array
586
    implicit none
587
    integer, parameter :: verbosity = 3
588

589
    initialized  = .false.
×
590
!AJ Does these need zero'd if they are to be deallocated below?
591
    call zero_array(phi) ; call zero_array(phinew)
×
592
    call zero_array(apar) ; call zero_array(aparnew)
×
593
    call zero_array(bpar) ; call zero_array(bparnew)
×
594
    call debug_message(verbosity, &
595
      'fields::finish_fields zeroed fields')
×
596
    
597
    select case (fieldopt_switch)
×
598
    case (fieldopt_implicit)
599
       call finish_fields_implicit
×
600
    case (fieldopt_local)
601
       call finish_fields_local
×
602
    case (fieldopt_gf_local)
603
       call finish_fields_gf_local
×
604
    end select
605

606
    call debug_message(verbosity, &
607
      'fields::finish_fields called subroutines')
×
608

609
    if (allocated(phi)) deallocate (phi, apar, bpar, phinew, aparnew, bparnew)
×
610
    if (allocated(gf_phi)) deallocate(gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew)
×
611
    if (allocated(apar_ext)) deallocate (apar_ext)
×
612
    call debug_message(verbosity, &
613
      'fields::finish_fields deallocated fields')
×
614

615
    call fields_config%reset()
×
616
  end subroutine finish_fields
×
617

618
#include "fields_auto_gen.inc"  
619
end module fields
×
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc