VerticalRegridMethod.F90 Source File


Files dependent on this one

sourcefile~~verticalregridmethod.f90~~AfferentGraph sourcefile~verticalregridmethod.f90 VerticalRegridMethod.F90 sourcefile~fieldspec.f90 FieldSpec.F90 sourcefile~fieldspec.f90->sourcefile~verticalregridmethod.f90 sourcefile~verticalregridaction.f90 VerticalRegridAction.F90 sourcefile~fieldspec.f90->sourcefile~verticalregridaction.f90 sourcefile~verticalregridaction.f90->sourcefile~verticalregridmethod.f90 sourcefile~bracketspec.f90 BracketSpec.F90 sourcefile~bracketspec.f90->sourcefile~fieldspec.f90 sourcefile~couplermetacomponent.f90 CouplerMetaComponent.F90 sourcefile~couplermetacomponent.f90->sourcefile~verticalregridaction.f90 sourcefile~genericcoupler.f90 GenericCoupler.F90 sourcefile~genericcoupler.f90->sourcefile~verticalregridaction.f90 sourcefile~genericcoupler.f90->sourcefile~couplermetacomponent.f90 sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~make_itemspec.f90->sourcefile~fieldspec.f90 sourcefile~make_itemspec.f90->sourcefile~bracketspec.f90 sourcefile~modelverticalgrid.f90 ModelVerticalGrid.F90 sourcefile~modelverticalgrid.f90->sourcefile~fieldspec.f90 sourcefile~stateitemextension.f90 StateItemExtension.F90 sourcefile~modelverticalgrid.f90->sourcefile~stateitemextension.f90 sourcefile~test_addfieldspec.pf Test_AddFieldSpec.pf sourcefile~test_addfieldspec.pf->sourcefile~fieldspec.f90 sourcefile~test_bracketspec.pf Test_BracketSpec.pf sourcefile~test_bracketspec.pf->sourcefile~fieldspec.f90 sourcefile~test_bracketspec.pf->sourcefile~bracketspec.f90 sourcefile~test_fieldspec.pf Test_FieldSpec.pf sourcefile~test_fieldspec.pf->sourcefile~fieldspec.f90 sourcefile~can_connect_to.f90 can_connect_to.F90 sourcefile~can_connect_to.f90->sourcefile~modelverticalgrid.f90 sourcefile~can_connect_to.f90~2 can_connect_to.F90 sourcefile~can_connect_to.f90~2->sourcefile~modelverticalgrid.f90 sourcefile~can_connect_to.f90~3 can_connect_to.F90 sourcefile~can_connect_to.f90~3->sourcefile~modelverticalgrid.f90 sourcefile~initialize_advertise.f90 initialize_advertise.F90 sourcefile~initialize_advertise.f90->sourcefile~make_itemspec.f90 sourcefile~parse_geometry_spec.f90 parse_geometry_spec.F90 sourcefile~parse_geometry_spec.f90->sourcefile~modelverticalgrid.f90 sourcefile~stateitemextension.f90->sourcefile~genericcoupler.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~make_itemspec.f90 sourcefile~test_modelverticalgrid.pf->sourcefile~modelverticalgrid.f90 sourcefile~test_modelverticalgrid.pf->sourcefile~stateitemextension.f90 sourcefile~extensionfamily.f90 ExtensionFamily.F90 sourcefile~extensionfamily.f90->sourcefile~stateitemextension.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~stateitemextension.f90 sourcefile~matchconnection.f90 MatchConnection.F90 sourcefile~matchconnection.f90->sourcefile~stateitemextension.f90 sourcefile~protoextdatagc.f90 ProtoExtDataGC.F90 sourcefile~protoextdatagc.f90->sourcefile~stateitemextension.f90 sourcefile~servicespec.f90 ServiceSpec.F90 sourcefile~servicespec.f90->sourcefile~stateitemextension.f90 sourcefile~simpleconnection.f90 SimpleConnection.F90 sourcefile~simpleconnection.f90->sourcefile~stateitemextension.f90 sourcefile~stateitemextensionptrvector.f90 StateItemExtensionPtrVector.F90 sourcefile~stateitemextensionptrvector.f90->sourcefile~stateitemextension.f90 sourcefile~stateitemextensionvector.f90 StateItemExtensionVector.F90 sourcefile~stateitemextensionvector.f90->sourcefile~stateitemextension.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~stateregistry.f90->sourcefile~stateitemextension.f90 sourcefile~test_extensionfamily.pf Test_ExtensionFamily.pf sourcefile~test_extensionfamily.pf->sourcefile~stateitemextension.f90 sourcefile~test_stateregistry.pf Test_StateRegistry.pf sourcefile~test_stateregistry.pf->sourcefile~stateitemextension.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_VerticalRegridMethod

   use esmf, only: ESMF_MAXSTR

   implicit none
   private
   
   public :: VerticalRegridMethod
   public :: VERTICAL_REGRID_UNKNOWN
   public :: VERTICAL_REGRID_LINEAR
   public :: VERTICAL_REGRID_CONSERVATIVE
   public :: operator(==), operator(/=)

   type :: VerticalRegridMethod
      private
      integer :: id = -1
   contains
      procedure :: write_formatted
      generic :: write(formatted) => write_formatted
   end type VerticalRegridMethod


   interface operator(==)
      procedure :: equal_to
   end interface operator(==)

   interface operator(/=)
      procedure :: not_equal_to
   end interface operator(/=)

   type(VerticalRegridMethod), parameter :: VERTICAL_REGRID_UNKNOWN = VerticalRegridMethod(-1)
   type(VerticalRegridMethod), parameter :: VERTICAL_REGRID_LINEAR = VerticalRegridMethod(1)
   type(VerticalRegridMethod), parameter :: VERTICAL_REGRID_CONSERVATIVE = VerticalRegridMethod(2)

contains

   subroutine write_formatted(this, unit, iotype, v_list, iostat, iomsg)
      class(VerticalRegridMethod), intent(in) :: this
      integer, intent(in) :: unit
      character(*), intent(in) :: iotype
      integer, intent(in) :: v_list(:)
      integer, intent(out) :: iostat
      character(*), intent(inout) :: iomsg

      integer :: id
      character(len=ESMF_MAXSTR) :: regrid_method_str

      id = this%id
      select case(id)
      case(-1)
         regrid_method_str = "VERTICAL_REGRID_UNKNOWN"
      case(1)
         regrid_method_str = "VERTICAL_REGRID_LINEAR"
      case(2)
         regrid_method_str = "VERTICAL_REGRID_CONSERVATIVE"
      ! case default
      !    _FAIL("Invalid vertical dim spec")
      end select
      write(unit, '("VerticalRegridMethod(",a,")")', iostat=iostat, iomsg=iomsg) trim(regrid_method_str)

      _UNUSED_DUMMY(iotype)
      _UNUSED_DUMMY(v_list)
   end subroutine write_formatted

   elemental logical function equal_to(a, b)
      type(VerticalRegridMethod), intent(in) :: a, b
      equal_to = (a%id == b%id)
   end function equal_to

   elemental logical function not_equal_to(a, b)
      type(VerticalRegridMethod), intent(in) :: a, b
      not_equal_to = .not. (a==b)
   end function not_equal_to

end module mapl3g_VerticalRegridMethod