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

gyrokinetics / gs2 / 1998640042

22 Aug 2025 01:50PM UTC coverage: 10.577% (-0.1%) from 10.718%
1998640042

push

gitlab-ci

David Dickinson
Merged in feature/dont_reset_configs_when_finishing_modules (pull request #1160)

4700 of 44434 relevant lines covered (10.58%)

125622.86 hits per line

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

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

6
  implicit none
7

8
  private 
9

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

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

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

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

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

175
  !> FIXME : Add documentation  
176
  subroutine wnml_fields(unit)
×
177
    implicit none
178
    integer, intent(in) :: unit
179
    call fields_config%write(unit)
×
180
  end subroutine wnml_fields
×
181

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

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

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

233
    call debug_message(verb, "init_fields: allocate_arrays")
×
234
    call allocate_arrays
×
235
  end subroutine fields_pre_init
×
236

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

249
  !> FIXME : Add documentation  
250
  subroutine finish_fields_parameters
28✔
251
    parameters_read = .false.
28✔
252
  end subroutine finish_fields_parameters
28✔
253

254
  !> FIXME : Add documentation  
255
  subroutine init_fields_level_1
×
256
    use unit_tests, only: debug_message
257
    implicit none
258
    integer, parameter :: verb=3
259
    call debug_message(verb, "init_fields: allocate_arrays")
×
260
    call allocate_arrays
×
261
  end subroutine init_fields_level_1
×
262

263
  !> FIXME : Add documentation  
264
  subroutine finish_fields_level_1
×
265
    call finish_fields
×
266
  end subroutine finish_fields_level_1
×
267

268
  !> FIXME : Add documentation  
269
  subroutine init_fields_level_2
×
270
    call init_fields
×
271
  end subroutine init_fields_level_2
×
272

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

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

335
  !> FIXME : Add documentation  
336
  subroutine init_fields(fields_config_in)
×
337
    use kt_grids, only: is_box, kwork_filter
338
    implicit none
339
    type(fields_config_type), intent(in), optional :: fields_config_in    
340
    logical, parameter :: debug=.false.
341

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

347
    call fields_init_response
×
348

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

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

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

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

433
    if (present(fields_config_in)) fields_config = fields_config_in
28✔
434

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

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

442
    ierr = error_unit()
28✔
443
    call get_option_value &
444
         (field_option, fieldopts, fieldopt_switch, &
445
         ierr, "field_option in fields_knobs",.true.)
28✔
446

447
    if (trim(response_file) == '') then
28✔
448
       response_file = trim(run_name)
28✔
449
    end if
450

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

471
    !Set the solve type specific flags
472
    call set_dump_and_read_response(dump_response, read_response)
28✔
473
  end subroutine read_parameters
28✔
474

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

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

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

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

554
    implicit none
555
    integer, intent (in) :: istep
556

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

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

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

600
    call debug_message(verbosity, &
601
      'fields::finish_fields called subroutines')
×
602

603
    if (allocated(phi)) deallocate (phi, apar, bpar, phinew, aparnew, bparnew)
×
604
    if (allocated(gf_phi)) deallocate(gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew)
×
605
    if (allocated(apar_ext)) deallocate (apar_ext)
×
606
    call debug_message(verbosity, &
607
      'fields::finish_fields deallocated fields')
×
608
  end subroutine finish_fields
×
609

610
#include "fields_auto_gen.inc"  
611
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