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

gyrokinetics / gs2 / 1969858349

06 Aug 2025 12:16PM UTC coverage: 8.174% (+0.004%) from 8.17%
1969858349

push

gitlab-ci

David Dickinson
Merged in minor/remove_unused_reset_init_routines (pull request #1105)

3673 of 44933 relevant lines covered (8.17%)

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

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

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

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

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

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

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

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

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

248
    call debug_message(verb, "init_fields: init_antenna")
×
249
    call init_antenna !Must come before allocate_arrays so we know if we need apar_ext
×
250
    call debug_message(verb, "init_fields: allocate_arrays")
×
251
    call allocate_arrays
×
252
  end subroutine fields_pre_init
×
253

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

266
  !> FIXME : Add documentation  
267
  subroutine finish_fields_parameters
×
268
    parameters_read = .false.
×
269
  end subroutine finish_fields_parameters
×
270

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

280
  !> FIXME : Add documentation  
281
  subroutine finish_fields_level_1
×
282
    call finish_fields
×
283
  end subroutine finish_fields_level_1
×
284

285
  !> FIXME : Add documentation  
286
  subroutine init_fields_level_2
×
287
    call init_fields
×
288
  end subroutine init_fields_level_2
×
289

290
  !> FIXME : Add documentation  
291
  subroutine finish_fields_level_2
×
292
    use fields_implicit, only: fi_reset => reset_init
293
    use fields_test, only: ft_reset => reset_init
294
    use fields_local, only: fl_reset => reset_fields_local
295
    use fields_gf_local, only: flgf_reset => reset_fields_gf_local
296
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
297
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
298
    use array_utils, only: zero_array
299
    implicit none
300
    initialized  = .false.
×
301
    call zero_array(phi) ; call zero_array(phinew)
×
302
    call zero_array(apar) ; call zero_array(aparnew)
×
303
    call zero_array(bpar) ; call zero_array(bparnew)
×
304
    if(fieldopt_switch == fieldopt_gf_local) then
×
305
       call zero_array(gf_phi) ; call zero_array(gf_phinew)
×
306
       call zero_array(gf_apar) ; call zero_array(gf_aparnew)
×
307
       call zero_array(gf_bpar) ; call zero_array(gf_bparnew)
×
308
    end if
309
    !What about apar_ext?
310
    select case (fieldopt_switch)
×
311
    case (fieldopt_implicit)
312
       call fi_reset
×
313
    case (fieldopt_test)
314
       call ft_reset
×
315
    case (fieldopt_local)
316
       call fl_reset
×
317
    case (fieldopt_gf_local)
318
       call flgf_reset
×
319
    end select
320
  end subroutine finish_fields_level_2
×
321

322
  !> FIXME : Add documentation  
323
  subroutine fields_init_response
×
324
    use fields_implicit, only: init_fields_implicit
325
    use fields_test, only: init_fields_test
326
    use fields_local, only: init_fields_local
327
    use fields_gf_local, only: init_fields_gf_local
328
    use unit_tests, only: debug_message
329
    implicit none
330
    integer, parameter :: verb=3
331
    select case (fieldopt_switch)
×
332
    case (fieldopt_implicit)
333
       call debug_message(verb, &
334
         "fields::fields_init_response init_fields_implicit")
×
335
       call init_fields_implicit
×
336
    case (fieldopt_test)
337
       call debug_message(verb, "fields::fields_init_response init_fields_test")
×
338
       call init_fields_test
×
339
    case (fieldopt_local)
340
       call debug_message(verb, &
341
         "fields::fields_init_response init_fields_local")
×
342
       call init_fields_local
×
343
    case (fieldopt_gf_local)
344
       call debug_message(verb, &
345
         "fields::fields_init_response init_fields_gf_local")
×
346
       call init_fields_gf_local
×
347
    case default
348
       !Silently ignore unsupported field options
349
    end select
350
  end subroutine fields_init_response
×
351

352
  !> FIXME : Add documentation  
353
  subroutine init_fields(fields_config_in)
×
354
    use theta_grid, only: init_theta_grid
355
    use run_parameters, only: init_run_parameters
356
    use dist_fn, only: init_dist_fn
357
    use antenna, only: init_antenna
358
    use kt_grids, only: is_box, kwork_filter
359
    implicit none
360
    type(fields_config_type), intent(in), optional :: fields_config_in    
361
    logical, parameter :: debug=.false.
362

363
    if (initialized) return
×
364
    initialized = .true.
×
365
    
366
    call fields_pre_init(fields_config_in)
×
367

368
    call fields_init_response
×
369

370
    !If running in flux tube disable evolution of ky=kx=0 mode
371
    if (is_box) kwork_filter(1,1)=.true.
×
372
  end subroutine init_fields
373

374
  !> Force the current response matrices to be written to file
375
  subroutine dump_response_to_file(suffix)
×
376
    use fields_implicit, only: dump_response_to_file_imp
377
    use fields_local, only: dump_response_to_file_local
378
    use fields_gf_local, only: dump_response_to_file_gf_local
379
    implicit none
380
    character(len=*), intent(in), optional :: suffix 
381
    !Note can pass optional straight through as long as also optional
382
    !in called routine (and not different routines combined in interface)
383
    select case (fieldopt_switch)
×
384
    case (fieldopt_implicit)
385
       call dump_response_to_file_imp(suffix)
×
386
    case (fieldopt_local)
387
       call dump_response_to_file_local(suffix)
×
388
    case (fieldopt_gf_local)
389
       call dump_response_to_file_gf_local(suffix)
×
390
    case default
391
       !Silently ignore unsupported field options
392
    end select
393
  end subroutine dump_response_to_file
×
394

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

437
  !> FIXME : Add documentation  
438
  subroutine read_parameters(fields_config_in)
×
439
    use file_utils, only: error_unit
440
    use text_options, only: text_option, get_option_value
441
    use fields_implicit, only: field_subgath
442
    use fields_local, only: minNRow
443
    use fields_local, only: do_smart_update, field_local_allreduce, field_local_allreduce_sub
444
    use fields_local, only: field_local_tuneminnrow,  field_local_nonblocking_collectives
445
    use fields_arrays, only: real_response_file => response_file
446
    use file_utils, only: run_name
447
    implicit none
448
    type(fields_config_type), intent(in), optional :: fields_config_in    
449
    character(20) :: field_option
450
    character(len=256) :: response_dir
451
    character(len=256) :: response_file
452
    integer :: ierr, ind_slash
453

454
    if (present(fields_config_in)) fields_config = fields_config_in
×
455

456
    call fields_config%init(name = 'fields_knobs', requires_index = .false.)
×
457

458
    ! Copy out internal values into module level parameters
459
    associate(self => fields_config)
460
#include "fields_copy_out_auto_gen.inc"
461
    end associate
462

463
    ierr = error_unit()
×
464
    call get_option_value &
465
         (field_option, fieldopts, fieldopt_switch, &
466
         ierr, "field_option in fields_knobs",.true.)
×
467

468
    if (trim(response_file) == '') then
×
469
       response_file = trim(run_name)
×
470
    end if
471

472
    if(trim(response_dir)=='')then
×
473
       write(real_response_file,'(A)') trim(response_file)
×
474
    else
475
       ! Need to check if resopnse_file has a directory path in it
476
       ! to ensure we merge with response_dir correctly. For example,
477
       ! consider response_file = '../../run/input' and response_dir = 'resp'.
478
       ! We want to form response_file = '../../run/resp/input' and not
479
       ! 'resp/../../run/input' as would happen if just concatenate.
480
       ! Check for index of last '/'
481
       ind_slash = index(response_file, "/", back = .true.)
×
482
       if (ind_slash == 0) then
×
483
          write(real_response_file,'(A,"/",A)') trim(response_dir),trim(response_file)
×
484
       else
485
          write(real_response_file,'(A,A,"/",A)') &
486
               response_file(1:ind_slash), &
×
487
               trim(response_dir), &
×
488
               trim(response_file(ind_slash+1:))
×
489
       end if
490
    endif
491

492
    !Set the solve type specific flags
493
    call set_dump_and_read_response(dump_response, read_response)
×
494
  end subroutine read_parameters
×
495

496
  !> FIXME : Add documentation  
497
  subroutine set_dump_and_read_response(dump_flag, read_flag)
×
498
    use fields_implicit, only: dump_response_imp => dump_response, read_response_imp=>read_response
499
    use fields_local, only: dump_response_loc => dump_response, read_response_loc=>read_response
500
    use fields_gf_local, only: dump_response_gf => dump_response, read_response_gf=>read_response
501
    implicit none
502
    logical, intent(in) :: dump_flag, read_flag
503
    select case (fieldopt_switch)
×
504
    case (fieldopt_implicit)
505
       dump_response_imp=dump_flag
×
506
       read_response_imp=read_flag
×
507
    case (fieldopt_local)
508
       dump_response_loc=dump_flag
×
509
       read_response_loc=read_flag
×
510
    case (fieldopt_gf_local)
511
       dump_response_gf=dump_flag
×
512
       read_response_gf=read_flag
×
513
    case default
514
       !Silently ignore unsupported field types
515
    end select
516
  end subroutine set_dump_and_read_response
×
517

518
  !> FIXME : Add documentation  
519
  subroutine allocate_arrays
×
520
    use theta_grid, only: ntgrid
521
    use kt_grids, only: naky, ntheta0
522
    use antenna, only: no_driver
523
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew, apar_ext
524
    use fields_arrays, only: gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew
525
    use unit_tests, only: debug_message
526
    use array_utils, only: zero_array
527
    implicit none
528
    integer, parameter :: verb=3
529

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

568
  !> FIXME : Add documentation  
569
  subroutine advance (istep)
×
570
    use fields_implicit, only: advance_implicit
571
    use fields_test, only: advance_test
572
    use fields_local, only: advance_local
573
    use fields_gf_local, only: advance_gf_local
574

575
    implicit none
576
    integer, intent (in) :: istep
577

578
    select case (fieldopt_switch)
×
579
    case (fieldopt_implicit)
580
       call advance_implicit (istep, remove_zonal_flows_switch)
×
581
    case (fieldopt_test)
582
       call advance_test (istep)
×
583
    case (fieldopt_local)
584
       call advance_local (istep, remove_zonal_flows_switch)
×
585
    case (fieldopt_gf_local)
586
       call advance_gf_local (istep, remove_zonal_flows_switch)
×
587
    end select
588
  end subroutine advance
×
589

590
  !> FIXME : Add documentation  
591
  subroutine finish_fields
×
592
    use fields_implicit, only: finish_fields_implicit
593
    use fields_test, only: test_reset => reset_init
594
    use fields_local, only: finish_fields_local
595
    use fields_gf_local, only: finish_fields_gf_local
596
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
597
    use fields_arrays, only: apar_ext, gf_phi, gf_apar, gf_bpar
598
    use fields_arrays, only: apar_ext, gf_phinew, gf_aparnew, gf_bparnew
599
    use unit_tests, only: debug_message
600
    use array_utils, only: zero_array
601
    implicit none
602
    integer, parameter :: verbosity = 3
603

604
    initialized  = .false.
×
605
!AJ Does these need zero'd if they are to be deallocated below?
606
    call zero_array(phi) ; call zero_array(phinew)
×
607
    call zero_array(apar) ; call zero_array(aparnew)
×
608
    call zero_array(bpar) ; call zero_array(bparnew)
×
609
    call debug_message(verbosity, &
610
      'fields::finish_fields zeroed fields')
×
611
    
612
    select case (fieldopt_switch)
×
613
    case (fieldopt_implicit)
614
       call finish_fields_implicit
×
615
    case (fieldopt_local)
616
       call finish_fields_local
×
617
    case (fieldopt_gf_local)
618
       call finish_fields_gf_local
×
619
    end select
620

621
    call debug_message(verbosity, &
622
      'fields::finish_fields called subroutines')
×
623

624
    if (allocated(phi)) deallocate (phi, apar, bpar, phinew, aparnew, bparnew)
×
625
    if (allocated(gf_phi)) deallocate(gf_phi, gf_apar, gf_bpar, gf_phinew, gf_aparnew, gf_bparnew)
×
626
    if (allocated(apar_ext)) deallocate (apar_ext)
×
627
    call debug_message(verbosity, &
628
      'fields::finish_fields deallocated fields')
×
629

630
    call fields_config%reset()
×
631
  end subroutine finish_fields
×
632

633
#include "fields_auto_gen.inc"  
634
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