make_itemSpec.F90 Source File


This file depends on

sourcefile~~make_itemspec.f90~~EfferentGraph sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~actualptvector.f90 ActualPtVector.F90 sourcefile~make_itemspec.f90->sourcefile~actualptvector.f90 sourcefile~bracketspec.f90 BracketSpec.F90 sourcefile~make_itemspec.f90->sourcefile~bracketspec.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~make_itemspec.f90->sourcefile~errorhandling.f90 sourcefile~fieldspec.f90~2 FieldSpec.F90 sourcefile~make_itemspec.f90->sourcefile~fieldspec.f90~2 sourcefile~invalidspec.f90 InvalidSpec.F90 sourcefile~make_itemspec.f90->sourcefile~invalidspec.f90 sourcefile~servicespec.f90 ServiceSpec.F90 sourcefile~make_itemspec.f90->sourcefile~servicespec.f90 sourcefile~stateitem.f90 StateItem.F90 sourcefile~make_itemspec.f90->sourcefile~stateitem.f90 sourcefile~stateitemspec.f90 StateItemSpec.F90 sourcefile~make_itemspec.f90->sourcefile~stateitemspec.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~make_itemspec.f90->sourcefile~stateregistry.f90 sourcefile~statespec.f90 StateSpec.F90 sourcefile~make_itemspec.f90->sourcefile~statespec.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~make_itemspec.f90->sourcefile~variablespec.f90 sourcefile~wildcardspec.f90 WildcardSpec.F90 sourcefile~make_itemspec.f90->sourcefile~wildcardspec.f90

Files dependent on this one

sourcefile~~make_itemspec.f90~~AfferentGraph sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~initialize_advertise.f90 initialize_advertise.F90 sourcefile~initialize_advertise.f90->sourcefile~make_itemspec.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~make_itemspec.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_make_itemSpec
   use mapl3g_StateItemSpec
   use mapl3g_StateItem
   use mapl3g_FieldSpec, only: FieldSpec
   use mapl3g_ServiceSpec, only: ServiceSpec
   use mapl3g_WildcardSpec, only: WildcardSpec
   use mapl3g_BracketSpec, only: BracketSpec
   use mapl3g_StateSpec, only: StateSpec
   use mapl3g_InvalidSpec, only: InvalidSpec
   use mapl3g_StateRegistry, only: StateRegistry
   use mapl_ErrorHandling
   use esmf, only: ESMF_STATEINTENT_INTERNAL, operator(==)
   implicit none
   private
   public :: make_ItemSpec

contains

   function make_itemSpec(variable_spec, registry, rc) result(item_spec)
      use mapl3g_VariableSpec, only: VariableSpec
      use mapl3g_ActualPtVector, only: ActualPtVector
      class(StateItemSpec), allocatable :: item_spec
      class(VariableSpec), intent(in) :: variable_spec
      type(StateRegistry), pointer, intent(in) :: registry
      integer, optional, intent(out) :: rc

      integer :: status
      type(FieldSpec) :: field_spec
      type(ActualPtVector) :: dependencies

      select case (variable_spec%itemtype%ot)
      case (MAPL_STATEITEM_FIELD%ot)
         allocate(FieldSpec :: item_spec)
         item_spec = FieldSpec(variable_spec)
      case (MAPL_STATEITEM_SERVICE%ot)
         allocate(ServiceSpec :: item_spec)
         item_spec = ServiceSpec(variable_spec, registry)
      case (MAPL_STATEITEM_WILDCARD%ot)
         allocate(WildcardSpec :: item_spec)
         field_spec = FieldSpec(variable_spec)
         item_spec = WildcardSpec(field_spec)
      case (MAPL_STATEITEM_BRACKET%ot)
         allocate(BracketSpec :: item_spec)
         field_spec = FieldSpec(variable_spec)
         item_spec = BracketSpec(field_spec, variable_spec%bracket_size)
      case (MAPL_STATEITEM_STATE%ot)
         allocate(StateSpec :: item_spec)
      case default
         allocate(InvalidSpec :: item_spec)
         _FAIL('Unsupported type.')
      end select

      if (variable_spec%state_intent == ESMF_STATEINTENT_INTERNAL) then
         call item_spec%set_active()
      end if

      dependencies = variable_spec%make_dependencies(_RC)
      call item_spec%set_dependencies(dependencies)
      call item_spec%set_raw_dependencies(variable_spec%dependencies)

      _RETURN(_SUCCESS)

   end function make_itemSpec

end module mapl3g_make_itemSpec