parse_child.F90 Source File


This file depends on

sourcefile~~parse_child.f90~~EfferentGraph sourcefile~parse_child.f90 parse_child.F90 sourcefile~componentspecparser.f90 ComponentSpecParser.F90 sourcefile~parse_child.f90->sourcefile~componentspecparser.f90 sourcefile~childspec.f90 ChildSpec.F90 sourcefile~componentspecparser.f90->sourcefile~childspec.f90 sourcefile~childspecmap.f90 ChildSpecMap.F90 sourcefile~componentspecparser.f90->sourcefile~childspecmap.f90 sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~componentspecparser.f90->sourcefile~componentspec.f90 sourcefile~connection.f90 Connection.F90 sourcefile~componentspecparser.f90->sourcefile~connection.f90 sourcefile~connectionpt.f90 ConnectionPt.F90 sourcefile~componentspecparser.f90->sourcefile~connectionpt.f90 sourcefile~connectionvector.f90 ConnectionVector.F90 sourcefile~componentspecparser.f90->sourcefile~connectionvector.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~componentspecparser.f90->sourcefile~errorhandling.f90 sourcefile~esmf_utilities.f90 ESMF_Utilities.F90 sourcefile~componentspecparser.f90->sourcefile~esmf_utilities.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~componentspecparser.f90->sourcefile~geom_mgr.f90 sourcefile~geometryspec.f90 GeometrySpec.F90 sourcefile~componentspecparser.f90->sourcefile~geometryspec.f90 sourcefile~matchconnection.f90 MatchConnection.F90 sourcefile~componentspecparser.f90->sourcefile~matchconnection.f90 sourcefile~reexportconnection.f90 ReexportConnection.F90 sourcefile~componentspecparser.f90->sourcefile~reexportconnection.f90 sourcefile~simpleconnection.f90 SimpleConnection.F90 sourcefile~componentspecparser.f90->sourcefile~simpleconnection.f90 sourcefile~stateitem.f90 StateItem.F90 sourcefile~componentspecparser.f90->sourcefile~stateitem.f90 sourcefile~ungriddeddim.f90 UngriddedDim.F90 sourcefile~componentspecparser.f90->sourcefile~ungriddeddim.f90 sourcefile~ungriddeddims.f90 UngriddedDims.F90 sourcefile~componentspecparser.f90->sourcefile~ungriddeddims.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~componentspecparser.f90->sourcefile~usersetservices.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~componentspecparser.f90->sourcefile~variablespec.f90 sourcefile~variablespecvector.f90 VariableSpecVector.F90 sourcefile~componentspecparser.f90->sourcefile~variablespecvector.f90 sourcefile~verticaldimspec.f90 VerticalDimSpec.F90 sourcefile~componentspecparser.f90->sourcefile~verticaldimspec.f90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~componentspecparser.f90->sourcefile~virtualconnectionpt.f90

Source Code

#include "MAPL_ErrLog.h"

submodule (mapl3g_ComponentSpecParser) parse_child_smod

contains

   module function parse_child(hconfig, rc) result(child)
      type(ChildSpec) :: child
      type(ESMF_HConfig), intent(in) :: hconfig
      integer, optional, intent(out) :: rc

      integer :: status
      class(AbstractUserSetServices), allocatable :: setservices

      character(*), parameter :: dso_keys(*) = [character(len=9) :: 'dso', 'DSO', 'sharedObj', 'sharedobj']
      character(*), parameter :: userProcedure_keys(*) = [character(len=10) :: 'SetServices', 'setServices', 'setservices']
      integer :: i
      character(:), allocatable :: dso_key, userProcedure_key, try_key
      logical :: dso_found, userProcedure_found
      logical :: has_key
      logical :: has_config_file
      character(:), allocatable :: sharedObj, userProcedure, config_file


      dso_found = .false.
      ! Ensure precisely one name is used for dso
      do i = 1, size(dso_keys)
         try_key = trim(dso_keys(i))
         has_key = ESMF_HconfigIsDefined(hconfig, keyString=try_key, _RC)
         if (has_key) then
            _ASSERT(.not. dso_found, 'multiple specifications for dso in hconfig for child')
            dso_found = .true.
            dso_key = try_key
         end if
      end do
      _ASSERT(dso_found, 'Must specify a dso for hconfig of child')
      sharedObj = ESMF_HconfigAsString(hconfig, keyString=dso_key, _RC)

      userProcedure_found = .false.
      do i = 1, size(userProcedure_keys)
         try_key = userProcedure_keys(i)
         if (ESMF_HconfigIsDefined(hconfig, keyString=try_key)) then
            _ASSERT(.not. userProcedure_found, 'multiple specifications for dso in hconfig for child')
            userProcedure_found = .true.
            userProcedure_key = try_key
         end if
      end do
      userProcedure = 'setservices_'         
      if (userProcedure_found) then
         userProcedure = ESMF_HconfigAsString(hconfig, keyString=userProcedure_key,_RC)
      end if

      has_config_file = ESMF_HconfigIsDefined(hconfig, keyString='config_file', _RC)
      if (has_config_file) then
         config_file = ESMF_HconfigAsString(hconfig, keyString='config_file',_RC)
      end if

      setservices = user_setservices(sharedObj, userProcedure)
      child = ChildSpec(setservices, config_file=config_file)

      _RETURN(_SUCCESS)
   end function parse_child

end submodule parse_child_smod