MAPL_create_bundle_from_metdata_id Subroutine

public subroutine MAPL_create_bundle_from_metdata_id(bundle, metadata_id, file_name, only_vars, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_FieldBundle), intent(inout) :: bundle
integer, intent(in) :: metadata_id
character(len=*), intent(in) :: file_name
character(len=*), intent(in), optional :: only_vars
integer, intent(out), optional :: rc

Calls

proc~~mapl_create_bundle_from_metdata_id~~CallsGraph proc~mapl_create_bundle_from_metdata_id MAPL_create_bundle_from_metdata_id ESMF_InfoGetFromHost ESMF_InfoGetFromHost proc~mapl_create_bundle_from_metdata_id->ESMF_InfoGetFromHost ESMF_InfoSet ESMF_InfoSet proc~mapl_create_bundle_from_metdata_id->ESMF_InfoSet begin begin proc~mapl_create_bundle_from_metdata_id->begin esmf_fieldbundleget esmf_fieldbundleget proc~mapl_create_bundle_from_metdata_id->esmf_fieldbundleget esmf_fieldcreate esmf_fieldcreate proc~mapl_create_bundle_from_metdata_id->esmf_fieldcreate esmf_fieldget esmf_fieldget proc~mapl_create_bundle_from_metdata_id->esmf_fieldget get_file_format_vars get_file_format_vars proc~mapl_create_bundle_from_metdata_id->get_file_format_vars interface~mapl_assert MAPL_Assert proc~mapl_create_bundle_from_metdata_id->interface~mapl_assert interface~mapl_fieldbundleadd MAPL_FieldBundleAdd proc~mapl_create_bundle_from_metdata_id->interface~mapl_fieldbundleadd none~at~197 MAPLCollectionVector%at proc~mapl_create_bundle_from_metdata_id->none~at~197 none~find~49 MAPLDataCollection%find proc~mapl_create_bundle_from_metdata_id->none~find~49 none~first~238 StringVariableMapIterator%first proc~mapl_create_bundle_from_metdata_id->none~first~238 none~ftn_begin~35 StringVariableMap%ftn_begin proc~mapl_create_bundle_from_metdata_id->none~ftn_begin~35 none~ftn_end~35 StringVariableMap%ftn_end proc~mapl_create_bundle_from_metdata_id->none~ftn_end~35 none~get_dimension FileMetadataUtils%get_dimension proc~mapl_create_bundle_from_metdata_id->none~get_dimension none~get_dimensions~3 Variable%get_dimensions proc~mapl_create_bundle_from_metdata_id->none~get_dimensions~3 none~get_level_name FileMetadataUtils%get_level_name proc~mapl_create_bundle_from_metdata_id->none~get_level_name none~get_var_attr_string FileMetadataUtils%get_var_attr_string proc~mapl_create_bundle_from_metdata_id->none~get_var_attr_string none~get_variables FileMetadataUtils%get_variables proc~mapl_create_bundle_from_metdata_id->none~get_variables none~next~96 StringVariableMapIterator%next proc~mapl_create_bundle_from_metdata_id->none~next~96 of of proc~mapl_create_bundle_from_metdata_id->of proc~get_factory~2 get_factory proc~mapl_create_bundle_from_metdata_id->proc~get_factory~2 proc~mapl_gridget MAPL_GridGet proc~mapl_create_bundle_from_metdata_id->proc~mapl_gridget proc~mapl_return MAPL_Return proc~mapl_create_bundle_from_metdata_id->proc~mapl_return proc~mapl_verify MAPL_Verify proc~mapl_create_bundle_from_metdata_id->proc~mapl_verify ptr2d ptr2d proc~mapl_create_bundle_from_metdata_id->ptr2d ptr3d ptr3d proc~mapl_create_bundle_from_metdata_id->ptr3d

Called by

proc~~mapl_create_bundle_from_metdata_id~~CalledByGraph proc~mapl_create_bundle_from_metdata_id MAPL_create_bundle_from_metdata_id proc~mapl_read_bundle MAPL_read_bundle proc~mapl_read_bundle->proc~mapl_create_bundle_from_metdata_id proc~main~2 main proc~main~2->proc~mapl_read_bundle program~time_ave time_ave program~time_ave->proc~mapl_read_bundle program~ut_regridding ut_ReGridding program~ut_regridding->proc~mapl_read_bundle program~regrid_util Regrid_Util program~regrid_util->proc~main~2

Source Code

      subroutine MAPL_create_bundle_from_metdata_id(bundle,metadata_id,file_name,only_vars,rc)
         type(ESMF_FieldBundle), intent(inout) :: bundle
         integer, intent(in) :: metadata_id
         character(len=*), intent(in) :: file_name
         character(len=*), optional, intent(in) :: only_vars
         integer, optional, intent(out) :: rc

         integer :: status
         type(MAPLDataCollection), pointer :: collection => null()
         type(fileMetaDataUtils), pointer :: metadata
         type(ESMF_Grid) :: grid,file_grid
         integer :: num_fields,dims,location
         logical :: create_variable, has_vertical_level, var_has_levels
         class (AbstractGridFactory), pointer :: factory
         character(len=:), allocatable :: grid_vars,exclude_vars
         type(StringVariableMap), pointer :: variables
         type(Variable), pointer :: this_variable
         type(StringVariableMapIterator) :: var_iter
         character(len=:), pointer :: var_name,dim_name
         character(len=:), allocatable :: lev_name
         type(ESMF_Field) :: field
         type (StringVector), pointer :: dimensions
         type (StringVectorIterator) :: dim_iter
         integer :: lev_size, grid_size(3)
         character(len=:), allocatable :: units,long_name
         type(ESMF_Info) :: infoh

         collection => DataCollections%at(metadata_id)
         _ASSERT(associated(collection), 'specified metadata_id not found')
         metadata => collection%find(trim(file_name), _RC)
         _ASSERT(associated(metadata), 'filename <'//trim(file_name)//'> not found')
         file_grid=collection%src_grid
         lev_name = metadata%get_level_name(_RC)
         has_vertical_level = (metadata%get_level_name(rc=status)/='')
         call ESMF_FieldBundleGet(bundle,grid=grid,FieldCount=num_fields,rc=status)
         _VERIFY(status)
         call MAPL_GridGet(grid,localCellCountPerDim=grid_size,rc=status)
         _VERIFY(status)

         _ASSERT(num_fields == 0,"Trying to fill non-empty bundle")
         factory => get_factory(file_grid,rc=status)
         _VERIFY(status)
         grid_vars = factory%get_file_format_vars()
         exclude_vars = grid_vars//",lev,time,lons,lats"
         if (has_vertical_level) lev_size = metadata%get_dimension(trim(lev_name))

         variables => metadata%get_variables()
         var_iter = variables%ftn_begin()
         do while (var_iter /= variables%ftn_end())
            call var_iter%next()

            var_has_levels = .false.
            var_name => var_iter%first()
            this_variable => var_iter%second()

            if (has_vertical_level) then
               dimensions => this_variable%get_dimensions()
               dim_iter = dimensions%begin()
               do while (dim_iter /= dimensions%end())
                  dim_name => dim_iter%of()
                  if (trim(dim_name) == lev_name) var_has_levels=.true.
                  call dim_iter%next()
               enddo
            end if

            if (index(','//trim(exclude_vars)//',',','//trim(var_name)//',') > 0) then
               call var_iter%next()
                  cycle
               end if
            create_variable = .true.
            if (present(only_vars)) then
               if (index(','//trim(only_vars)//',',','//trim(var_name)//',') < 1) create_variable = .false.
            end if
            if (create_variable) then
               if(var_has_levels) then
                   if (grid_size(3) == lev_size) then
                      location=MAPL_VLocationCenter
                      dims = MAPL_DimsHorzVert
                      field= ESMF_FieldCreate(grid,name=trim(var_name),typekind=ESMF_TYPEKIND_R4, &
                        ungriddedUbound=[grid_size(3)],ungriddedLBound=[1], rc=status)
                        block
                           real, pointer :: ptr3d(:,:,:)
                           call ESMF_FieldGEt(field,0,farrayPtr=ptr3d)
                           ptr3d =0.0
                        end block
                   else if (grid_size(3)+1 == lev_size) then
                      location=MAPL_VLocationEdge
                      dims = MAPL_DimsHorzVert
                      field= ESMF_FieldCreate(grid,name=trim(var_name),typekind=ESMF_TYPEKIND_R4, &
                        ungriddedUbound=[grid_size(3)],ungriddedLBound=[0], rc=status)
                        block
                           real, pointer :: ptr3d(:,:,:)
                           call ESMF_FieldGEt(field,0,farrayPtr=ptr3d)
                           ptr3d =0.0
                        end block
                  end if
               else
                   location=MAPL_VLocationNone
                   dims = MAPL_DimsHorzOnly
                   field= ESMF_FieldCreate(grid,name=trim(var_name),typekind=ESMF_TYPEKIND_R4, &
                      rc=status)
                        block
                           real, pointer :: ptr2d(:,:)
                           call ESMF_FieldGEt(field,0,farrayPtr=ptr2d)
                           ptr2d =0.0
                        end block
               end if
               call ESMF_InfoGetFromHost(field,infoh,rc=status)
               _VERIFY(status)
               call ESMF_InfoSet(infoh,'DIMS',dims,rc=status)
               _VERIFY(status)
               call ESMF_InfoSet(infoh,'VLOCATION',location,rc=status)
               _VERIFY(status)
               units = metadata%get_var_attr_string(var_name,'units',_RC)
               long_name = metadata%get_var_attr_string(var_name,'long_name',_RC)
               call ESMF_InfoSet(infoh,'UNITS',units,rc=status)
               _VERIFY(status)
               call ESMF_InfoSet(infoh,'LONG_NAME',long_name,rc=status)
               _VERIFY(status)
               call MAPL_FieldBundleAdd(bundle,field,rc=status)
               _VERIFY(status)
            end if
         end do

         _RETURN(_SUCCESS)

      end subroutine MAPL_create_bundle_from_metdata_id