MirrorVerticalGrid.F90 Source File


This file depends on

sourcefile~~mirrorverticalgrid.f90~~EfferentGraph sourcefile~mirrorverticalgrid.f90 MirrorVerticalGrid.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mirrorverticalgrid.f90->sourcefile~errorhandling.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~mirrorverticalgrid.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~mirrorverticalgrid.f90->sourcefile~verticalgrid.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~griddedcomponentdriver.f90->sourcefile~errorhandling.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~griddedcomponentdriver.f90->sourcefile~componentdriver.f90 sourcefile~componentdrivervector.f90 ComponentDriverVector.F90 sourcefile~griddedcomponentdriver.f90->sourcefile~componentdrivervector.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~griddedcomponentdriver.f90->sourcefile~keywordenforcer.f90 sourcefile~multistate.f90 MultiState.F90 sourcefile~griddedcomponentdriver.f90->sourcefile~multistate.f90 sourcefile~verticalgrid.f90->sourcefile~errorhandling.f90 sourcefile~componentdriver.f90->sourcefile~errorhandling.f90 sourcefile~componentdriver.f90->sourcefile~multistate.f90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~componentdriver.f90->sourcefile~maplshared.f90 sourcefile~componentdrivervector.f90->sourcefile~componentdriver.f90 sourcefile~multistate.f90->sourcefile~errorhandling.f90 sourcefile~multistate.f90->sourcefile~keywordenforcer.f90 sourcefile~esmf_utilities.f90 ESMF_Utilities.F90 sourcefile~multistate.f90->sourcefile~esmf_utilities.f90 sourcefile~esmf_utilities.f90->sourcefile~errorhandling.f90 sourcefile~maplshared.f90->sourcefile~errorhandling.f90 sourcefile~maplshared.f90->sourcefile~keywordenforcer.f90 sourcefile~maplshared.f90->sourcefile~mapl_throw.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~filesystemutilities.f90 FileSystemUtilities.F90 sourcefile~maplshared.f90->sourcefile~filesystemutilities.f90 sourcefile~interp.f90 Interp.F90 sourcefile~maplshared.f90->sourcefile~interp.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~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

Files dependent on this one

sourcefile~~mirrorverticalgrid.f90~~AfferentGraph sourcefile~mirrorverticalgrid.f90 MirrorVerticalGrid.F90 sourcefile~can_connect_to.f90 can_connect_to.F90 sourcefile~can_connect_to.f90->sourcefile~mirrorverticalgrid.f90 sourcefile~can_connect_to.f90~2 can_connect_to.F90 sourcefile~can_connect_to.f90~2->sourcefile~mirrorverticalgrid.f90 sourcefile~can_connect_to.f90~3 can_connect_to.F90 sourcefile~can_connect_to.f90~3->sourcefile~mirrorverticalgrid.f90

Source Code

#include "MAPL_Generic.h"

! MirrorVerticalGrid objects should always have been replaced with an
! object of a different subclass by the timet they are used.  As such,
! it should only be used with import stateIntent, and will be replaced
! by whatever source grid is connected to it.

module mapl3g_MirrorVerticalGrid
   use mapl3g_VerticalGrid
   use mapl3g_GriddedComponentDriver
   use mapl_ErrorHandling
   use esmf, only: ESMF_TypeKind_Flag
   use esmf, only: ESMF_Field
   use esmf, only: ESMF_Geom
   implicit none
   private
   public :: MirrorVerticalGrid

   type, extends(VerticalGrid) :: MirrorVerticalGrid
      private
   contains
      procedure :: get_num_levels
      procedure :: get_coordinate_field
      procedure :: can_connect_to
   end type MirrorVerticalGrid

   interface MirrorVerticalGrid
      module procedure new_MirrorVerticalGrid
   end interface MirrorVerticalGrid

contains

   function new_MirrorVerticalGrid() result(vertical_grid)
      type(MirrorVerticalGrid) :: vertical_grid
   end function

   function get_num_levels(this) result(num_levels)
      integer :: num_levels
      class(MirrorVerticalGrid), intent(in) :: this
      num_levels = -1
      _UNUSED_DUMMY(this)
   end function
      
   subroutine get_coordinate_field(this, field, coupler, standard_name, geom, typekind, units, rc)
      class(MirrorVerticalGrid), intent(in) :: this
      type(ESMF_Field), intent(out) :: field
      type(GriddedComponentDriver), pointer, intent(out) :: coupler
      character(*), intent(in) :: standard_name
      type(ESMF_Geom), intent(in) :: geom
      type(ESMF_TypeKind_Flag), intent(in) :: typekind
      character(*), intent(in) :: units
      integer, optional, intent(out) :: rc

      _FAIL('MirrorVerticalGrid should have been replaced before this procedure was called.')
 
        _UNUSED_DUMMY(this)
       _UNUSED_DUMMY(field)
       _UNUSED_DUMMY(coupler)
       _UNUSED_DUMMY(standard_name)
       _UNUSED_DUMMY(geom)
       _UNUSED_DUMMY(typekind)
       _UNUSED_DUMMY(units)
 end subroutine get_coordinate_field

   logical function can_connect_to(this, src, rc)
      class(MirrorVerticalGrid), intent(in) :: this
      class(VerticalGrid), intent(in) :: src
      integer, optional, intent(out) :: rc

      can_connect_to = .false.
      _RETURN(_SUCCESS)

       _UNUSED_DUMMY(this)
       _UNUSED_DUMMY(src)
   end function

end module mapl3g_MirrorVerticalGrid