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

gyrokinetics / gs2 / 1969605222

06 Aug 2025 09:58AM UTC coverage: 8.231% (+0.01%) from 8.219%
1969605222

push

gitlab-ci

David Dickinson
Merged in minor/refactor_initialising_of_nonlinear_terms_to_simplify_setup (pull request #1106)

3710 of 45073 relevant lines covered (8.23%)

123835.53 hits per line

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

0.0
/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
13
  public :: reset_init, set_init_fields
14
  public :: fields_init_response, set_dump_and_read_response
15
  public :: dump_response_to_file
16
  public :: init_fields_parameters
17
  public :: finish_fields_parameters
18
  public :: set_overrides
19
  public :: init_fields_level_1, init_fields_level_2
20
  public :: finish_fields_level_1, finish_fields_level_2
21
  public :: fieldopt_switch, fieldopt_implicit, fieldopt_test, fieldopt_local, fieldopt_gf_local
22

23
  !> Made public for unit tests
24
  public :: fields_pre_init
25
  public :: remove_zonal_flows_switch
26

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

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

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

185
  !> FIXME : Add documentation  
186
  subroutine wnml_fields(unit)
×
187
    implicit none
188
    integer, intent(in) :: unit
189
    call fields_config%write(unit)
×
190
  end subroutine wnml_fields
×
191

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

220
  !> Calls all initialisations required for init_fields_implicit/local, 
221
  !! reads parameters and allocates field arrays
222
  subroutine fields_pre_init(fields_config_in)
×
223
    use theta_grid, only: init_theta_grid
224
    use run_parameters, only: init_run_parameters
225
    use dist_fn, only: init_dist_fn, gf_lo_integrate
226
    use antenna, only: init_antenna
227
    use unit_tests, only: debug_message
228
    use kt_grids, only: naky, ntheta0
229
    use mp, only: nproc, proc0
230
    implicit none
231
    type(fields_config_type), intent(in), optional :: fields_config_in    
232
    integer, parameter :: verb=3
233
    
234
    call init_fields_parameters(fields_config_in)
×
235
    call debug_message(verb, "init_fields: init_theta_grid")
×
236
    call init_theta_grid
×
237
    call debug_message(verb, "init_fields: init_run_parameters")
×
238
    call init_run_parameters
×
239
    call debug_message(verb, "init_fields: init_dist_fn")
×
240
    call init_dist_fn
×
241

242
    if(nproc < ntheta0*naky .and. fieldopt_switch == fieldopt_gf_local) then
×
243
       fieldopt_switch = fieldopt_local
×
244
       gf_lo_integrate = .false.
×
245
       if(proc0) then
×
246
          write(*,*) 'gf local fields cannot be used as you are running less MPI processes than there are'
×
247
          write(*,*) 'naky*ntheta0 points.  Defaulting to local fields.  You need to use at least',naky*ntheta0
×
248
          write(*,*) 'MPI processes for this simulation'
×
249
       end if
250
    end if
251

252
    call debug_message(verb, "init_fields: init_antenna")
×
253
    call init_antenna !Must come before allocate_arrays so we know if we need apar_ext
×
254
    call debug_message(verb, "init_fields: allocate_arrays")
×
255
    call allocate_arrays
×
256
  end subroutine fields_pre_init
×
257

258
  !> FIXME : Add documentation  
259
  subroutine init_fields_parameters(fields_config_in)
×
260
    use unit_tests, only: debug_message
261
    implicit none
262
    type(fields_config_type), intent(in), optional :: fields_config_in    
263
    integer, parameter :: verb=3
264
    if (parameters_read) return
×
265
    call debug_message(verb, "init_fields: read_parameters")
×
266
    call read_parameters(fields_config_in)
×
267
    parameters_read = .true.
×
268
  end subroutine init_fields_parameters
269

270
  !> FIXME : Add documentation  
271
  subroutine finish_fields_parameters
×
272
    parameters_read = .false.
×
273
  end subroutine finish_fields_parameters
×
274

275
  !> FIXME : Add documentation  
276
  subroutine init_fields_level_1
×
277
    use unit_tests, only: debug_message
278
    implicit none
279
    integer, parameter :: verb=3
280
    call debug_message(verb, "init_fields: allocate_arrays")
×
281
    call allocate_arrays
×
282
  end subroutine init_fields_level_1
×
283

284
  !> FIXME : Add documentation  
285
  subroutine finish_fields_level_1
×
286
    call finish_fields
×
287
  end subroutine finish_fields_level_1
×
288

289
  !> FIXME : Add documentation  
290
  subroutine init_fields_level_2
×
291
    call init_fields
×
292
  end subroutine init_fields_level_2
×
293

294
  !> FIXME : Add documentation  
295
  subroutine finish_fields_level_2
×
296
    call reset_init
×
297
  end subroutine finish_fields_level_2
×
298

299
  !> FIXME : Add documentation  
300
  subroutine fields_init_response
×
301
    use fields_implicit, only: init_fields_implicit
302
    use fields_test, only: init_fields_test
303
    use fields_local, only: init_fields_local
304
    use fields_gf_local, only: init_fields_gf_local
305
    use unit_tests, only: debug_message
306
    implicit none
307
    integer, parameter :: verb=3
308
    select case (fieldopt_switch)
×
309
    case (fieldopt_implicit)
310
       call debug_message(verb, &
311
         "fields::fields_init_response init_fields_implicit")
×
312
       call init_fields_implicit
×
313
    case (fieldopt_test)
314
       call debug_message(verb, "fields::fields_init_response init_fields_test")
×
315
       call init_fields_test
×
316
    case (fieldopt_local)
317
       call debug_message(verb, &
318
         "fields::fields_init_response init_fields_local")
×
319
       call init_fields_local
×
320
    case (fieldopt_gf_local)
321
       call debug_message(verb, &
322
         "fields::fields_init_response init_fields_gf_local")
×
323
       call init_fields_gf_local
×
324
    case default
325
       !Silently ignore unsupported field options
326
    end select
327
  end subroutine fields_init_response
×
328

329
  !> FIXME : Add documentation  
330
  subroutine init_fields(fields_config_in)
×
331
    use theta_grid, only: init_theta_grid
332
    use run_parameters, only: init_run_parameters
333
    use dist_fn, only: init_dist_fn
334
    use antenna, only: init_antenna
335
    use kt_grids, only: is_box, kwork_filter
336
    implicit none
337
    type(fields_config_type), intent(in), optional :: fields_config_in    
338
    logical, parameter :: debug=.false.
339

340
    if (initialized) return
×
341
    initialized = .true.
×
342
    
343
    call fields_pre_init(fields_config_in)
×
344

345
    call fields_init_response
×
346

347
    !If running in flux tube disable evolution of ky=kx=0 mode
348
    if (is_box) kwork_filter(1,1)=.true.
×
349
  end subroutine init_fields
350

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

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

414
  !> FIXME : Add documentation  
415
  subroutine read_parameters(fields_config_in)
×
416
    use file_utils, only: error_unit
417
    use text_options, only: text_option, get_option_value
418
    use fields_implicit, only: field_subgath
419
    use fields_local, only: minNRow
420
    use fields_local, only: do_smart_update, field_local_allreduce, field_local_allreduce_sub
421
    use fields_local, only: field_local_tuneminnrow,  field_local_nonblocking_collectives
422
    use fields_arrays, only: real_response_file => response_file
423
    use file_utils, only: run_name
424
    implicit none
425
    type(fields_config_type), intent(in), optional :: fields_config_in    
426
    character(20) :: field_option
427
    character(len=256) :: response_dir
428
    character(len=256) :: response_file
429
    integer :: ierr, ind_slash
430

431
    if (present(fields_config_in)) fields_config = fields_config_in
×
432

433
    call fields_config%init(name = 'fields_knobs', requires_index = .false.)
×
434

435
    ! Copy out internal values into module level parameters
436
    associate(self => fields_config)
437
#include "fields_copy_out_auto_gen.inc"
438
    end associate
439

440
    ierr = error_unit()
×
441
    call get_option_value &
442
         (field_option, fieldopts, fieldopt_switch, &
443
         ierr, "field_option in fields_knobs",.true.)
×
444

445
    if (trim(response_file) == '') then
×
446
       response_file = trim(run_name)
×
447
    end if
448

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

469
    !Set the solve type specific flags
470
    call set_dump_and_read_response(dump_response, read_response)
×
471
  end subroutine read_parameters
×
472

473
  !> FIXME : Add documentation  
474
  subroutine set_dump_and_read_response(dump_flag, read_flag)
×
475
    use fields_implicit, only: dump_response_imp => dump_response, read_response_imp=>read_response
476
    use fields_local, only: dump_response_loc => dump_response, read_response_loc=>read_response
477
    use fields_gf_local, only: dump_response_gf => dump_response, read_response_gf=>read_response
478
    implicit none
479
    logical, intent(in) :: dump_flag, read_flag
480
    select case (fieldopt_switch)
×
481
    case (fieldopt_implicit)
482
       dump_response_imp=dump_flag
×
483
       read_response_imp=read_flag
×
484
    case (fieldopt_local)
485
       dump_response_loc=dump_flag
×
486
       read_response_loc=read_flag
×
487
    case (fieldopt_gf_local)
488
       dump_response_gf=dump_flag
×
489
       read_response_gf=read_flag
×
490
    case default
491
       !Silently ignore unsupported field types
492
    end select
493
  end subroutine set_dump_and_read_response
×
494

495
  !> FIXME : Add documentation  
496
  subroutine allocate_arrays
×
497
    use theta_grid, only: ntgrid
498
    use kt_grids, only: naky, ntheta0
499
    use antenna, only: no_driver
500
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew, apar_ext
501
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
502
    use unit_tests, only: debug_message
503
    use array_utils, only: zero_array
504
    implicit none
505
    integer, parameter :: verb=3
506

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

545
  !> FIXME : Add documentation  
546
  subroutine advance (istep)
×
547
    use fields_implicit, only: advance_implicit
548
    use fields_test, only: advance_test
549
    use fields_local, only: advance_local
550
    use fields_gf_local, only: advance_gf_local
551

552
    implicit none
553
    integer, intent (in) :: istep
554

555
    select case (fieldopt_switch)
×
556
    case (fieldopt_implicit)
557
       call advance_implicit (istep, remove_zonal_flows_switch)
×
558
    case (fieldopt_test)
559
       call advance_test (istep)
×
560
    case (fieldopt_local)
561
       call advance_local (istep, remove_zonal_flows_switch)
×
562
    case (fieldopt_gf_local)
563
       call advance_gf_local (istep, remove_zonal_flows_switch)
×
564
    end select
565
  end subroutine advance
×
566

567
  !> FIXME : Add documentation  
568
  subroutine reset_init
×
569
    use fields_implicit, only: fi_reset => reset_init
570
    use fields_test, only: ft_reset => reset_init
571
    use fields_local, only: fl_reset => reset_fields_local
572
    use fields_gf_local, only: flgf_reset => reset_fields_gf_local
573
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
574
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
575
    use array_utils, only: zero_array
576
    implicit none
577
    initialized  = .false.
×
578
    call zero_array(phi) ; call zero_array(phinew)
×
579
    call zero_array(apar) ; call zero_array(aparnew)
×
580
    call zero_array(bpar) ; call zero_array(bparnew)
×
581
    if(fieldopt_switch == fieldopt_gf_local) then
×
582
       call zero_array(gf_phi) ; call zero_array(gf_phinew)
×
583
       call zero_array(gf_apar) ; call zero_array(gf_aparnew)
×
584
       call zero_array(gf_bpar) ; call zero_array(gf_bparnew)
×
585
    end if
586
    !What about apar_ext?
587
    select case (fieldopt_switch)
×
588
    case (fieldopt_implicit)
589
       call fi_reset
×
590
    case (fieldopt_test)
591
       call ft_reset
×
592
    case (fieldopt_local)
593
       call fl_reset
×
594
    case (fieldopt_gf_local)
595
       call flgf_reset
×
596
    end select
597
  end subroutine reset_init
×
598

599
  !> FIXME : Add documentation  
600
  subroutine finish_fields
×
601
    use fields_implicit, only: finish_fields_implicit
602
    use fields_test, only: test_reset => reset_init
603
    use fields_local, only: finish_fields_local
604
    use fields_gf_local, only: finish_fields_gf_local
605
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
606
    use fields_arrays, only: apar_ext, gf_phi, gf_apar, gf_bpar
607
    use fields_arrays, only: apar_ext, gf_phinew, gf_aparnew, gf_bparnew
608
    use unit_tests, only: debug_message
609
    use array_utils, only: zero_array
610
    implicit none
611
    integer, parameter :: verbosity = 3
612

613
    initialized  = .false.
×
614
!AJ Does these need zero'd if they are to be deallocated below?
615
    call zero_array(phi) ; call zero_array(phinew)
×
616
    call zero_array(apar) ; call zero_array(aparnew)
×
617
    call zero_array(bpar) ; call zero_array(bparnew)
×
618
    call debug_message(verbosity, &
619
      'fields::finish_fields zeroed fields')
×
620
    
621
    select case (fieldopt_switch)
×
622
    case (fieldopt_implicit)
623
       call finish_fields_implicit
×
624
    case (fieldopt_local)
625
       call finish_fields_local
×
626
    case (fieldopt_gf_local)
627
       call finish_fields_gf_local
×
628
    end select
629

630
    call debug_message(verbosity, &
631
      'fields::finish_fields called subroutines')
×
632

633
    if (allocated(phi)) deallocate (phi, apar, bpar, phinew, aparnew, bparnew)
×
634
    if (allocated(gf_phi)) deallocate(gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew)
×
635
    if (allocated(apar_ext)) deallocate (apar_ext)
×
636
    call debug_message(verbosity, &
637
      'fields::finish_fields deallocated fields')
×
638

639
    call fields_config%reset()
×
640
  end subroutine finish_fields
×
641

642
#include "fields_auto_gen.inc"  
643
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