ExtDataNode.F90 Source File


This file depends on

sourcefile~~extdatanode.f90~~EfferentGraph sourcefile~extdatanode.f90 ExtDataNode.F90 sourcefile~base_base.f90 Base_Base.F90 sourcefile~extdatanode.f90->sourcefile~base_base.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~extdatanode.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~extdatanode.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~base_base.f90->sourcefile~keywordenforcer.f90 sourcefile~constants.f90 Constants.F90 sourcefile~base_base.f90->sourcefile~constants.f90 sourcefile~mapl_range.f90 MAPL_Range.F90 sourcefile~base_base.f90->sourcefile~mapl_range.f90 sourcefile~maplgrid.f90 MaplGrid.F90 sourcefile~base_base.f90->sourcefile~maplgrid.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.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~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~mapl_range.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~maplgrid.f90->sourcefile~keywordenforcer.f90 sourcefile~maplgrid.f90->sourcefile~constants.f90 sourcefile~maplgrid.f90->sourcefile~errorhandling.f90 sourcefile~mapl_sort.f90 MAPL_Sort.F90 sourcefile~maplgrid.f90->sourcefile~mapl_sort.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~maplgrid.f90->sourcefile~pflogger_stub.f90 sourcefile~mapl_sort.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfl_keywordenforcer.f90 PFL_KeywordEnforcer.F90 sourcefile~pflogger_stub.f90->sourcefile~pfl_keywordenforcer.f90 sourcefile~wraparray.f90 WrapArray.F90 sourcefile~pflogger_stub.f90->sourcefile~wraparray.f90 sourcefile~physicalconstants.f90->sourcefile~mathconstants.f90

Files dependent on this one

sourcefile~~extdatanode.f90~~AfferentGraph sourcefile~extdatanode.f90 ExtDataNode.F90 sourcefile~extdatabracket.f90 ExtDataBracket.F90 sourcefile~extdatabracket.f90->sourcefile~extdatanode.f90 sourcefile~extdataabstractfilehandler.f90 ExtDataAbstractFileHandler.F90 sourcefile~extdataabstractfilehandler.f90->sourcefile~extdatabracket.f90 sourcefile~extdataclimfilehandler.f90 ExtDataClimFileHandler.F90 sourcefile~extdataclimfilehandler.f90->sourcefile~extdatabracket.f90 sourcefile~extdataclimfilehandler.f90->sourcefile~extdataabstractfilehandler.f90 sourcefile~extdatasimplefilehandler.f90 ExtDataSimpleFileHandler.F90 sourcefile~extdatasimplefilehandler.f90->sourcefile~extdatabracket.f90 sourcefile~extdatasimplefilehandler.f90->sourcefile~extdataabstractfilehandler.f90 sourcefile~extdatatypedef.f90 ExtDataTypeDef.F90 sourcefile~extdatatypedef.f90->sourcefile~extdatabracket.f90 sourcefile~extdatatypedef.f90->sourcefile~extdataabstractfilehandler.f90 sourcefile~extdataderivedexportvector.f90 ExtDataDerivedExportVector.F90 sourcefile~extdataderivedexportvector.f90->sourcefile~extdatatypedef.f90 sourcefile~extdatagridcompng.f90 ExtDataGridCompNG.F90 sourcefile~extdatagridcompng.f90->sourcefile~extdatatypedef.f90 sourcefile~extdatagridcompng.f90->sourcefile~extdataderivedexportvector.f90 sourcefile~extdataoldtypescreator.f90 ExtDataOldTypesCreator.F90 sourcefile~extdatagridcompng.f90->sourcefile~extdataoldtypescreator.f90 sourcefile~extdataprimaryexportvector.f90 ExtDataPrimaryExportVector.F90 sourcefile~extdatagridcompng.f90->sourcefile~extdataprimaryexportvector.f90 sourcefile~extdataoldtypescreator.f90->sourcefile~extdataabstractfilehandler.f90 sourcefile~extdataoldtypescreator.f90->sourcefile~extdataclimfilehandler.f90 sourcefile~extdataoldtypescreator.f90->sourcefile~extdatasimplefilehandler.f90 sourcefile~extdataoldtypescreator.f90->sourcefile~extdatatypedef.f90 sourcefile~extdataprimaryexportvector.f90->sourcefile~extdatatypedef.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~extdatagridcompng.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~extdatagridcompng.f90

Source Code

#include "MAPL_Exceptions.h"
#include "MAPL_ErrLog.h"
module MAPL_ExtDataNode
   use ESMF
   use MAPL_KeywordEnforcerMod
   use MAPL_ExceptionHandling
   use MAPL_BaseMod, only: MAPL_UNDEF
   implicit none
   private

   type, public :: ExtDataNode
      type(ESMF_Field) :: field
      type(ESMF_Time)  :: time
      character(len=ESMF_MAXPATHLEN) :: file
      integer :: time_index
      logical :: was_set = .false.
      contains
         procedure :: check_if_initialized
         procedure :: set
         procedure :: get
         procedure :: equals
         generic :: operator(==) => equals
   end type

contains

   function check_if_initialized(this,rc) result(field_initialized)
      logical :: field_initialized
      class(ExtDataNode), intent(inout) :: this
      integer, intent(out), optional :: rc
      integer :: status
      field_initialized = ESMF_FieldIsCreated(this%field,_RC)
      _RETURN(_SUCCESS)
   end function

   subroutine set(this, unusable, field, time, file, time_index, was_set, rc)
      class(ExtDataNode), intent(inout) :: this
      class(KeywordEnforcer), optional, intent(in) :: unusable
      type(ESMF_Time), optional, intent(in) :: time
      type(ESMF_Field), optional, intent(in) :: field
      character(len=*), optional, intent(in) :: file
      integer, optional, intent(in) :: time_index
      logical, optional, intent(in) :: was_set
      integer, optional, intent(out) :: rc

      _UNUSED_DUMMY(unusable)
      if (present(time)) this%time = time
      if (present(field)) this%field = field
      if (present(file)) this%file = trim(file)
      if (present(time_index)) this%time_index = time_index
      if (present(was_set)) this%was_set = was_set
      _RETURN(_SUCCESS)

   end subroutine set

   subroutine get(this, unusable, field, time, file, time_index, was_set, rc)
      class(ExtDataNode), intent(inout) :: this
      class(KeywordEnforcer), optional, intent(in) :: unusable
      type(ESMF_Time), optional, intent(out) :: time
      type(ESMF_Field), optional, intent(out) :: field
      character(len=*), optional, intent(out) :: file
      integer, optional, intent(out) :: time_index
      logical, optional, intent(out) :: was_set
      integer, optional, intent(out) :: rc

      _UNUSED_DUMMY(unusable)
      if (present(time)) time = this%time
      if (present(field)) field = this%field
      if (present(file)) file = trim(this%file)
      if (present(time_index)) time_index = this%time_index
      if (present(was_set)) was_set = this%was_set
      _RETURN(_SUCCESS)

   end subroutine get

   logical function equals(a,b)
      class(ExtDataNode), intent(in) :: a
      class(ExtDataNode), intent(in) :: b
 
      equals = (trim(a%file)==trim(b%file)) .and. (a%time==b%time) .and. (a%time_index==b%time_index)
   end function equals

end module MAPL_ExtDataNode