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

gyrokinetics / gs2 / 1821477209

16 May 2025 02:50PM UTC coverage: 8.139% (+0.2%) from 7.92%
1821477209

push

gitlab-ci

David Dickinson
Merged in bugfix/use_uv_in_coverage_test_to_install_packages (pull request #1142)

3704 of 45511 relevant lines covered (8.14%)

122643.73 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 nonlinear_terms, only: nl_finish_init => finish_init
335
    use antenna, only: init_antenna
336
    use kt_grids, only: is_box, kwork_filter
337
    implicit none
338
    type(fields_config_type), intent(in), optional :: fields_config_in    
339
    logical, parameter :: debug=.false.
340

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

346
    call fields_init_response
×
347

348
    ! Turn on nonlinear terms.
349
    if (debug) write(6,*) "init_fields: nl_finish_init"
350
    call nl_finish_init
×
351

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

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

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

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

436
    if (present(fields_config_in)) fields_config = fields_config_in
×
437

438
    call fields_config%init(name = 'fields_knobs', requires_index = .false.)
×
439

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

445
    ierr = error_unit()
×
446
    call get_option_value &
447
         (field_option, fieldopts, fieldopt_switch, &
448
         ierr, "field_option in fields_knobs",.true.)
×
449

450
    if (trim(response_file) == '') then
×
451
       response_file = trim(run_name)
×
452
    end if
453

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

474
    !Set the solve type specific flags
475
    call set_dump_and_read_response(dump_response, read_response)
×
476
  end subroutine read_parameters
×
477

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

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

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

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

557
    implicit none
558
    integer, intent (in) :: istep
559

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

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

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

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

635
    call debug_message(verbosity, &
636
      'fields::finish_fields called subroutines')
×
637

638
    if (allocated(phi)) deallocate (phi, apar, bpar, phinew, aparnew, bparnew)
×
639
    if (allocated(gf_phi)) deallocate(gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew)
×
640
    if (allocated(apar_ext)) deallocate (apar_ext)
×
641
    call debug_message(verbosity, &
642
      'fields::finish_fields deallocated fields')
×
643

644
    call fields_config%reset()
×
645
  end subroutine finish_fields
×
646

647
#include "fields_auto_gen.inc"  
648
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