MAPL_GridCreate Subroutine

public subroutine MAPL_GridCreate(GC, MAPLOBJ, ESMFGRID, srcGC, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_GridComp), intent(inout), optional :: GC
type(MAPL_MetaComp), intent(inout), optional, target :: MAPLOBJ
type(ESMF_Grid), intent(out), optional :: ESMFGRID
type(ESMF_GridComp), intent(inout), optional :: srcGC
integer, intent(out), optional :: rc

Calls

proc~~mapl_gridcreate~~CallsGraph proc~mapl_gridcreate MAPL_GridCreate ESMF_ConfigGetAttribute ESMF_ConfigGetAttribute proc~mapl_gridcreate->ESMF_ConfigGetAttribute ESMF_GridCompGet ESMF_GridCompGet proc~mapl_gridcreate->ESMF_GridCompGet ESMF_GridCompSet ESMF_GridCompSet proc~mapl_gridcreate->ESMF_GridCompSet ESMF_UserCompGetInternalState ESMF_UserCompGetInternalState proc~mapl_gridcreate->ESMF_UserCompGetInternalState ESMF_VMGetCurrent ESMF_VMGetCurrent proc~mapl_gridcreate->ESMF_VMGetCurrent interface~mapl_assert MAPL_Assert proc~mapl_gridcreate->interface~mapl_assert interface~mapl_configsetattribute MAPL_ConfigSetAttribute proc~mapl_gridcreate->interface~mapl_configsetattribute none~make_grid~4 GridManager%make_grid proc~mapl_gridcreate->none~make_grid~4 none~set~31 MaplGrid%set proc~mapl_gridcreate->none~set~31 proc~mapl_return MAPL_Return proc~mapl_gridcreate->proc~mapl_return proc~mapl_verify MAPL_Verify proc~mapl_gridcreate->proc~mapl_verify none~make_grid_from_distgrid GridManager%make_grid_from_distGrid none~make_grid~4->none~make_grid_from_distgrid none~set~31->ESMF_VMGetCurrent none~set~31->interface~mapl_assert none~set~31->proc~mapl_return none~set~31->proc~mapl_verify ESMF_DistGridGet ESMF_DistGridGet none~set~31->ESMF_DistGridGet ESMF_GridGet ESMF_GridGet none~set~31->ESMF_GridGet ESMF_GridGetCoord ESMF_GridGetCoord none~set~31->ESMF_GridGetCoord ESMF_GridValidate ESMF_GridValidate none~set~31->ESMF_GridValidate ESMF_VMGet ESMF_VMGet none~set~31->ESMF_VMGet interface~wraparray wrapArray none~set~31->interface~wraparray none~debug~4 Logger%debug none~set~31->none~debug~4 proc~mapl_distgridget MAPL_DistGridGet none~set~31->proc~mapl_distgridget proc~mapl_getimsjms MAPL_GetImsJms none~set~31->proc~mapl_getimsjms proc~mapl_gridget MAPL_GridGet none~set~31->proc~mapl_gridget at at proc~mapl_return->at insert insert proc~mapl_return->insert proc~mapl_throw_exception MAPL_throw_exception proc~mapl_return->proc~mapl_throw_exception proc~mapl_verify->proc~mapl_throw_exception none~make_grid_from_distgrid->none~make_grid~4 none~make_grid_from_distgrid->proc~mapl_return none~make_grid_from_distgrid->proc~mapl_verify ESMF_AttributeSet ESMF_AttributeSet none~make_grid_from_distgrid->ESMF_AttributeSet none~make_factory~3 GridManager%make_factory none~make_grid_from_distgrid->none~make_factory~3 proc~mapl_distgridget->proc~mapl_verify proc~mapl_distgridget->ESMF_DistGridGet proc~mapl_getimsjms->interface~mapl_assert proc~mapl_getimsjms->proc~mapl_return proc~mapl_getimsjms->proc~mapl_verify interface~mapl_sort MAPL_Sort proc~mapl_getimsjms->interface~mapl_sort proc~mapl_gridget->proc~mapl_return proc~mapl_gridget->proc~mapl_verify proc~mapl_gridget->ESMF_DistGridGet proc~mapl_gridget->ESMF_GridGet proc~mapl_gridget->proc~mapl_distgridget proc~mapl_gridget->proc~mapl_getimsjms ESMF_AttributeGet ESMF_AttributeGet proc~mapl_gridget->ESMF_AttributeGet proc~mapl_gridhasde MAPL_GridHasDE proc~mapl_gridget->proc~mapl_gridhasde

Source Code

   subroutine MAPL_GridCreate(GC, MAPLOBJ, ESMFGRID, srcGC, rc)
      type(ESMF_GridComp), optional,         intent(INOUT) :: GC
      type (MAPL_MetaComp),optional, target, intent(INOUT) :: MAPLOBJ
      type (ESMF_Grid),    optional,         intent(  OUT) :: ESMFGRID
      type(ESMF_GridComp), optional,         intent(INout) :: srcGC
      integer,             optional,         intent(  OUT) :: rc

      integer                               :: status
      character(len=ESMF_MAXSTR)            :: Comp_Name
      character(len=ESMF_MAXSTR)            :: IAm

      type (ESMF_VM)                        :: VM
      type (MAPL_MetaComp), pointer         :: STATE
      type (ESMF_Grid)                      :: GRID
      integer                               :: nn,ny
      character(len=ESMF_MAXSTR)            :: GridName
      character(len=ESMF_MAXSTR)            :: Prefix
      character(len=2)                      :: dateline
#ifdef CREATE_REGULAR_GRIDS
      logical                               :: isRegular
#endif

      ! Query GC
      !---------

      Iam='MAPL_GridCreate'
      Prefix = ''
      if(present(GC)) then
         call ESMF_GridCompGet( GC, name=Comp_Name,   _RC)
         Iam = trim(Comp_Name)//Iam
         Prefix = trim(comp_name)//MAPL_CF_COMPONENT_SEPARATOR
      endif

      ! New option to get grid from existing component
      !-----------------------------------------------

      if(present(srcGC)) then
         call ESMF_GridCompGet ( srcGC, grid=Grid, _RC)
         if(present(GC)) then
            call ESMF_GridCompSet(GC, GRID=GRID, _RC)
         end if
         if(present(ESMFGRID)) then
            ESMFGRID=GRID
         end if
         _RETURN(ESMF_SUCCESS)
      end if



      call ESMF_VMGetCurrent(vm, _RC)

      ! Get MAPL object
      !----------------

      if(present(GC)) then
         _ASSERT(.not. present(MAPLOBJ),'needs informative message')
         call MAPL_InternalStateGet(GC, STATE, _RC)
      elseif(present(MAPLOBJ)) then
         STATE => MAPLOBJ
      else
         _FAIL('needs informative message')
      endif

      if (trim(Prefix) /= '') then
         call MAPL_ConfigPrepend(state%cf,trim(comp_name),MAPL_CF_COMPONENT_SEPARATOR,'NX:', _RC)
         call MAPL_ConfigPrepend(state%cf,trim(comp_name),MAPL_CF_COMPONENT_SEPARATOR,'NY:', _RC)
      endif

      call ESMF_ConfigGetAttribute(state%cf,gridname,label=trim(Prefix)//'GRIDNAME:', _RC)
      nn = len_trim(gridname)
      dateline = gridname(nn-1:nn)
      if (dateline == 'CF') then
         ! convert global NY to a local NY for each face
         call ESMF_ConfigGetAttribute(state%CF,ny,label=trim(Prefix)//'NY:', _RC)
         call MAPL_ConfigSetAttribute(state%CF, value=ny/6, label=trim(Prefix)//'NY:', _RC)
      end if

      grid = grid_manager%make_grid(state%CF, prefix=trim(Prefix), _RC)

      call state%grid%set(grid, _RC)

      if(present(GC)) then
         call ESMF_GridCompSet(GC, GRID=GRID, _RC)
      end if

      if(present(ESMFGRID)) then
         ESMFGRID=GRID
      end if

      _RETURN(ESMF_SUCCESS)

   contains

      subroutine MAPL_ConfigPrepend(cf, comp_name,separator,label,rc)
         type(ESMF_Config), intent(inout) :: cf
         character(len=*) , intent(in   ) :: comp_name
         character(len=*) , intent(in   ) :: separator
         character(len=*) , intent(in   ) :: label
         integer, optional , intent(out  ) :: rc

         integer  :: status
         character(len=ESMF_MAXSTR) :: Iam = "MAPL_ConfigPrepend"
         integer  :: val

         call ESMF_ConfigGetAttribute( cf, val, label=trim(comp_name)//trim(separator)//trim(label), rc = status )
         if (status /= ESMF_SUCCESS) then
            call ESMF_ConfigGetAttribute(CF,val,label=trim(label), _RC)
            call MAPL_ConfigSetAttribute(CF, val, label=trim(comp_name)//trim(separator)//trim(label), _RC)
         end if

         _RETURN(ESMF_SUCCESS)

      end subroutine MAPL_ConfigPrepend

   end subroutine MAPL_GridCreate