gs2_init.fpp Source File


Contents

Source Code


Source Code

! This file is used alongside code generated by generate_gs2_init.py

!> This module is analogous to the init() function
!> in Linux-based operating systems: it initialises
!> gs2 to a certain init_level. At a given init level,
!> certain modules are initialised and certain are not.
!>
!> The gs2_init module is used by gs2_main to initialise modules. A typical
!> additional use case for this module is when it is desired
!> to override a given parameter (as in the override_* functions
!> in gs2_main). GS2 must be taken down to the appropriate
!> init_level, where all modules which contain any of those
!> parameters are uninitialized. The override is then set
!> and gs2 is brought back up to the highest init_level.
!>
!> As in Linux, this module cannot be used until a certain
!> basic initialization has happened (think loading the kernel).
!> This basic initialization occurs in gs2_initialize in gs2_main,
!> and set the init_level to gs2_initialized.
!>
!> This is free software released under the MIT licence.
!> Originally written by:
!>            Edmund Highcock (edmundhighcock@users.sourceforge.net)
module gs2_init
  use abstract_config, only: abstract_config_type, CONFIG_MAX_NAME_LEN
  use overrides, only: miller_geometry_overrides_type, initial_values_overrides_type, optimisations_overrides_type
  use overrides, only: profiles_overrides_type, kt_grids_overrides_type, timestep_overrides_type
  implicit none

  private

  public :: init_type

  !> A list of possible intialization levels.
  public :: init_level_list

  !> Bring gs2 to the target initialization level.
  public :: init

  !> Reads the gs2_init namelist
  public :: init_gs2_init

  !> Finalize the module
  public :: finish_gs2_init

  public :: write_init_times, report_init_times, reset_init_times

  !> A type for storing the current initialization
  !> status, as well as all the overrides.
  type init_type
     !> The current init level
     integer :: level = 0
     !> Whether or not diagnostics have been initialized
     !> Not obvious why this belongs here really as we don't
     !> deal with diagnostics in this module.
     logical :: diagnostics_initialized = .false.
     !> An object for overriding all or selected
     !> Miller geometry parameters. You must call
     !> gs2_main::prepare_miller_geometry_overrides
     !> before setting these overrides. See
     !> documentation for the overrides::miller_geometry_overrides_type
     !> for more information.
     type(miller_geometry_overrides_type) :: mgeo_ov
     !> An object for overriding all or selected
     !> profile parameters such as species temperature, density, and gradients
     !> as well as the flow gradient and mach number. You must call
     !> gs2_main::prepare_profiles_overrides
     !> before setting these overrides. See
     !> documentation for the overrides::profiles_overrides_type
     !> for more information.
     type(kt_grids_overrides_type) :: kt_ov
     !> An object for overriding all or selected
     !> kt_grids parameters such as ny, nx, y0, jtwist etc.
     !> You must call
     !> gs2_main::prepare_kt_grids_overrides
     !> before setting these overrides. See
     !> documentation for the overrides::kt_grids_overrides_type
     !> for more information.
     type(profiles_overrides_type) :: prof_ov
     !> An object for overriding parameters connected
     !> to the timestep and cfl condition
     type(timestep_overrides_type) :: tstep_ov
     !> An object for overriding the initial values of
     !> the fields and distribution function. You must call
     !> gs2_main::prepare_initial_values_overrides
     !> before setting these overrides. This override
     !> is very complicated. See
     !> documentation for the overrides::initial_values_overrides_type
     !> for more information.
     type(initial_values_overrides_type) :: initval_ov
     !> An object for overriding non physics parameters which
     !> may alter run time and efficiency. You must call
     !> gs2_main::prepare_optimisations_overrides
     !> before setting these overrides.
     type(optimisations_overrides_type) :: opt_ov
  end type init_type

  !> Define an type to represent an initialisation level.
  !> This uses a hack to approximate type extension without
  !> the boiler plate of extending an abstract type.
  !> Specifically, we offer a type bound change_level procedure
  !> which just calls a procedure pointer to implement the
  !> actual work to change the level, specific to each instance.
  type :: init_level_type
     character(len=40) :: name = 'init level name not set'
     integer :: level = -1
     !> Used to set the verbosity level at which this
     !> level reports debug messages.
     integer :: debug_message_level = 1
     procedure(change_level_specific_interface), pointer, nopass, private :: change_level_specific => null()
     real, dimension(2) :: time_init = 0.
   contains
     procedure :: generate_debug_message => init_level_generate_debug_message
     procedure :: report_time => init_level_report_time
     procedure :: change_level => init_level_change_level
  end type init_level_type

  interface
     subroutine change_level_specific_interface(current, going_up)
       import init_type
       implicit none
       type(init_type), intent(in) :: current
       logical, intent(in) :: going_up
     end subroutine change_level_specific_interface
  end interface

  !> Used to store all the init_level_type instances. Setup during
  !> init_gs2_init.
  type(init_level_type), dimension(:), allocatable :: init_levels

  !> A type for labelling the different init
  !> levels available in gs2.
  type init_level_list_type
#include "gs2_init_level_list.inc"
  end type init_level_list_type

  type(init_level_list_type), parameter :: init_level_list = init_level_list_type()

  logical :: initialized = .false.

  interface init
     module procedure :: init_pass_type
     module procedure :: init_pass_int
  end interface init

contains

  !> Produce the debug message associated with this level
  subroutine init_level_generate_debug_message(self, going_up)
    use unit_tests, only: debug_message
    implicit none
    class(init_level_type), intent(in) :: self
    logical, intent(in) :: going_up
    character(len=:), allocatable :: direction_msg
    character(len=3) :: level_as_string
    if (going_up) then
       direction_msg = 'up'
    else
       direction_msg = 'down'
    end if
    write(level_as_string , '(I0)') self%level
    call debug_message(self%debug_message_level, &
         'gs2_init:init '//direction_msg//' reached init level -- '// &
         trim(adjustl(self%name))//' ('//trim(level_as_string)//')')
  end subroutine init_level_generate_debug_message

  !> Report the time spent in init for this level
  subroutine init_level_report_time(self, unit)
    use iso_fortran_env, only: output_unit
    use optionals, only: get_option_with_default
    implicit none
    class(init_level_type), intent(in) :: self
    integer, intent(in), optional :: unit
    write(get_option_with_default(unit, output_unit), '(A," : ",0pf9.3," seconds")') &
         trim(adjustl(self%name)), self%time_init(1)
  end subroutine init_level_report_time

  !> General wrapper to the init_level instance's specific
  !> change level method.
  integer function init_level_change_level(self, current, going_up) result(new_level)
    use job_manage, only: time_message
    implicit none
    class(init_level_type), intent(in out) :: self
    type(init_type), intent(in) :: current
    logical, intent(in) :: going_up
    call self%generate_debug_message(going_up)
    call time_message(.false., self%time_init, 'Init')
    call self%change_level_specific(current, going_up)
    call time_message(.false., self%time_init, 'Init')
    if (going_up) then
       new_level = self%level
    else
       new_level = self%level - 1
    end if
  end function init_level_change_level

  !> Write the init times to <run_name>.init_times
  subroutine write_init_times()
    use mp, only: proc0
    use file_utils, only: open_output_file, close_output_file
    implicit none
    integer :: unit
    if (.not. proc0) return
    call open_output_file(unit, '.init_times')
    call report_init_times(unit)
    call close_output_file(unit)
  end subroutine write_init_times

  !> Report the time spent in each initialisation level
  subroutine report_init_times(unit)
    implicit none
    integer, intent(in), optional :: unit
    integer :: ilevel
    do ilevel = 1, size(init_levels)
       call init_levels(ilevel)%report_time(unit)
    end do
  end subroutine report_init_times

  !> Reset the time spent in each initialisation level
  subroutine reset_init_times()
    implicit none
    init_levels%time_init(1) = 0.
    init_levels%time_init(2) = 0.
  end subroutine reset_init_times

  !> Small wrapper to allow init_level_type to be passed
  !> instead of the level integer.
  subroutine init_pass_type(current, target_level)
    type(init_type), intent(inout) :: current
    type(init_level_type), intent(in) :: target_level
    call init(current, target_level%level)
  end subroutine init_pass_type

  !> Initialize gs2 to the level of target_level.
  !> The init_type current contains info
  !> about the current initialization level. At the end
  !> of the subroutine, current%level is set to target_level
  subroutine init_pass_int(current, target_level)
    use fields, only: init_fields
    use mp, only: mp_abort
    implicit none
    type(init_type), intent(inout) :: current
    integer, intent(in) :: target_level
    logical :: going_up
    integer :: ilevel, offset
    if (current%level .lt. init_level_list%basic) then
       call mp_abort("gs2_init::init cannot be called before &
            & initialize_gs2 in gs2 main", .true.)
    end if

    if (current%level .eq. target_level) then
       return
    else
       going_up = current%level < target_level

       if (going_up) then
          offset = 1
       else
          offset = 0
       end if

       ! Written as a while loop in this way such that we are not sensitive to the
       ! order of entries in the init_levels array.
       do while (current%level /= target_level)
          ilevel = findloc(init_levels%level, current%level + offset, dim = 1)
          current%level = init_levels(ilevel)%change_level(current, going_up)
       end do

    end if
  end subroutine init_pass_int

#include "gs2_init_subroutines.inc"

  !> Initialise this module. As we pass in the initialisation state
  !> object (current), we could/should consider making this set the
  !> level to basic, e.g. current%level = init_level_list%basic
  subroutine init_gs2_init
    implicit none
    if (initialized) return
    initialized = .true.
#include "gs2_init_level_array.inc"
  end subroutine init_gs2_init

  !> Finish this module
  subroutine finish_gs2_init()
    use run_parameters, only: save_init_times
    implicit none
    if (save_init_times) call write_init_times
    initialized = .false.
    if (allocated(init_levels)) deallocate(init_levels)
  end subroutine finish_gs2_init

  subroutine set_initial_field_and_dist_fn_values(current)
    use dist_fn_arrays, only: g, gnew, gexp_1, gexp_2, gexp_3
    use fields_arrays, only: phinew, aparnew, bparnew, phi, apar, bpar
    use fields, only: force_maxwell_reinit
    use fields, only: set_init_fields
    use file_utils, only: error_unit
    use init_g, only: ginit, init_vnmult
    use init_g, only: ginitopt_restart_many, initial_condition_is_nonadiabatic_dfn
    use run_parameters, only: has_phi, has_apar, has_bpar
    use collisions, only: set_vnmult
    use array_utils, only: copy, zero_array
    implicit none
    type (init_type), intent(in) :: current
    logical :: restarted
    real, dimension(2) :: new_vnmult
    if (.not. current%initval_ov%override) then
       ! This is the usual initial setup
       call ginit (restarted)
       ! If initial_condition_is_nonadiabatic_dfn then we have already
       ! calculated the correct fields, unless restarting, so return straight away.
       ! If restarting then we deal with this further below.
       if ((.not.restarted) .and. initial_condition_is_nonadiabatic_dfn) return
       ! If we're restarting from file then we don't want to recalculate
       ! the fields unless force_maxwell_reinit is true. If we are not
       ! restarting then we better call set_init_fields to set the initial
       ! fields here.
       if ((.not.restarted) .or. force_maxwell_reinit) call set_init_fields
       return
    else
       if (current%initval_ov%in_memory) then
          call copy(current%initval_ov%g, g)
          call copy(g, gnew)
          new_vnmult = current%initval_ov%vnmult
       else
          call ginit(restarted, ginitopt_restart_many)
          call init_vnmult(new_vnmult)
       end if
       call set_vnmult(new_vnmult)
    end if

    if (current%initval_ov%in_memory) then
       if (allocated(current%initval_ov%gexp_1)) call copy(current%initval_ov%gexp_1, gexp_1)
       if (allocated(current%initval_ov%gexp_1)) call copy(current%initval_ov%gexp_2, gexp_2)
       if (allocated(current%initval_ov%gexp_1)) call copy(current%initval_ov%gexp_3, gexp_3)
    end if

    ! Do not use the value from state%init%initval_ov%force_maxwell_reinit = current%initval_ov%force_maxwell_reinit as follows:
    !     if (current%initval_ov%force_maxwell_reinit)then
    ! as was done previously because, when restarting a run, this part of the overrides system has not been initialised with the
    ! value from the input file yet. As a result, the above condition is always true, even if the restart file has
    ! force_maxwell_reinit = .false.! (For a reinitialisation due to a timestep change, this part of the override system would be
    ! set up correctly and the above condition would respect the value in the input file.) Unfortunately, because of the way the
    ! state object and the overrides system is set up, it is not possible to have this value correctly initialised from the input
    ! file by this point in a restarted run. Therefore, use the input file value directly to ensure we respect the value in the
    ! input file at the start of restarted runs.
    if (force_maxwell_reinit)then
       call set_init_fields
    else

       if(current%initval_ov%override .and. current%initval_ov%in_memory) then
          if(has_phi) then
             call copy(current%initval_ov%phi, phinew)
          else
             call zero_array(phinew)
          endif
          if(has_apar) then
             call copy(current%initval_ov%apar, aparnew)
          else
             call zero_array(aparnew)
          endif
          if(has_bpar) then
             call copy(current%initval_ov%bpar, bparnew)
          else
             call zero_array(bparnew)
          endif
          call copy(phinew, phi)
          call copy(aparnew, apar)
          call copy(bparnew, bpar)
       else
          ! No need to do anything: fields read from file in
          ! [[gs2_save:gs2_restore_many]]
       end if
    end if
  end subroutine set_initial_field_and_dist_fn_values
end module gs2_init