read_M_files_4_swath Subroutine

public subroutine read_M_files_4_swath(filenames, Xdim, Ydim, index_name_lon, index_name_lat, var_name_lon, var_name_lat, var_name_time, lon, lat, time, Tfilter, rc)

Uses

  • proc~~read_m_files_4_swath~~UsesGraph proc~read_m_files_4_swath read_M_files_4_swath module~pflogger pflogger proc~read_m_files_4_swath->module~pflogger module~pfl_keywordenforcermod PFL_KeywordEnforcerMod module~pflogger->module~pfl_keywordenforcermod module~pfl_logger PFL_Logger module~pflogger->module~pfl_logger module~pfl_loggermanager PFL_LoggerManager module~pflogger->module~pfl_loggermanager module~pfl_severitylevels PFL_SeverityLevels module~pflogger->module~pfl_severitylevels module~pfl_wraparray PFL_WrapArray module~pflogger->module~pfl_wraparray module~pfl_logger->module~pfl_keywordenforcermod module~pfl_logger->module~pfl_severitylevels gFTL_StringUnlimitedMap gFTL_StringUnlimitedMap module~pfl_logger->gFTL_StringUnlimitedMap module~pfl_loggermanager->module~pfl_logger
      write(6,*) 'af ith, filename', i, trim(filename)

write(6,’(2x,a,10i10)’) ‘true Xdim, Ydim:’, Xdim, Ydim write(6,’(2x,a,10i10)’) ‘false Xdim, Ydim:’, nlon, j2

write(6,’(2x,a,10i6)’) ‘M, i, nlon, nlat:’, M, i, nlon, nlat write(6,’(2x,a)’) ‘time_loc_r8’

write(6,’(5f20.2)’) time_loc_R8(1,j)

Arguments

Type IntentOptional Attributes Name
character(len=ESMF_MAXSTR), intent(in) :: filenames(:)
integer, intent(out) :: Xdim
integer, intent(out) :: Ydim
character(len=ESMF_MAXSTR), intent(in) :: index_name_lon
character(len=ESMF_MAXSTR), intent(in) :: index_name_lat
character(len=ESMF_MAXSTR), intent(in), optional :: var_name_lon
character(len=ESMF_MAXSTR), intent(in), optional :: var_name_lat
character(len=ESMF_MAXSTR), intent(in), optional :: var_name_time
real(kind=ESMF_KIND_R8), intent(inout), optional, allocatable :: lon(:,:)
real(kind=ESMF_KIND_R8), intent(inout), optional, allocatable :: lat(:,:)
real(kind=ESMF_KIND_R8), intent(inout), optional, allocatable :: time(:,:)
logical, intent(in), optional :: Tfilter
integer, intent(out), optional :: rc

Calls

proc~~read_m_files_4_swath~~CallsGraph proc~read_m_files_4_swath read_M_files_4_swath interface~mapl_assert MAPL_Assert proc~read_m_files_4_swath->interface~mapl_assert none~debug~7 Logger%debug proc~read_m_files_4_swath->none~debug~7 proc~get_ncfile_dimension get_ncfile_dimension proc~read_m_files_4_swath->proc~get_ncfile_dimension proc~get_var_from_name_w_group get_var_from_name_w_group proc~read_m_files_4_swath->proc~get_var_from_name_w_group proc~mapl_return MAPL_Return proc~read_m_files_4_swath->proc~mapl_return proc~mapl_verify MAPL_Verify proc~read_m_files_4_swath->proc~mapl_verify proc~get_ncfile_dimension->proc~mapl_return proc~get_ncfile_dimension->proc~mapl_verify nf90_close nf90_close proc~get_ncfile_dimension->nf90_close nf90_inq_dimid nf90_inq_dimid proc~get_ncfile_dimension->nf90_inq_dimid nf90_inquire_dimension nf90_inquire_dimension proc~get_ncfile_dimension->nf90_inquire_dimension nf90_open nf90_open proc~get_ncfile_dimension->nf90_open proc~check_nc_status check_nc_status proc~get_ncfile_dimension->proc~check_nc_status proc~get_var_from_name_w_group->proc~mapl_return proc~get_var_from_name_w_group->proc~mapl_verify proc~get_var_from_name_w_group->nf90_close nf90_get_var nf90_get_var proc~get_var_from_name_w_group->nf90_get_var nf90_inq_ncid nf90_inq_ncid proc~get_var_from_name_w_group->nf90_inq_ncid nf90_inq_varid nf90_inq_varid proc~get_var_from_name_w_group->nf90_inq_varid proc~get_var_from_name_w_group->nf90_open proc~get_var_from_name_w_group->proc~check_nc_status 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 proc~check_nc_status->interface~mapl_assert proc~check_nc_status->proc~mapl_return nf90_strerror nf90_strerror proc~check_nc_status->nf90_strerror

Source Code

  subroutine read_M_files_4_swath ( filenames, Xdim, Ydim, &
       index_name_lon, index_name_lat,&
       var_name_lon, var_name_lat, var_name_time, &
       lon, lat, time, Tfilter, rc )
    use pFlogger, only: logging, Logger
    character(len=ESMF_MAXSTR), intent(in) :: filenames(:)
    integer,  intent(out) :: Xdim
    integer,  intent(out) :: Ydim
    character(len=ESMF_MAXSTR), intent(in) :: index_name_lon
    character(len=ESMF_MAXSTR), intent(in) :: index_name_lat
    character(len=ESMF_MAXSTR), optional, intent(in) :: var_name_lon
    character(len=ESMF_MAXSTR), optional, intent(in) :: var_name_lat
    character(len=ESMF_MAXSTR), optional, intent(in) :: var_name_time
    real(ESMF_KIND_R8), allocatable, optional, intent(inout) :: lon(:,:)
    real(ESMF_KIND_R8), allocatable, optional, intent(inout) :: lat(:,:)
    real(ESMF_KIND_R8), allocatable, optional, intent(inout) :: time(:,:)
    logical, optional, intent(in)  ::  Tfilter
    integer, optional, intent(out) :: rc

    integer :: M
    integer :: i, j, jx, j2, status
    integer :: nlon, nlat
    integer :: ncid, ncid2
    character(len=ESMF_MAXSTR) :: grp1, grp2
    integer :: varid
    logical :: found_group

    character(len=ESMF_MAXSTR) :: filename
    integer, allocatable :: nlons(:), nlats(:)
    real(ESMF_KIND_R8), allocatable :: time_loc_R8(:,:)
    real(ESMF_KIND_R8), allocatable :: lon_loc(:,:)
    real(ESMF_KIND_R8), allocatable :: lat_loc(:,:)
    class(Logger), pointer :: lgr

    !__ s1. get Xdim Ydim
    M = size(filenames)
    _ASSERT(M/=0, 'M is zero, no files found')
    lgr => logging%get_logger('MAPL.Sampler')

    allocate(nlons(M), nlats(M))
    jx=0
    do i = 1, M
       filename = filenames(i)
       CALL get_ncfile_dimension(filename, nlon=nlon, nlat=nlat, &
            key_lon=index_name_lon, key_lat=index_name_lat, _RC)
       nlons(i)=nlon
       nlats(i)=nlat
       jx=jx+nlat

       call lgr%debug('Input filename: %a', trim(filename))
       call lgr%debug('Input file    : nlon, nlat= %i6  %i6', nlon, nlat)
    end do
    !
    ! __ output results wo filter
    !
    Xdim=nlon
    Ydim=jx
    j2=jx

    !__ s2. get fields

    if ( present(Tfilter) .AND. Tfilter ) then
       if ( .not. (present(time) .AND. present(lon) .AND. present(lat)) ) then
          _FAIL('when Tfilter present, time/lon/lat must also present')
       end if

       !
       ! -- determine jx
       !
       jx=0
       do i = 1, M
          filename = filenames(i)
          nlon = nlons(i)
          nlat = nlats(i)
          allocate (time_loc_R8(nlon, nlat))
          call get_var_from_name_w_group (var_name_time, time_loc_R8, filename, _RC)
!!          write(6,*) 'af ith, filename', i, trim(filename)

          do j=1, nlat
             !
             ! -- filter, e.g., eliminate -9999
             !
             if ( time_loc_R8(1, j) > 0.0 ) then
                jx = jx + 1
             end if
          end do
          deallocate(time_loc_R8)
       end do
       Xdim=nlon
       Ydim=jx
       if (allocated (time)) then
          deallocate(time)
          allocate (time(Xdim, Ydim))
       end if
       if (allocated (lon)) then
          deallocate(lon)
          allocate (lon(Xdim, Ydim))
       end if
       if (allocated (lat)) then
          deallocate(lat)
          allocate (lat(Xdim, Ydim))
       end if
       !
       !!write(6,'(2x,a,10i10)') 'true  Xdim, Ydim:', Xdim, Ydim
       !!write(6,'(2x,a,10i10)') 'false Xdim, Ydim:', nlon, j2
       !


       !
       ! -- determine true time/lon/lat by filtering T < 0
       !
       jx=0
       do i = 1, M
          filename = filenames(i)
          nlon = nlons(i)
          nlat = nlats(i)
          !!write(6,'(2x,a,10i6)')  'M, i, nlon, nlat:', M, i, nlon, nlat
          !!write(6,'(2x,a)') 'time_loc_r8'
          !
          allocate (time_loc_R8(nlon, nlat))
          call get_var_from_name_w_group (var_name_time, time_loc_R8, filename, _RC)
          allocate (lon_loc(nlon, nlat))
          call get_var_from_name_w_group (var_name_lon, lon_loc, filename, _RC)
          allocate (lat_loc(nlon, nlat))
          call get_var_from_name_w_group (var_name_lat, lat_loc, filename, _RC)
          !
          do j=1, nlat
             !
             ! -- filter, e.g., eliminate -9999
             !
             if ( time_loc_R8(1, j) > 0.0 ) then
                jx = jx + 1
                time(1:nlon,jx) = time_loc_R8(1:nlon,j)
                lon (1:nlon,jx) = lon_loc (1:nlon,j)
                lat (1:nlon,jx) = lat_loc (1:nlon,j)
             end if
             !!write(6,'(5f20.2)') time_loc_R8(1,j)
          end do

          deallocate(time_loc_R8)
          deallocate(lon_loc)
          deallocate(lat_loc)
       end do

    else

       if (allocated (time)) then
          deallocate(time)
          allocate (time(Xdim, Ydim))
       end if
       if (allocated (lon)) then
          deallocate(lon)
          allocate (lon(Xdim, Ydim))
       end if
       if (allocated (lat)) then
          deallocate(lat)
          allocate (lat(Xdim, Ydim))
       end if

       jx=0
       do i = 1, M
          filename = filenames(i)
          nlon = nlons(i)
          nlat = nlats(i)

          if (present(var_name_time).AND.present(time)) then
             call get_var_from_name_w_group (var_name_time, time(1:nlon,jx+1:jx+nlat), filename, _RC)
          end if
          if (present(var_name_lon).AND.present(lon)) then
             call get_var_from_name_w_group (var_name_lon, lon(1:nlon,jx+1:jx+nlat), filename, _RC)
          end if
          if (present(var_name_lat).AND.present(lat)) then
             call get_var_from_name_w_group (var_name_lat, lat(1:nlon,jx+1:jx+nlat), filename, _RC)
          end if

          jx = jx + nlat
       end do

    end if

    _RETURN(_SUCCESS)
  end subroutine read_M_files_4_swath