normalisations.f90 Source File


Contents

Source Code


Source Code

!> FIXME : Add documentation
module normalisations
  use abstract_config, only: abstract_config_type, CONFIG_MAX_NAME_LEN
  
  implicit none
  
  private

  public :: norms, init_normalisations, finish_normalisations, check_normalisations

  public :: normalisations_config_type
  public :: set_normalisations_config
  public :: get_normalisations_config
  
  real, parameter :: default_value = -999.0
  
  !> Define a type to hold the set of normalisations, we
  !> could imagine extending this in the future to provide
  !> a normalise/denormalise routine which can be used to
  !> automatically convert quantities
  type norms_type
     private
     !Internal parameters
     real :: def_val = default_value !Default value, used to check if parameter has been set.

     !Note def_val is really a parameter, but not allowed to define params in derived type
     logical :: some_norms_set=.false.
     logical :: all_norms_set=.false.
     logical :: initialised = .false.

     !The following is used to help automate loops over normalisations
     integer :: nnorm
     character(len=6), dimension(:), allocatable, public :: names

     !The normalisations
     real :: mref !< Reference mass in atomic mass units
     real :: zref !< Reference charge in units of the elementary charge
     real :: nref !< Reference density in \(m^{-3}\)
     real :: tref !< Reference temperature in \(eV\)
     real :: aref !< Reference length in \(m\)
     real :: vref !< Reference (thermal) velocity in \(m/s\)
     real :: bref !< Reference magnetic field in Tesla, \(T\)
     real :: rhoref !< Reference Larmor radius in \(m\)
   contains
     private
     procedure, public :: init => norms_init
     procedure, public :: finish => norms_finish
     procedure, public :: reset => norms_reset
     procedure :: read_parameters => norms_read_parameters
     procedure :: set_value => norms_set_value
     procedure, public :: get_value => norms_get_value
     procedure :: check_if_set => norms_check_if_set
     procedure :: set_logicals => norms_set_logicals
  end type norms_type

  type(norms_type) :: norms !The normalisation object, there should only be one of these
  logical :: initialized = .false. !Have we setup the module yet?

  !> Used to represent the input configuration of
  !> normalisations. These values are not used for anything but will
  !> be written to the output file to aid post processing etc.
  type, extends(abstract_config_type) :: normalisations_config_type
     ! namelist : normalisations_knobs
     !> Reference length in \(m\)
     real :: aref = default_value
     !> Reference magnetic field in \(T\)
     real :: bref = default_value
     !> Reference mass in atomic mass units
     real :: mref = default_value
     !> Reference density in \(m^{-3}\)
     real :: nref = default_value
     !> Reference Larmor radius in \(m\)
     real :: rhoref = default_value
     !> Reference temperature in \(eV\)
     real :: tref = default_value
     !> Reference (thermal) velocity in \(m/s\)
     real :: vref = default_value
     !> Reference charge in units of the elementary charge
     real :: zref = default_value
   contains
     procedure, public :: read => read_normalisations_config
     procedure, public :: write => write_normalisations_config
     procedure, public :: reset => reset_normalisations_config
     procedure, public :: broadcast => broadcast_normalisations_config
     procedure, public, nopass :: get_default_name => get_default_name_normalisations_config
     procedure, public, nopass :: get_default_requires_index => get_default_requires_index_normalisations_config
  end type normalisations_config_type
  
  type(normalisations_config_type) :: normalisations_config  
contains
  !/////////////////////////////
  !// TYPE BOUND PROCEDURES
  !/////////////////////////////

  !> Sets the value of a particular normalisation, determined by the
  !> passed `val_name` string. Unknown `val_name` values result in a
  !> warning message on `proc0`.
  subroutine norms_set_value(self, val_name, val)
    use runtime_tests, only: verbosity
    use mp, only: proc0
    use warning_helpers, only: exactly_equal
    implicit none
    class(norms_type), intent(in out) :: self
    character(len=*), intent(in) :: val_name
    real, intent(in) :: val
    
    !Here we can have a message in very verbose runs
    if ((verbosity()>5) .and. proc0) then
       if (exactly_equal(val, self%def_val)) then
          write(6,'("The ",A," normalisation has not been set. This may prevent conversion of some quantities.")') trim(val_name)
       else
          write(6,'("Setting the ",A," normalisation to ",F12.5)') trim(val_name), val
       end if
    end if

    !Should probably convert to lower case here, but until we
    !add some string utils to do this sort of stuff we'll rely
    !on developer doing the right thing.
    select case (trim(val_name))
    case("mref")
       self%mref=val
    case("zref")
       self%zref=val
    case("nref")
       self%nref=val
    case("tref")
       self%tref=val
    case("aref")
       self%aref=val
    case("vref")
       self%vref=val
    case("bref")
       self%bref=val
    case("rhoref")
       self%rhoref=val
    case default
       if(proc0) write(6,'("Warning : Attempt to set unknown normalisation ",A," --> Ignoring")')
    end select
  end subroutine norms_set_value

  !> Get the value of the normalisation associated with `val_name`.
  !> Unknown values of `val_name` result in a call to `mp_abort`.
  function norms_get_value(self, val_name)
    use mp, only: mp_abort
    implicit none
    class(norms_type), intent(in) :: self
    character(len=*), intent(in) :: val_name
    real :: norms_get_value

    !Should probably convert to lower case here, but until we
    !add some string utils to do this sort of stuff we'll rely
    !on developer doing the right thing.
    select case (trim(val_name))
    case("mref")
       norms_get_value=self%mref
    case("zref")
       norms_get_value=self%zref
    case("nref")
       norms_get_value=self%nref
    case("tref")
       norms_get_value=self%tref
    case("aref")
       norms_get_value=self%aref
    case("vref")
       norms_get_value=self%vref
    case("bref")
       norms_get_value=self%bref
    case("rhoref")
       norms_get_value=self%rhoref
    case default
      call mp_abort("Invalid normalisation requested")
    end select
  end function norms_get_value

  !> FIXME : Add documentation  
  subroutine norms_read_parameters(self, normalisations_config_in)
    implicit none
    class(norms_type), intent(in out) :: self
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
    real :: mref,zref,nref,tref,aref,vref,bref,rhoref

    if (present(normalisations_config_in)) normalisations_config = normalisations_config_in

    call normalisations_config%init(name = 'normalisations_knobs', requires_index = .false.)

    ! Copy out internal values into module level parameters
    associate(self => normalisations_config)
#include "normalisations_copy_out_auto_gen.inc"
    end associate

    !Now copy parameters into holder type
    call self%set_value("mref",mref)
    call self%set_value("zref",zref)
    call self%set_value("nref",nref)
    call self%set_value("tref",tref)
    call self%set_value("aref",aref)
    call self%set_value("vref",vref)
    call self%set_value("bref",bref)
    call self%set_value("rhoref",rhoref)
  end subroutine norms_read_parameters

  !> Initialise the norms object
  subroutine norms_init(self, normalisations_config_in)
    implicit none
    class(norms_type), intent(in out) :: self
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in

    !First setup allowed normalisations
    self%nnorm=8
    if(.not.allocated(self%names)) allocate(self%names(self%nnorm))
    self%names(1)="mref"
    self%names(2)="zref"
    self%names(3)="nref"
    self%names(4)="tref"
    self%names(5)="aref"
    self%names(6)="vref"
    self%names(7)="bref"
    self%names(8)="rhoref"

    if(self%initialised) return
    self%initialised = .true.

    call self%read_parameters(normalisations_config_in)
  end subroutine norms_init

  !> Reset the properties
  subroutine norms_reset(self)
    implicit none
    class(norms_type), intent(in out) :: self
    integer :: i
    
    !Loop over parameters and set them to def_val
    do i=1,len(self%names)
       call self%set_value(self%names(i),self%def_val)
    enddo

    !Set the logical vars
    self%initialised=.false.
    call self%set_logicals
  end subroutine norms_reset

  !> Reset and free memory
  subroutine norms_finish(self)
    implicit none
    class(norms_type), intent(in out) :: self
    call self%reset
    if(allocated(self%names)) deallocate(self%names)
  end subroutine norms_finish

  !> Decide if a given normalisation has been set
  function norms_check_if_set(self,val_name)
    use warning_helpers, only: not_exactly_equal
    implicit none
    class(norms_type), intent(in) :: self
    character(len=*), intent(in) :: val_name
    logical :: norms_check_if_set
    norms_check_if_set = not_exactly_equal(self%get_value(val_name), self%def_val)
  end function norms_check_if_set

  !> Decide if all/some of the normalisations have been set
  subroutine norms_set_logicals(self)
    implicit none
    class(norms_type), intent(in out) :: self
    integer :: i
    logical :: some_set, all_set

    !Init internals
    some_set=.false.
    all_set=.true.

    !Loop over parameters and set them to def_val
    do i=1,len(self%names)
       all_set=all_set.and.self%check_if_set(self%names(i))
       some_set=some_set.or.self%check_if_set(self%names(i))
    enddo

    !Update object parameters
    self%some_norms_set=some_set
    self%all_norms_set=all_set
  end subroutine norms_set_logicals

  !/////////////////////////////
  !// MODULE LEVEL PROCDURES
  !/////////////////////////////
  
  !> FIXME : Add documentation
  subroutine check_normalisations(report_unit)
    implicit none
    integer, intent(in) :: report_unit
    character(len=7) :: msg
    if(norms%all_norms_set)then
       msg = "All of"
    else
       if(norms%some_norms_set)then
          msg = "Some of"
       else
          msg = "None of"
       endif
    endif

    write(report_unit,fmt='(A," the normalisation parameters have been provided.")') trim(msg)
  end subroutine check_normalisations

  !> Read input file and populate the norms object
  subroutine init_normalisations(normalisations_config_in)
    implicit none
    type(normalisations_config_type), intent(in), optional :: normalisations_config_in
    if(initialized) return
    initialized = .true.
    call norms%init(normalisations_config_in)
  end subroutine init_normalisations

  !> Free memory etc. associated with normalisations
  subroutine finish_normalisations
    implicit none
    initialized = .false.
    call norms%finish
    call normalisations_config%reset()
  end subroutine finish_normalisations

#include "normalisations_auto_gen.inc"
end module normalisations