ESMF_Interfaces.F90 Source File


Files dependent on this one

sourcefile~~esmf_interfaces.f90~~AfferentGraph sourcefile~esmf_interfaces.f90 ESMF_Interfaces.F90 sourcefile~attach_outer_meta.f90 attach_outer_meta.F90 sourcefile~attach_outer_meta.f90->sourcefile~esmf_interfaces.f90 sourcefile~couplermetacomponent.f90 CouplerMetaComponent.F90 sourcefile~couplermetacomponent.f90->sourcefile~esmf_interfaces.f90 sourcefile~free_outer_meta.f90 free_outer_meta.F90 sourcefile~free_outer_meta.f90->sourcefile~esmf_interfaces.f90 sourcefile~generic3g.f90 Generic3g.F90 sourcefile~generic3g.f90->sourcefile~esmf_interfaces.f90 sourcefile~get_outer_meta_from_outer_gc.f90 get_outer_meta_from_outer_gc.F90 sourcefile~get_outer_meta_from_outer_gc.f90->sourcefile~esmf_interfaces.f90 sourcefile~innermetacomponent.f90 InnerMetaComponent.F90 sourcefile~innermetacomponent.f90->sourcefile~esmf_interfaces.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~mapl_generic.f90~2->sourcefile~esmf_interfaces.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~esmf_interfaces.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~usersetservices.f90->sourcefile~esmf_interfaces.f90

Source Code

!-------
! The interfaces specified here are mandated by ESMF. By providing these
! as an abstract interface,  we enable declaration of corresponding dummy procedure
! arguments elsewhere in the code in a precise and elegant manner.  E.g.,
!
!    procedure(I_SetServices) :: userRoutine
!
!-------


module mapl3g_ESMF_Interfaces
   implicit none
   private

   public :: I_SetServices
   public :: I_Run

   public :: I_CplSetServices
   public :: I_CplRun

   public :: MAPL_UserCompGetInternalState
   public :: MAPL_UserCompSetInternalState

   interface MAPL_UserCompGetInternalState
      subroutine ESMF_UserCompGetInternalState(gridcomp, name, wrapper, status)
         use ESMF, only: ESMF_GridComp
         type(ESMF_GridComp), intent(inout) :: gridcomp
         character(*), intent(in) :: name
         type(*), intent(inout) :: wrapper
         integer, optional, intent(out) :: status
      end subroutine ESMF_UserCompGetInternalState
   end interface MAPL_UserCompGetInternalState

   interface MAPL_UserCompSetInternalState
      subroutine ESMF_UserCompSetInternalState(gridcomp, name, wrapper, status)
         use ESMF, only: ESMF_GridComp
         type(ESMF_GridComp), intent(inout) :: gridcomp
         character(*), intent(in) :: name
         type(*), intent(inout) :: wrapper
         integer, optional, intent(out) :: status
      end subroutine ESMF_UserCompSetInternalState
   end interface MAPL_UserCompSetInternalState

   abstract interface

      subroutine I_SetServices(gridcomp, rc)
         use ESMF, only: ESMF_GridComp
         implicit none
         type(ESMF_GridComp)  :: gridcomp
         integer, intent(out) :: rc
      end subroutine I_SetServices

      subroutine I_Run(gridcomp, importState, exportState, clock, rc)
         use esmf, only: ESMF_GridComp
         use esmf, only: ESMF_State
         use esmf, only: ESMF_Clock
         implicit none
         type(ESMF_GridComp)   :: gridcomp
         type(ESMF_State)      :: importState
         type(ESMF_State)      :: exportState
         type(ESMF_Clock)      :: clock      
         integer, intent(out)  :: rc         
      end subroutine I_Run

      subroutine I_CplSetServices(cplcomp, rc)
         use ESMF, only: ESMF_CplComp
         implicit none
         type(ESMF_CplComp)   :: cplcomp
         integer, intent(out) :: rc
      end subroutine I_CplSetServices


      subroutine I_CplRun(cplcomp, importState, exportState, clock, rc)
         use :: esmf, only: ESMF_CplComp
         use :: esmf, only: ESMF_State
         use :: esmf, only: ESMF_Clock
         implicit none
         type(ESMF_CplComp)    :: cplcomp
         type(ESMF_State)      :: importState
         type(ESMF_State)      :: exportState
         type(ESMF_Clock)      :: clock      
         integer, intent(out)  :: rc         
      end subroutine I_CplRun

   end interface


end module mapl3g_ESMF_Interfaces