MAPL_MaskMod.F90 Source File


This file depends on

sourcefile~~mapl_maskmod.f90~~EfferentGraph sourcefile~mapl_maskmod.f90 MAPL_MaskMod.F90 sourcefile~base_base.f90 Base_Base.F90 sourcefile~mapl_maskmod.f90->sourcefile~base_base.f90 sourcefile~binio.f90 BinIO.F90 sourcefile~mapl_maskmod.f90->sourcefile~binio.f90 sourcefile~filemetadata.f90 FileMetadata.F90 sourcefile~mapl_maskmod.f90->sourcefile~filemetadata.f90 sourcefile~filemetadatautilities.f90 FileMetadataUtilities.F90 sourcefile~mapl_maskmod.f90->sourcefile~filemetadatautilities.f90 sourcefile~griddedioitem.f90 GriddedIOitem.F90 sourcefile~mapl_maskmod.f90->sourcefile~griddedioitem.f90 sourcefile~mapl_comms.f90 MAPL_Comms.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_comms.f90 sourcefile~mapl_errorhandling.f90 MAPL_ErrorHandling.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_errorhandling.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_keywordenforcer.f90 MAPL_KeywordEnforcer.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_keywordenforcer.f90 sourcefile~mapl_locstreamfactorymod.f90 MAPL_LocStreamFactoryMod.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_locstreamfactorymod.f90 sourcefile~mapl_locstreamregridder.f90 MAPL_LocstreamRegridder.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_locstreamregridder.f90 sourcefile~mapl_netcdf.f90 MAPL_NetCDF.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_netcdf.f90 sourcefile~mapl_obsutil.f90 MAPL_ObsUtil.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_obsutil.f90 sourcefile~mapl_sort.f90 MAPL_Sort.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_sort.f90 sourcefile~mapl_timemethods.f90 MAPL_TimeMethods.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_timemethods.f90 sourcefile~mapl_verticalmethods.f90 MAPL_VerticalMethods.F90 sourcefile~mapl_maskmod.f90->sourcefile~mapl_verticalmethods.f90 sourcefile~netcdf4_fileformatter.f90 NetCDF4_FileFormatter.F90 sourcefile~mapl_maskmod.f90->sourcefile~netcdf4_fileformatter.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~mapl_maskmod.f90->sourcefile~pfio.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~mapl_maskmod.f90->sourcefile~pflogger_stub.f90 sourcefile~plain_netcdf_time.f90 Plain_netCDF_Time.F90 sourcefile~mapl_maskmod.f90->sourcefile~plain_netcdf_time.f90 sourcefile~stringtemplate.f90 StringTemplate.F90 sourcefile~mapl_maskmod.f90->sourcefile~stringtemplate.f90

Files dependent on this one

sourcefile~~mapl_maskmod.f90~~AfferentGraph sourcefile~mapl_maskmod.f90 MAPL_MaskMod.F90 sourcefile~mapl_historycollection.f90 MAPL_HistoryCollection.F90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_maskmod.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_maskmod.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_historycollection.f90 sourcefile~mapl_maskmod_smod.f90 MAPL_MaskMod_smod.F90 sourcefile~mapl_maskmod_smod.f90->sourcefile~mapl_maskmod.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivermod.f90 sourcefile~extdatadrivermod.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~mapl_gridcomps.f90 MAPL_GridComps.F90 sourcefile~mapl_gridcomps.f90->sourcefile~mapl_cap.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~mapl_cap.f90

Source Code

module MaskSamplerMod
  use ESMF
  use MAPL_ErrorHandlingMod
  use MAPL_KeywordEnforcerMod
  use LocStreamFactoryMod
  use MAPL_LocstreamRegridderMod
  use MAPL_FileMetadataUtilsMod
  use pFIO
  use MAPL_GriddedIOItemMod
  use MAPL_GriddedIOItemVectorMod
  use MAPL_TimeDataMod
  use MAPL_VerticalDataMod
  use MAPL_BaseMod
  use MAPL_CommsMod
  use MAPL_SortMod
  use MAPL_NetCDF
  use MAPL_StringTemplate
  use gFTL_StringVector
  use gFTL_StringStringMap
  use Plain_netCDF_Time
  use MAPL_ObsUtilMod
  use MPI
  use pFIO_FileMetadataMod, only : FileMetadata
  use pFIO_NetCDF4_FileFormatterMod, only : NetCDF4_FileFormatter
  use MAPL_GenericMod, only : MAPL_MetaComp, MAPL_TimerOn, MAPL_TimerOff
  use MPI, only  :  MPI_INTEGER, MPI_REAL, MPI_REAL8
  use, intrinsic :: iso_fortran_env, only: REAL32
  use, intrinsic :: iso_fortran_env, only: REAL64
  use pflogger, only: Logger, logging
  implicit none
  intrinsic :: size

  private

  public :: var2d_unit
  public :: var3d_unit
  type :: var2d_unit
     real(kind=REAL32), allocatable :: array_x(:)
  end type var2d_unit

  type :: var3d_unit
     real(kind=REAL32), allocatable :: array_xz(:,:)
  end type var3d_unit


  public :: MaskSampler
  type :: MaskSampler
     character(len=ESMF_MAXSTR) :: grid_file_name
     !     we need on each PET
     !     npt_mask, index_mask(1:2,npt_mask)=[i,j]
     !
     integer :: npt_mask
     integer :: npt_mask_tot
     integer :: i1, in
     integer, allocatable :: index_mask(:,:)
     type(ESMF_FieldBundle) :: bundle
     type(GriddedIOitemVector) :: items
     type(VerticalData) :: vdata
     type(var2d_unit), allocatable :: var2d(:)
     type(var3d_unit), allocatable :: var3d(:)
     logical :: do_vertical_regrid
     type(TimeData)           :: timeinfo
     type(ESMF_Clock)         :: clock
     type(ESMF_Time)          :: RingTime
     type(ESMF_TimeInterval)  :: epoch_frequency
     type(FileMetadata), allocatable, public:: metadata
     type(NetCDF4_FileFormatter) :: formatter
     character(len=ESMF_MAXSTR)  :: ofile
     integer :: write_collection_id
     logical :: use_pfio
     !
     integer                        :: nobs
     integer                        :: obs_written
     character(len=ESMF_MAXSTR)     :: index_name_x
     character(len=ESMF_MAXSTR)     :: index_name_y
     character(len=ESMF_MAXSTR)     :: index_name_location
     character(len=ESMF_MAXSTR)     :: index_name_lon
     character(len=ESMF_MAXSTR)     :: index_name_lat
     character(len=ESMF_MAXSTR)     :: index_name_loc
     character(len=ESMF_MAXSTR)     :: var_name_time
     character(len=ESMF_MAXSTR)     :: var_name_lat
     character(len=ESMF_MAXSTR)     :: var_name_lon
     character(len=ESMF_MAXSTR)     :: var_name_x
     character(len=ESMF_MAXSTR)     :: var_name_y
     character(len=ESMF_MAXSTR)     :: var_name_proj
     character(len=ESMF_MAXSTR)     :: att_name_proj

     integer :: xdim_true
     integer :: ydim_true
     integer :: thin_factor

     integer                        :: epoch        ! unit: second
     integer(kind=ESMF_KIND_I8)     :: epoch_index(2)
     real(kind=REAL64), allocatable :: lons(:)
     real(kind=REAL64), allocatable :: lats(:)
     real(kind=REAL32), allocatable :: lons_deg(:)
     real(kind=REAL32), allocatable :: lats_deg(:)

     real(kind=REAL32) :: rtime
     integer, allocatable :: recvcounts(:)
     integer, allocatable :: displs(:)
     type(MAPL_MetaComp), pointer :: GENSTATE

     integer, allocatable :: local_start(:)
     integer, allocatable :: global_start(:)
     integer, allocatable :: global_count(:)

     real, allocatable :: array_scalar_1d(:)
     real, allocatable :: array_scalar_2d(:,:)
     real, allocatable :: array_scalar_3d(:,:,:)
     logical :: itemOrderAlphabetical = .true.

     integer :: tmax     ! duration / freq

     real(kind=ESMF_KIND_R8), pointer:: obsTime(:)
     real(kind=ESMF_KIND_R8), allocatable:: t_alongtrack(:)
     integer                        :: nobs_dur
     integer                        :: nobs_dur_sum
     type(ESMF_Time)                :: obsfile_start_time   ! user specify
     type(ESMF_Time)                :: obsfile_end_time
     type(ESMF_TimeInterval)        :: obsfile_interval
     integer                        :: obsfile_Ts_index     ! for epoch
     integer                        :: obsfile_Te_index
     logical                        :: is_valid
   contains

     procedure :: initialize
     procedure :: finalize
     procedure :: create_metadata
     procedure :: regrid_append_file
     procedure :: create_Geosat_grid_find_mask
     procedure :: compute_time_for_current
     procedure :: set_param
     procedure :: stage2dlatlon
     procedure :: modifytime
     procedure :: alphabatize_variables
  end type MaskSampler

  interface MaskSampler
     module procedure MaskSampler_from_config
  end interface MaskSampler

  interface
     module function MaskSampler_from_config(config,string,clock,GENSTATE,rc) result(mask)
       use BinIOMod
       use pflogger, only         :  Logger, logging
       type(MaskSampler) :: mask
       type(ESMF_Config), intent(inout)        :: config
       character(len=*),  intent(in)           :: string
       type(ESMF_Clock),  intent(in)           :: clock
       type(MAPL_MetaComp), pointer, intent(in), optional  :: GENSTATE
       integer, optional, intent(out)          :: rc
     end function MaskSampler_from_config

     module subroutine initialize(this,duration,frequency,items,bundle,timeInfo,vdata,global_attributes,reinitialize,rc)
       class(MaskSampler), intent(inout) :: this
       integer, intent(in) :: duration
       integer, intent(in) :: frequency
       type(GriddedIOitemVector), optional, intent(inout) :: items
       type(ESMF_FieldBundle), optional, intent(inout)   :: bundle
       type(TimeData), optional, intent(inout)           :: timeInfo
       type(VerticalData), optional, intent(inout)       :: vdata
       type(StringStringMap), target, intent(in), optional :: global_attributes
       logical, optional, intent(in)           :: reinitialize
       integer, optional, intent(out)          :: rc
     end subroutine initialize

     module subroutine finalize(this,rc)
       class(MaskSampler), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine finalize

     module subroutine create_Geosat_grid_find_mask(this, rc)
       use pflogger, only: Logger, logging
       implicit none
       class(MaskSampler), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine create_Geosat_grid_find_mask

     module subroutine  create_metadata(this,global_attributes,rc)
       class(MaskSampler), intent(inout) :: this
       type(StringStringMap), target, intent(in) :: global_attributes
       integer, optional, intent(out)          :: rc
     end subroutine create_metadata

     module subroutine regrid_append_file (this,current_time,filename,oClients,rc)
       class(MaskSampler), intent(inout)       :: this
       type(ESMF_Time), intent(inout)          :: current_time
       character(len=*), intent(in)            :: filename
       type (ClientManager), target, optional, intent(inout) :: oClients
       integer, optional, intent(out)          :: rc
     end subroutine regrid_append_file

     module subroutine set_param(this,deflation,quantize_algorithm,quantize_level,chunking,&
          nbits_to_keep,regrid_method,itemOrder,write_collection_id,regrid_hints,oClients,rc)
       class (MaskSampler), intent(inout) :: this
       integer, optional, intent(in) :: deflation
       integer, optional, intent(in) :: quantize_algorithm
       integer, optional, intent(in) :: quantize_level
       integer, optional, intent(in) :: chunking(:)
       integer, optional, intent(in) :: nbits_to_keep
       integer, optional, intent(in) :: regrid_method
       logical, optional, intent(in) :: itemOrder
       integer, optional, intent(in) :: write_collection_id
       integer, optional, intent(in) :: regrid_hints
       type (ClientManager), optional, intent(in) :: oClients
       integer, optional, intent(out) :: rc
     end subroutine set_param

     module subroutine stage2dlatlon(this,filename,oClients,rc)
       class(MaskSampler), intent(inout) :: this
       character(len=*), intent(in) :: fileName
       type (ClientManager), optional, target, intent(inout) :: oClients
       integer, optional, intent(out) :: rc
     end subroutine stage2dlatlon

     module function compute_time_for_current(this,current_time,rc) result(rtime)
       use  MAPL_NetCDF, only : convert_NetCDF_DateTime_to_ESMF
       class(MaskSampler), intent(inout) :: this
       type(ESMF_Time), intent(in) :: current_time
       integer, optional, intent(out) :: rc
       real(kind=ESMF_KIND_R8) :: rtime
     end function compute_time_for_current

    module subroutine modifyTime(this, oClients, rc)
      class(MaskSampler), intent(inout) :: this
      type (ClientManager), optional, intent(inout) :: oClients
      integer, optional, intent(out) :: rc
    end subroutine modifyTime

    module subroutine alphabatize_variables(this,nfixedVars,rc)
      class (MaskSampler), intent(inout) :: this
      integer, intent(in) :: nFixedVars
      integer, optional, intent(out) :: rc
    end subroutine alphabatize_variables

  end interface
end module MaskSamplerMod