MAPL_ESMF_InfoKeys.F90 Source File


This file depends on

sourcefile~~mapl_esmf_infokeys.f90~~EfferentGraph sourcefile~mapl_esmf_infokeys.f90 MAPL_ESMF_InfoKeys.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_esmf_infokeys.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~mapl_esmf_infokeys.f90~~AfferentGraph sourcefile~mapl_esmf_infokeys.f90 MAPL_ESMF_InfoKeys.F90 sourcefile~outputinfo.f90 OutputInfo.F90 sourcefile~outputinfo.f90->sourcefile~mapl_esmf_infokeys.f90 sourcefile~test_outputinfo.pf Test_OutputInfo.pf sourcefile~test_outputinfo.pf->sourcefile~mapl_esmf_infokeys.f90 sourcefile~test_outputinfo.pf->sourcefile~outputinfo.f90 sourcefile~generic3g.f90 Generic3g.F90 sourcefile~generic3g.f90->sourcefile~outputinfo.f90 sourcefile~historycollectiongridcomp_private.f90 HistoryCollectionGridComp_private.F90 sourcefile~historycollectiongridcomp_private.f90->sourcefile~outputinfo.f90 sourcefile~historycollectiongridcomp_private.f90->sourcefile~generic3g.f90 sourcefile~sharedio.f90 SharedIO.F90 sourcefile~sharedio.f90->sourcefile~outputinfo.f90 sourcefile~cap.f90 Cap.F90 sourcefile~cap.f90->sourcefile~generic3g.f90 sourcefile~capgridcomp.f90 CapGridComp.F90 sourcefile~cap.f90->sourcefile~capgridcomp.f90 sourcefile~capgridcomp.f90->sourcefile~generic3g.f90 sourcefile~configurableleafgridcomp.f90 ConfigurableLeafGridComp.F90 sourcefile~configurableleafgridcomp.f90->sourcefile~generic3g.f90 sourcefile~configurableparentgridcomp.f90 ConfigurableParentGridComp.F90 sourcefile~configurableparentgridcomp.f90->sourcefile~generic3g.f90 sourcefile~extdatagridcomp.f90 ExtDataGridComp.F90 sourcefile~extdatagridcomp.f90->sourcefile~generic3g.f90 sourcefile~geom_pfio.f90 Geom_PFIO.F90 sourcefile~geom_pfio.f90->sourcefile~sharedio.f90 sourcefile~geomio.f90 GeomIO.F90 sourcefile~geomio.f90->sourcefile~sharedio.f90 sourcefile~geomio.f90->sourcefile~geom_pfio.f90 sourcefile~grid_pfio.f90 Grid_PFIO.F90 sourcefile~grid_pfio.f90->sourcefile~sharedio.f90 sourcefile~grid_pfio.f90->sourcefile~geom_pfio.f90 sourcefile~historycollectiongridcomp.f90 HistoryCollectionGridComp.F90 sourcefile~historycollectiongridcomp.f90->sourcefile~generic3g.f90 sourcefile~historycollectiongridcomp.f90->sourcefile~historycollectiongridcomp_private.f90 sourcefile~historycollectiongridcomp.f90->sourcefile~geomio.f90 sourcefile~historygridcomp.f90 HistoryGridComp.F90 sourcefile~historygridcomp.f90->sourcefile~generic3g.f90 sourcefile~historygridcomp.f90->sourcefile~historycollectiongridcomp.f90 sourcefile~mapl3g.f90 mapl3g.F90 sourcefile~mapl3g.f90->sourcefile~generic3g.f90 sourcefile~mapl3g.f90->sourcefile~cap.f90 sourcefile~restarthandler.f90 RestartHandler.F90 sourcefile~restarthandler.f90->sourcefile~sharedio.f90 sourcefile~restarthandler.f90->sourcefile~geomio.f90 sourcefile~test_extdatagridcomp.pf Test_ExtDataGridComp.pf sourcefile~test_extdatagridcomp.pf->sourcefile~generic3g.f90 sourcefile~test_historycollectiongridcomp.pf Test_HistoryCollectionGridComp.pf sourcefile~test_historycollectiongridcomp.pf->sourcefile~historycollectiongridcomp_private.f90 sourcefile~test_historygridcomp.pf Test_HistoryGridComp.pf sourcefile~test_historygridcomp.pf->sourcefile~generic3g.f90 sourcefile~test_sharedio.pf Test_SharedIO.pf sourcefile~test_sharedio.pf->sourcefile~sharedio.f90 sourcefile~geomcatagorizer.f90 GeomCatagorizer.F90 sourcefile~geomcatagorizer.f90->sourcefile~geom_pfio.f90 sourcefile~geomcatagorizer.f90->sourcefile~grid_pfio.f90 sourcefile~geos.f90 GEOS.F90 sourcefile~geos.f90->sourcefile~mapl3g.f90 sourcefile~read_restart.f90~2 read_restart.F90 sourcefile~read_restart.f90~2->sourcefile~restarthandler.f90 sourcefile~write_restart.f90~2 write_restart.F90 sourcefile~write_restart.f90~2->sourcefile~restarthandler.f90

Source Code

#include "MAPL_Exceptions.h"
module mapl3g_esmf_info_keys

   use MAPL_ErrorHandling

   implicit none

   public :: KEY_UNGRIDDED_DIMS
   public :: KEY_VERT_DIM
   public :: KEY_VERT_GEOM
   public :: KEY_UNITS
   public :: KEY_LONG_NAME
   public :: KEY_STANDARD_NAME
   public :: KEY_NUM_LEVELS
   public :: KEY_VLOC
   public :: KEY_NUM_UNGRID_DIMS
   public :: KEYSTUB_DIM
   public :: KEY_UNGRIDDED_NAME
   public :: KEY_UNGRIDDED_UNITS
   public :: KEY_UNGRIDDED_COORD
   public :: KEY_DIM_STRINGS
   public :: make_dim_key
   private

   ! FieldSpec info keys
   character(len=*), parameter :: PREFIX = 'MAPL/'
   character(len=*), parameter :: KEY_UNGRIDDED_DIMS = PREFIX // 'ungridded_dims/'
   character(len=*), parameter :: KEY_VERT_DIM = PREFIX // 'vertical_dim/'
   character(len=*), parameter :: KEY_VERT_GEOM = PREFIX // 'vertical_geom/'
   character(len=*), parameter :: KEY_UNITS = PREFIX // 'units'
   character(len=*), parameter :: KEY_LONG_NAME = PREFIX // 'long_name'
   character(len=*), parameter :: KEY_STANDARD_NAME = PREFIX // 'standard_name'

   ! VerticalGeom info keys
   character(len=*), parameter :: KEY_NUM_LEVELS = KEY_VERT_GEOM // 'num_levels'

   ! VerticalDimSpec info keys
   character(len=*), parameter :: KEY_VLOC = KEY_VERT_DIM // 'vloc'

   ! UngriddedDims info keys
   character(len=*), parameter :: KEY_NUM_UNGRID_DIMS = KEY_UNGRIDDED_DIMS // 'num_ungridded_dimensions'
   character(len=*), parameter :: KEYSTUB_DIM = KEY_UNGRIDDED_DIMS // 'dim_'

   ! UngriddedDim info keys
   character(len=*), parameter :: KEY_UNGRIDDED_NAME = 'name'
   character(len=*), parameter :: KEY_UNGRIDDED_UNITS = 'units'
   character(len=*), parameter :: KEY_UNGRIDDED_COORD = 'coordinates'

   character(len=*), parameter :: KEY_DIM_STRINGS(9) = [ &
      KEYSTUB_DIM // '1', KEYSTUB_DIM // '2', KEYSTUB_DIM // '3', &
      KEYSTUB_DIM // '4', KEYSTUB_DIM // '5', KEYSTUB_DIM // '6', &
      KEYSTUB_DIM // '7', KEYSTUB_DIM // '8', KEYSTUB_DIM // '9']

contains

   function make_dim_key(n, rc) result(key)
      character(len=:), allocatable :: key
      integer, intent(in) :: n
      integer, optional, intent(out) :: rc
      integer :: status
      character(len=32) :: raw

      key = ''
      _ASSERT(n > 0, 'Index must be positive.')
      if(n <= size(KEY_DIM_STRINGS)) then
         key = KEY_DIM_STRINGS(n)
         _RETURN(_SUCCESS)
      end if
      write(raw, fmt='(I0)', iostat=status) n
      _ASSERT(status == 0, 'Write failed')
      key = KEYSTUB_DIM // trim(raw)
      _RETURN(_SUCCESS)

   end function make_dim_key

end module mapl3g_esmf_info_keys