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

gyrokinetics / gs2 / 2078249816

03 Oct 2025 10:07AM UTC coverage: 10.842% (+0.007%) from 10.835%
2078249816

push

gitlab-ci

David Dickinson
Merged in feature/auto_create_response_dir_if_dumping (pull request #1183)

5054 of 46614 relevant lines covered (10.84%)

119748.47 hits per line

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

12.44
/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, remove_zonal_flows_switch
21
  public :: fields_config_type, set_fields_config, get_fields_config
22
  
23
  ! knobs
24
  integer :: fieldopt_switch
25
  logical :: remove_zonal_flows_switch, force_maxwell_reinit, make_response_dir
26
  logical :: dump_response, read_response
27
  integer, parameter :: fieldopt_implicit = 1, fieldopt_test = 2, fieldopt_local = 3, fieldopt_gf_local = 4
28
  logical :: initialized = .false., parameters_read = .false.
29

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

142
  !> FIXME : Add documentation  
143
  subroutine check_fields(report_unit)
×
144
    use fields_local, only: do_smart_update, minNRow
145
    implicit none
146
    integer, intent(in) :: report_unit
147
    select case (fieldopt_switch)
×
148
    case (fieldopt_implicit)
149
       write (report_unit, fmt="('The field equations will be advanced in time implicitly.')")
×
150
       if(dump_response) write (report_unit, fmt="('The response matrix will be dumped to file.')")
×
151
       if(read_response) write (report_unit, fmt="('The response matrix will be read from file.')")
×
152
    case (fieldopt_test)
153
       write (report_unit, *) 
×
154
       write (report_unit, fmt="('################# WARNING #######################')")
×
155
       write (report_unit, fmt="('The field equations will only be tested.')")
×
156
       write (report_unit, fmt="('THIS IS PROBABLY AN ERROR.')") 
×
157
       write (report_unit, fmt="('################# WARNING #######################')")
×
158
       write (report_unit, *) 
×
159
    case (fieldopt_local)
160
       write (report_unit, fmt="('The field equations will be advanced in time implicitly with decomposition respecting g_lo layout.')")
×
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
       write(report_unit, fmt="('Using a min block size of ',I0)") minNrow
×
164
       if(do_smart_update) write(report_unit, fmt="('Using optimised field update.')")
×
165
    case (fieldopt_gf_local)
166
       write (report_unit, fmt="('The field equations will be advanced in time implicitly with decomposition respecting gf_lo layout.')")
×
167
    end select
168
  end subroutine check_fields
×
169

170
  !> FIXME : Add documentation  
171
  subroutine wnml_fields(unit)
×
172
    implicit none
173
    integer, intent(in) :: unit
174
    call fields_config%write(unit)
×
175
  end subroutine wnml_fields
×
176

177
  !> FIXME : Add documentation
178
  subroutine set_overrides(opt_ov)
×
179
    use overrides, only: optimisations_overrides_type
180
    use file_utils, only: error_unit
181
    use text_options, only: get_option_value
182
    use fields_local, only: minnrow
183
    use fields_implicit, only: field_subgath
184
    use fields_local, only: do_smart_update
185
    use fields_local, only: field_local_allreduce
186
    use fields_local, only: field_local_allreduce_sub
187
    type(optimisations_overrides_type), intent(in) :: opt_ov
188
    integer :: ierr
189
    if (.not. opt_ov%is_initialised()) return
×
190
    if (opt_ov%override_field_option) then
×
191
       ierr = error_unit()
×
192
       call get_option_value &
193
            (opt_ov%field_option, fieldopts, fieldopt_switch, &
194
            ierr, "field_option in set_overrides",.true.)
×
195
    end if
196
    if (opt_ov%override_minnrow) minnrow = opt_ov%minnrow
×
197
    if (opt_ov%override_field_subgath) field_subgath = opt_ov%field_subgath
×
198
    if (opt_ov%override_do_smart_update) do_smart_update = opt_ov%do_smart_update
×
199
    if (opt_ov%override_field_local_allreduce) field_local_allreduce = &
×
200
         opt_ov%field_local_allreduce
×
201
    if (opt_ov%override_field_local_allreduce_sub) field_local_allreduce_sub = &
×
202
      opt_ov%field_local_allreduce_sub
×
203
  end subroutine set_overrides
204

205
  !> Calls all initialisations required for init_fields_implicit/local, 
206
  !! reads parameters and allocates field arrays
207
  subroutine fields_pre_init(fields_config_in)
×
208
    use unit_tests, only: debug_message
209
    use kt_grids, only: naky, ntheta0
210
    use mp, only: nproc, proc0
211
    use dist_fn, only: gf_lo_integrate
212
    implicit none
213
    type(fields_config_type), intent(in), optional :: fields_config_in    
214
    integer, parameter :: verb=3
215
    
216
    call init_fields_parameters(fields_config_in)
×
217

218
    if(nproc < ntheta0*naky .and. fieldopt_switch == fieldopt_gf_local) then
×
219
       fieldopt_switch = fieldopt_local
×
220
       gf_lo_integrate = .false.
×
221
       if(proc0) then
×
222
          write(*,*) 'gf local fields cannot be used as you are running less MPI processes than there are'
×
223
          write(*,*) 'naky*ntheta0 points.  Defaulting to local fields.  You need to use at least',naky*ntheta0
×
224
          write(*,*) 'MPI processes for this simulation'
×
225
       end if
226
    end if
227

228
    call debug_message(verb, "init_fields: allocate_arrays")
×
229
    call allocate_arrays
×
230
  end subroutine fields_pre_init
×
231

232
  !> FIXME : Add documentation  
233
  subroutine init_fields_parameters(fields_config_in)
28✔
234
    use unit_tests, only: debug_message
235
    implicit none
236
    type(fields_config_type), intent(in), optional :: fields_config_in    
237
    integer, parameter :: verb=3
238
    if (parameters_read) return
28✔
239
    call debug_message(verb, "init_fields: read_parameters")
28✔
240
    call read_parameters(fields_config_in)
28✔
241
    parameters_read = .true.
28✔
242
  end subroutine init_fields_parameters
243

244
  !> FIXME : Add documentation  
245
  subroutine finish_fields_parameters
28✔
246
    parameters_read = .false.
28✔
247
  end subroutine finish_fields_parameters
28✔
248

249
  !> FIXME : Add documentation  
250
  subroutine init_fields_level_1
×
251
    use unit_tests, only: debug_message
252
    implicit none
253
    integer, parameter :: verb=3
254
    call debug_message(verb, "init_fields: allocate_arrays")
×
255
    call allocate_arrays
×
256
  end subroutine init_fields_level_1
×
257

258
  !> FIXME : Add documentation  
259
  subroutine finish_fields_level_1
×
260
    call finish_fields
×
261
  end subroutine finish_fields_level_1
×
262

263
  !> FIXME : Add documentation  
264
  subroutine init_fields_level_2
×
265
    call init_fields
×
266
  end subroutine init_fields_level_2
×
267

268
  !> FIXME : Add documentation  
269
  subroutine finish_fields_level_2
×
270
    use fields_implicit, only: fi_reset => reset_init
271
    use fields_test, only: ft_reset => reset_init
272
    use fields_local, only: fl_reset => reset_fields_local
273
    use fields_gf_local, only: flgf_reset => reset_fields_gf_local
274
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
275
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
276
    use array_utils, only: zero_array
277
    implicit none
278
    initialized  = .false.
×
279
    call zero_array(phi) ; call zero_array(phinew)
×
280
    call zero_array(apar) ; call zero_array(aparnew)
×
281
    call zero_array(bpar) ; call zero_array(bparnew)
×
282
    if(fieldopt_switch == fieldopt_gf_local) then
×
283
       call zero_array(gf_phi) ; call zero_array(gf_phinew)
×
284
       call zero_array(gf_apar) ; call zero_array(gf_aparnew)
×
285
       call zero_array(gf_bpar) ; call zero_array(gf_bparnew)
×
286
    end if
287
    !What about apar_ext?
288
    select case (fieldopt_switch)
×
289
    case (fieldopt_implicit)
290
       call fi_reset
×
291
    case (fieldopt_test)
292
       call ft_reset
×
293
    case (fieldopt_local)
294
       call fl_reset
×
295
    case (fieldopt_gf_local)
296
       call flgf_reset
×
297
    end select
298
  end subroutine finish_fields_level_2
×
299

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

330
  !> FIXME : Add documentation  
331
  subroutine init_fields(fields_config_in)
×
332
    use kt_grids, only: is_box, kwork_filter
333
    implicit none
334
    type(fields_config_type), intent(in), optional :: fields_config_in    
335
    logical, parameter :: debug=.false.
336

337
    if (initialized) return
×
338
    initialized = .true.
×
339
    
340
    call fields_pre_init(fields_config_in)
×
341

342
    call fields_init_response
×
343

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

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

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

411
  !> FIXME : Add documentation
412
  subroutine read_parameters(fields_config_in)
28✔
413
    use file_utils, only: error_unit
414
    use mp, only: proc0
415
    use text_options, only: text_option, get_option_value
416
    use fields_implicit, only: field_subgath
417
    use fields_local, only: minNRow
418
    use fields_local, only: do_smart_update, field_local_allreduce, field_local_allreduce_sub
419
    use fields_local, only: field_local_tuneminnrow,  field_local_nonblocking_collectives
420
    use fields_arrays, only: real_response_file => response_file
421
    use gs2_save, only: restart_writable
422
    use file_utils, only: run_name, dirname, basename, mkdir
423
    implicit none
424
    type(fields_config_type), intent(in), optional :: fields_config_in
425
    character(20) :: field_option
426
    character(len=256) :: response_dir, response_file
427
    integer :: ierr
428

429
    if (present(fields_config_in)) fields_config = fields_config_in
28✔
430

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

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

438
    ierr = error_unit()
28✔
439
    call get_option_value &
440
         (field_option, fieldopts, fieldopt_switch, &
441
         ierr, "field_option in fields_knobs",.true.)
28✔
442

443
    if (trim(response_file) == '') response_file = trim(run_name)
28✔
444
    
445
    real_response_file = dirname(response_file) // trim(response_dir) // basename(response_file)
28✔
446
    if (dump_response .and. make_response_dir) then
28✔
447
       if (.not. restart_writable(my_file = real_response_file)) then
×
448
          if (proc0) then
×
449
             write(*, '(A," (",A,") ",A)') "Initial attempt to write to response_dir", &
×
450
                  trim(dirname(real_response_file)),"failed, attempting to create it."
×
451
             call mkdir(dirname(real_response_file))
×
452
          end if
453
       end if
454
    end if
455

456
    !Set the solve type specific flags
457
    call set_dump_and_read_response(dump_response, read_response)
28✔
458
  end subroutine read_parameters
28✔
459

460
  !> FIXME : Add documentation  
461
  subroutine set_dump_and_read_response(dump_flag, read_flag)
28✔
462
    use fields_implicit, only: dump_response_imp => dump_response, read_response_imp=>read_response
463
    use fields_local, only: dump_response_loc => dump_response, read_response_loc=>read_response
464
    use fields_gf_local, only: dump_response_gf => dump_response, read_response_gf=>read_response
465
    implicit none
466
    logical, intent(in) :: dump_flag, read_flag
467
    select case (fieldopt_switch)
28✔
468
    case (fieldopt_implicit)
469
       dump_response_imp=dump_flag
28✔
470
       read_response_imp=read_flag
28✔
471
    case (fieldopt_local)
472
       dump_response_loc=dump_flag
×
473
       read_response_loc=read_flag
×
474
    case (fieldopt_gf_local)
475
       dump_response_gf=dump_flag
×
476
       read_response_gf=read_flag
28✔
477
    case default
478
       !Silently ignore unsupported field types
479
    end select
480
  end subroutine set_dump_and_read_response
28✔
481

482
  !> FIXME : Add documentation  
483
  subroutine allocate_arrays
×
484
    use theta_grid, only: ntgrid
485
    use kt_grids, only: naky, ntheta0
486
    use antenna, only: no_driver
487
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew, apar_ext
488
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
489
    use unit_tests, only: debug_message
490
    use array_utils, only: zero_array
491
    implicit none
492
    integer, parameter :: verb=3
493

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

532
  !> FIXME : Add documentation  
533
  subroutine advance (istep)
×
534
    use fields_implicit, only: advance_implicit
535
    use fields_test, only: advance_test
536
    use fields_local, only: advance_local
537
    use fields_gf_local, only: advance_gf_local
538

539
    implicit none
540
    integer, intent (in) :: istep
541

542
    select case (fieldopt_switch)
×
543
    case (fieldopt_implicit)
544
       call advance_implicit (istep, remove_zonal_flows_switch)
×
545
    case (fieldopt_test)
546
       call advance_test (istep)
×
547
    case (fieldopt_local)
548
       call advance_local (istep, remove_zonal_flows_switch)
×
549
    case (fieldopt_gf_local)
550
       call advance_gf_local (istep, remove_zonal_flows_switch)
×
551
    end select
552
  end subroutine advance
×
553

554
  !> FIXME : Add documentation  
555
  subroutine finish_fields
×
556
    use fields_implicit, only: finish_fields_implicit
557
    use fields_test, only: test_reset => reset_init
558
    use fields_local, only: finish_fields_local
559
    use fields_gf_local, only: finish_fields_gf_local
560
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
561
    use fields_arrays, only: apar_ext, gf_phi, gf_apar, gf_bpar
562
    use fields_arrays, only: apar_ext, gf_phinew, gf_aparnew, gf_bparnew
563
    use unit_tests, only: debug_message
564
    use array_utils, only: zero_array
565
    implicit none
566
    integer, parameter :: verbosity = 3
567

568
    initialized  = .false.
×
569
!AJ Does these need zero'd if they are to be deallocated below?
570
    call zero_array(phi) ; call zero_array(phinew)
×
571
    call zero_array(apar) ; call zero_array(aparnew)
×
572
    call zero_array(bpar) ; call zero_array(bparnew)
×
573
    call debug_message(verbosity, &
574
      'fields::finish_fields zeroed fields')
×
575
    
576
    select case (fieldopt_switch)
×
577
    case (fieldopt_implicit)
578
       call finish_fields_implicit
×
579
    case (fieldopt_local)
580
       call finish_fields_local
×
581
    case (fieldopt_gf_local)
582
       call finish_fields_gf_local
×
583
    end select
584

585
    call debug_message(verbosity, &
586
      'fields::finish_fields called subroutines')
×
587

588
    if (allocated(phi)) deallocate (phi, apar, bpar, phinew, aparnew, bparnew)
×
589
    if (allocated(gf_phi)) deallocate(gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew)
×
590
    if (allocated(apar_ext)) deallocate (apar_ext)
×
591
    call debug_message(verbosity, &
592
      'fields::finish_fields deallocated fields')
×
593
  end subroutine finish_fields
×
594

595
#include "fields_auto_gen.inc"  
596
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