MAPL_Range.F90 Source File


This file depends on

sourcefile~~mapl_range.f90~~EfferentGraph sourcefile~mapl_range.f90 MAPL_Range.F90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~mapl_range.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~mapl_range.f90~~AfferentGraph sourcefile~mapl_range.f90 MAPL_Range.F90 sourcefile~base_base.f90 Base_Base.F90 sourcefile~base_base.f90->sourcefile~mapl_range.f90 sourcefile~base_base_implementation.f90 Base_Base_implementation.F90 sourcefile~base_base_implementation.f90->sourcefile~mapl_range.f90 sourcefile~coordinateaxis.f90 CoordinateAxis.F90 sourcefile~coordinateaxis.f90->sourcefile~mapl_range.f90 sourcefile~cub2latlon_regridder.f90 cub2latlon_regridder.F90 sourcefile~cub2latlon_regridder.f90->sourcefile~mapl_range.f90 sourcefile~cubedspheregeomspec_smod.f90 CubedSphereGeomSpec_smod.F90 sourcefile~cubedspheregeomspec_smod.f90->sourcefile~mapl_range.f90 sourcefile~equal_to.f90~2 equal_to.F90 sourcefile~equal_to.f90~2->sourcefile~mapl_range.f90 sourcefile~fix_bad_pole.f90 fix_bad_pole.F90 sourcefile~fix_bad_pole.f90->sourcefile~mapl_range.f90 sourcefile~get_lat_corners.f90 get_lat_corners.F90 sourcefile~get_lat_corners.f90->sourcefile~mapl_range.f90 sourcefile~get_lat_range.f90 get_lat_range.F90 sourcefile~get_lat_range.f90->sourcefile~mapl_range.f90 sourcefile~get_lon_corners.f90 get_lon_corners.F90 sourcefile~get_lon_corners.f90->sourcefile~mapl_range.f90 sourcefile~get_lon_range.f90 get_lon_range.F90 sourcefile~get_lon_range.f90->sourcefile~mapl_range.f90 sourcefile~make_decomposition.f90 make_decomposition.F90 sourcefile~make_decomposition.f90->sourcefile~mapl_range.f90 sourcefile~make_distribution.f90 make_distribution.F90 sourcefile~make_distribution.f90->sourcefile~mapl_range.f90 sourcefile~make_lataxis_from_hconfig.f90 make_LatAxis_from_hconfig.F90 sourcefile~make_lataxis_from_hconfig.f90->sourcefile~mapl_range.f90 sourcefile~make_lataxis_from_metadata.f90 make_lataxis_from_metadata.F90 sourcefile~make_lataxis_from_metadata.f90->sourcefile~mapl_range.f90 sourcefile~make_latlongeomspec_from_hconfig.f90 make_LatLonGeomSpec_from_hconfig.F90 sourcefile~make_latlongeomspec_from_hconfig.f90->sourcefile~mapl_range.f90 sourcefile~make_latlongeomspec_from_metadata.f90 make_LatLonGeomSpec_from_metadata.F90 sourcefile~make_latlongeomspec_from_metadata.f90->sourcefile~mapl_range.f90 sourcefile~make_lonaxis_from_hconfig.f90 make_LonAxis_from_hconfig.F90 sourcefile~make_lonaxis_from_hconfig.f90->sourcefile~mapl_range.f90 sourcefile~make_lonaxis_from_metadata.f90 make_LonAxis_from_metadata.F90 sourcefile~make_lonaxis_from_metadata.f90->sourcefile~mapl_range.f90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~maplshared.f90->sourcefile~mapl_range.f90 sourcefile~supports_hconfig.f90 supports_hconfig.F90 sourcefile~supports_hconfig.f90->sourcefile~mapl_range.f90 sourcefile~supports_hconfig.f90~2 supports_hconfig.F90 sourcefile~supports_hconfig.f90~2->sourcefile~mapl_range.f90 sourcefile~supports_hconfig.f90~3 supports_hconfig.F90 sourcefile~supports_hconfig.f90~3->sourcefile~mapl_range.f90 sourcefile~supports_metadata.f90 supports_metadata.F90 sourcefile~supports_metadata.f90->sourcefile~mapl_range.f90 sourcefile~supports_metadata.f90~2 supports_metadata.F90 sourcefile~supports_metadata.f90~2->sourcefile~mapl_range.f90 sourcefile~supports_metadata.f90~3 supports_metadata.F90 sourcefile~supports_metadata.f90~3->sourcefile~mapl_range.f90

Source Code

#include "MAPL_ErrLog.h"
#include "unused_dummy.H"

module MAPL_RangeMod
  use, intrinsic :: iso_fortran_env, only: REAL32
  use, intrinsic :: iso_fortran_env, only: REAL64
  use MAPL_ExceptionHandling
  implicit none
  private

  public :: MAPL_Range

  interface MAPL_Range
    module procedure MAPL_Range_REAL64
    module procedure MAPL_Range_REAL32
  end interface

contains

  ! Analog of range() procedure in Python for constructing
  ! an arithmetic sequence of values.  Introducing
  ! into MAPL to enforce consistent roundoff within
  ! various parts of the model that generate lat and lon
  ! coordinates.

  function MAPL_Range_REAL64(x0, x1, n, conversion_factor,rc) result(range)
     real(kind=REAL64), allocatable :: range(:)
     real(kind=REAL64), intent(in) :: x0
     real(kind=REAL64), intent(in) :: x1
     integer, intent(in) :: n
     real(kind=REAL64), optional, intent(in) :: conversion_factor
     integer, optional, intent(out) :: rc

     integer :: i
     real(kind=REAL64) :: delta

     _ASSERT(((n /= 1) .or. (x0 == x1)),'needs informative message')
     allocate(range(n))
     
     range(1) = x0
     range(n) = x1

     if (n > 1) then
        delta = (x1 - x0)/(n-1)
        do i = 2, n-1
           range(i) = x0 + (i-1)*delta
        end do
     end if

     if (present(conversion_factor)) then
        range = range * conversion_factor
     end if

     _RETURN(_SUCCESS)
        
  end function MAPL_Range_REAL64

  function MAPL_Range_REAL32(x0, x1, n, conversion_factor,rc) result(range)
     real(kind=REAL64), allocatable :: range(:)
     real(kind=REAL32), intent(in) :: x0
     real(kind=REAL32), intent(in) :: x1
     integer, intent(in) :: n
     real(kind=REAL64), optional, intent(in) :: conversion_factor
     integer, optional, intent(out) :: rc

     integer :: i
     real(kind=REAL64) :: delta

     _ASSERT((n /= 1) .or. (x0 == x1),'needs informative message')
     allocate(range(n))
     
     range(1) = x0
     range(n) = x1

     if (n > 1) then
        delta = real(x1 - x0,REAL64)/(n-1)
        do i = 2, n-1
           range(i) = x0 + (i-1)*delta
        end do
     end if

     if (present(conversion_factor)) then
        range = range * conversion_factor
     end if

     _RETURN(_SUCCESS)
        
  end function MAPL_Range_REAL32

end module MAPL_RangeMod