FieldUnits.F90 Source File


This file depends on

sourcefile~~fieldunits.f90~~EfferentGraph sourcefile~fieldunits.f90 FieldUnits.F90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~fieldunits.f90->sourcefile~maplshared.f90 sourcefile~udunits2f.f90 udunits2f.F90 sourcefile~fieldunits.f90->sourcefile~udunits2f.f90 sourcefile~abstractcommsplitter.f90 AbstractCommSplitter.F90 sourcefile~maplshared.f90->sourcefile~abstractcommsplitter.f90 sourcefile~commgroupdescription.f90 CommGroupDescription.F90 sourcefile~maplshared.f90->sourcefile~commgroupdescription.f90 sourcefile~constants.f90 Constants.F90 sourcefile~maplshared.f90->sourcefile~constants.f90 sourcefile~downbit.f90 DownBit.F90 sourcefile~maplshared.f90->sourcefile~downbit.f90 sourcefile~dso_utilities.f90 DSO_Utilities.F90 sourcefile~maplshared.f90->sourcefile~dso_utilities.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~maplshared.f90->sourcefile~errorhandling.f90 sourcefile~filesystemutilities.f90 FileSystemUtilities.F90 sourcefile~maplshared.f90->sourcefile~filesystemutilities.f90 sourcefile~interp.f90 Interp.F90 sourcefile~maplshared.f90->sourcefile~interp.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~maplshared.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_dirpath.f90 MAPL_DirPath.F90 sourcefile~maplshared.f90->sourcefile~mapl_dirpath.f90 sourcefile~mapl_hash.f90 MAPL_Hash.F90 sourcefile~maplshared.f90->sourcefile~mapl_hash.f90 sourcefile~mapl_loadbalance.f90 MAPL_LoadBalance.F90 sourcefile~maplshared.f90->sourcefile~mapl_loadbalance.f90 sourcefile~mapl_minmax.f90 MAPL_MinMax.F90 sourcefile~maplshared.f90->sourcefile~mapl_minmax.f90 sourcefile~mapl_range.f90 MAPL_Range.F90 sourcefile~maplshared.f90->sourcefile~mapl_range.f90 sourcefile~mapl_sleep.f90 MAPL_Sleep.F90 sourcefile~maplshared.f90->sourcefile~mapl_sleep.f90 sourcefile~mapl_sort.f90 MAPL_Sort.F90 sourcefile~maplshared.f90->sourcefile~mapl_sort.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~maplshared.f90->sourcefile~mapl_throw.f90 sourcefile~shmem.f90 Shmem.F90 sourcefile~maplshared.f90->sourcefile~shmem.f90 sourcefile~simplecommsplitter.f90 SimpleCommSplitter.F90 sourcefile~maplshared.f90->sourcefile~simplecommsplitter.f90 sourcefile~splitcommunicator.f90 SplitCommunicator.F90 sourcefile~maplshared.f90->sourcefile~splitcommunicator.f90 sourcefile~string.f90 String.F90 sourcefile~maplshared.f90->sourcefile~string.f90 sourcefile~interfaces.f90 interfaces.F90 sourcefile~udunits2f.f90->sourcefile~interfaces.f90 sourcefile~status_codes.f90 status_codes.F90 sourcefile~udunits2f.f90->sourcefile~status_codes.f90 sourcefile~udsystem.f90 UDSystem.F90 sourcefile~udunits2f.f90->sourcefile~udsystem.f90 sourcefile~commgroupdescription.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~commgroupdescription.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~internalconstants.f90 InternalConstants.F90 sourcefile~constants.f90->sourcefile~internalconstants.f90 sourcefile~mathconstants.f90 MathConstants.F90 sourcefile~constants.f90->sourcefile~mathconstants.f90 sourcefile~physicalconstants.f90 PhysicalConstants.F90 sourcefile~constants.f90->sourcefile~physicalconstants.f90 sourcefile~downbit.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~dso_utilities.f90->sourcefile~filesystemutilities.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~interfaces.f90->sourcefile~status_codes.f90 sourcefile~mapl_dirpath.f90->sourcefile~constants.f90 sourcefile~mapl_dirpath.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_hash.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_loadbalance.f90->sourcefile~constants.f90 sourcefile~mapl_loadbalance.f90->sourcefile~mapl_sort.f90 sourcefile~mapl_loadbalance.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_range.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_sort.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~shmem.f90->sourcefile~constants.f90 sourcefile~simplecommsplitter.f90->sourcefile~abstractcommsplitter.f90 sourcefile~simplecommsplitter.f90->sourcefile~commgroupdescription.f90 sourcefile~simplecommsplitter.f90->sourcefile~keywordenforcer.f90 sourcefile~simplecommsplitter.f90->sourcefile~splitcommunicator.f90 sourcefile~simplecommsplitter.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~udsystem.f90->sourcefile~interfaces.f90 sourcefile~udsystem.f90->sourcefile~status_codes.f90 sourcefile~cptrwrapper.f90 CptrWrapper.F90 sourcefile~udsystem.f90->sourcefile~cptrwrapper.f90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~physicalconstants.f90->sourcefile~mathconstants.f90

Source Code

! Retrieve unit converter using udunits2, and use it to convert values.
! x and y are scalar or array variables of type(c_double) or type(c_float).

! The sequence is:
!     call InitializeFieldUnits(path, encoding, rc)
!     ...
!     call GetFieldUnitsConverter(from1, to1, conv1, rc)
!     call GetFieldUnitsConverter(from2, to2, conv2, rc)
!     ...
!     y1 = conv1 % convert(x1)
!     ...
!     y2 = conv2 % convert(x2)
!     ...
!     call conv1 % free()
!     ...
!     call conv2 % free()
!     ...
!     call FinalizeFieldUnits()

! InitializeFieldUnits must be called first, and FinalizeFieldUnits must be called last.
! InitializeFieldUnits and FinalizeFieldUnits are called once, before and after,
! respectively, all GetFieldUnitsConverter and conv % convert calls.

! For a given FieldUnitsConverter, GetFieldUnitsConverter and conv % convert
! cannot be called before InitializeFieldUnits or after FinalizeFieldUnits
! and conv % convert cannot be called before calling GetFieldUnitsConverter for conv.
#include "MAPL_Generic.h"
#include "unused_dummy.H"
module mapl_FieldUnits
   use udunits2f, FieldUnitsConverter => Converter, &
      initialize_udunits => initialize, finalize_udunits => finalize
   use MaplShared
   use ESMF

   implicit none

   public :: FieldUnitsConverter
   public :: GetFieldUnitsConverter
   public :: InitializeFieldUnits
   public :: FinalizeFieldUnits

   private 

contains
    
   ! Possible values for encoding are found in udunits2encoding.
   ! The default, UT_ENCODING_DEFAULT is used if encoding is not provided.
   ! If no path is given, the default path to the units database is used.
   subroutine InitializeFieldUnits(path, encoding, rc)
      character(len=*), optional, intent(in) :: path
      integer(ut_encoding), optional, intent(in) :: encoding
      integer, optional, intent(out) :: rc
      integer :: status

      call initialize_udunits(path, encoding, _RC)
      _RETURN(_SUCCESS)
      
   end subroutine InitializeFieldUnits

   ! Get converter to convert quantities from one unit to a different unit
   ! from_identifier and to_identifier are strings for unit names or symbols
   ! in the udunits2 database.
   subroutine GetFieldUnitsConverter(from_identifier, to_identifier, conv, unusable, rc)
      character(len=*), intent(in) :: from_identifier, to_identifier
      type(FieldUnitsConverter), intent(out) :: conv
      class(KeywordEnforcer), optional, intent(in) :: unusable
      integer, optional, intent(out) :: rc
      integer :: status

      _UNUSED_DUMMY(unusable)
      call get_converter(conv, from_identifier, to_identifier, _RC)
      _RETURN(_SUCCESS)

   end subroutine GetFieldUnitsConverter

   ! Free up memory for units system
   subroutine FinalizeFieldUnits()

      call finalize_udunits()

   end subroutine FinalizeFieldUnits

 end module mapl_FieldUnits