Skip to content

Commit

Permalink
Merge pull request #2838 from GEOS-ESM/feature/ygyu/revise_stataion_s…
Browse files Browse the repository at this point in the history
…ampler

Improved station sampler
  • Loading branch information
mathomp4 authored Jun 24, 2024
2 parents 24885cf + 0b843ab commit d60d6f2
Show file tree
Hide file tree
Showing 5 changed files with 554 additions and 256 deletions.
6 changes: 3 additions & 3 deletions gridcomps/History/MAPL_HistoryGridComp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2426,11 +2426,11 @@ subroutine Initialize ( gc, import, dumexport, clock, rc )
call list(n)%trajectory%initialize(items=list(n)%items,bundle=list(n)%bundle,timeinfo=list(n)%timeInfo,vdata=list(n)%vdata,_RC)
IntState%stampoffset(n) = list(n)%trajectory%epoch_frequency
elseif (list(n)%sampler_spec == 'mask') then
list(n)%mask_sampler = MaskSamplerGeosat(cfg,string,clock,_RC)
list(n)%mask_sampler = MaskSamplerGeosat(cfg,string,clock,genstate=GENSTATE,_RC)
call list(n)%mask_sampler%initialize(items=list(n)%items,bundle=list(n)%bundle,timeinfo=list(n)%timeInfo,vdata=list(n)%vdata,_RC)
elseif (list(n)%sampler_spec == 'station') then
list(n)%station_sampler = StationSampler (trim(list(n)%stationIdFile), nskip_line=list(n)%stationSkipLine, _RC)
call list(n)%station_sampler%add_metadata_route_handle(list(n)%bundle,list(n)%timeInfo,vdata=list(n)%vdata,_RC)
list(n)%station_sampler = StationSampler (list(n)%bundle, trim(list(n)%stationIdFile), nskip_line=list(n)%stationSkipLine, genstate=GENSTATE, _RC)
call list(n)%station_sampler%add_metadata_route_handle(items=list(n)%items,bundle=list(n)%bundle,timeinfo=list(n)%timeInfo,vdata=list(n)%vdata,_RC)
else
global_attributes = list(n)%global_atts%define_collection_attributes(_RC)
if (index(trim(list(n)%output_grid_label), 'SwathGrid') > 0) then
Expand Down
14 changes: 7 additions & 7 deletions gridcomps/History/Sampler/MAPL_GeosatMaskMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ module MaskSamplerGeosatMod
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, intrinsic :: iso_fortran_env, only: REAL32
use, intrinsic :: iso_fortran_env, only: REAL64
use pflogger, only: Logger, logging
Expand Down Expand Up @@ -76,6 +77,7 @@ module MaskSamplerGeosatMod
real(kind=REAL64), allocatable :: lats(:)
integer, allocatable :: recvcounts(:)
integer, allocatable :: displs(:)
type(MAPL_MetaComp), pointer :: GENSTATE

real(kind=ESMF_KIND_R8), pointer:: obsTime(:)
real(kind=ESMF_KIND_R8), allocatable:: t_alongtrack(:)
Expand All @@ -92,7 +94,7 @@ module MaskSamplerGeosatMod
procedure :: add_metadata
procedure :: create_file_handle
procedure :: close_file_handle
procedure :: append_file => regrid_accumulate_append_file
procedure :: append_file => regrid_append_file
! procedure :: create_new_bundle
procedure :: create_grid => create_Geosat_grid_find_mask
procedure :: compute_time_for_current
Expand All @@ -104,14 +106,14 @@ module MaskSamplerGeosatMod


interface
module function MaskSamplerGeosat_from_config(config,string,clock,rc) result(mask)
module function MaskSamplerGeosat_from_config(config,string,clock,GENSTATE,rc) result(mask)
use BinIOMod
use pflogger, only : Logger, logging

type(MaskSamplerGeosat) :: 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 MaskSamplerGeosat_from_config

Expand Down Expand Up @@ -156,13 +158,11 @@ module subroutine close_file_handle(this,rc)
integer, optional, intent(out) :: rc
end subroutine close_file_handle

module subroutine regrid_accumulate_append_file(this,current_time,rc)
implicit none

module subroutine regrid_append_file(this,current_time,rc)
class(MaskSamplerGeosat), intent(inout) :: this
type(ESMF_Time), intent(inout) :: current_time
integer, optional, intent(out) :: rc
end subroutine regrid_accumulate_append_file
end subroutine regrid_append_file

module function compute_time_for_current(this,current_time,rc) result(rtime)
use MAPL_NetCDF, only : convert_NetCDF_DateTime_to_ESMF
Expand Down
23 changes: 13 additions & 10 deletions gridcomps/History/Sampler/MAPL_GeosatMaskMod_smod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,14 @@
implicit none
contains

module function MaskSamplerGeosat_from_config(config,string,clock,rc) result(mask)
module function MaskSamplerGeosat_from_config(config,string,clock,GENSTATE,rc) result(mask)
use BinIOMod
use pflogger, only : Logger, logging
type(MaskSamplerGeosat) :: 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

type(ESMF_Time) :: currTime
Expand All @@ -33,6 +34,8 @@ module function MaskSamplerGeosat_from_config(config,string,clock,rc) result(mas

mask%clock=clock
mask%grid_file_name=''
if (present(GENSTATE)) mask%GENSTATE => GENSTATE

call ESMF_ClockGet ( clock, CurrTime=currTime, _RC )
if (mapl_am_I_root()) write(6,*) 'string', string

Expand Down Expand Up @@ -342,7 +345,6 @@ module subroutine create_Geosat_grid_find_mask(this, rc)
obs_lats = lats_ds * MAPL_DEGREES_TO_RADIANS_R8
nx = size ( lons_ds )
allocate ( II(nx), JJ(nx), _STAT )
call MPI_Barrier(mpic, status)
call MAPL_GetHorzIJIndex(nx,II,JJ,lonR8=obs_lons,latR8=obs_lats,grid=grid,_RC)
call ESMF_VMBarrier (vm, _RC)

Expand Down Expand Up @@ -372,7 +374,6 @@ module subroutine create_Geosat_grid_find_mask(this, rc)

call ESMF_FieldHaloStore (fieldI4, routehandle=RH_halo, _RC)
call ESMF_FieldHalo (fieldI4, routehandle=RH_halo, _RC)
call ESMF_VMBarrier (vm, _RC)

k=0
do i=eLB(1), eUB(1)
Expand Down Expand Up @@ -429,7 +430,7 @@ module subroutine create_Geosat_grid_find_mask(this, rc)
lons(i) = lons_ptr (ix, jx)
lats(i) = lats_ptr (ix, jx)
end do
call ESMF_VMBarrier (vm, _RC)


iroot=0
if (mapl_am_i_root()) then
Expand Down Expand Up @@ -548,11 +549,11 @@ module subroutine add_metadata(this,rc)
endif
if (field_rank==2) then
vdims = "mask_index,time"
v = variable(type=PFIO_REAL32,dimensions=trim(vdims),chunksizes=[this%npt_mask_tot,1])
v = variable(type=PFIO_REAL32,dimensions=trim(vdims))
else if (field_rank==3) then
vdims = "lev,mask_index,time"
call ESMF_FieldGet(field,ungriddedLBound=lb,ungriddedUBound=ub,_RC)
v = variable(type=PFIO_REAL32,dimensions=trim(vdims),chunksizes=[ub(1)-lb(1)+1,1,1])
v = variable(type=PFIO_REAL32,dimensions=trim(vdims))
end if
call v%add_attribute('units', trim(units))
call v%add_attribute('long_name', trim(long_name))
Expand All @@ -567,7 +568,7 @@ module subroutine add_metadata(this,rc)
end subroutine add_metadata


module subroutine regrid_accumulate_append_file(this,current_time,rc)
module subroutine regrid_append_file(this,current_time,rc)
implicit none

class(MaskSamplerGeosat), intent(inout) :: this
Expand Down Expand Up @@ -651,15 +652,16 @@ module subroutine regrid_accumulate_append_file(this,current_time,rc)
iy = this%index_mask(2,j)
p_dst_2d(j) = p_src_2d(ix, iy)
end do
call MPI_Barrier(mpic, status)
nsend = nx
call MPI_gatherv ( p_dst_2d, nsend, MPI_REAL, &
p_dst_2d_full, this%recvcounts, this%displs, MPI_REAL,&
iroot, mpic, ierr )
call MAPL_TimerOn(this%GENSTATE,"put2D")
if (mapl_am_i_root()) then
call this%formatter%put_var(item%xname,p_dst_2d_full,&
start=[1,this%obs_written],count=[this%npt_mask_tot,1],_RC)
end if
call MAPL_TimerOff(this%GENSTATE,"put2D")
else if (rank==3) then
call ESMF_FieldGet(src_field,farrayptr=p_src_3d,_RC)
call ESMF_FieldGet(src_field,ungriddedLBound=lb,ungriddedUBound=ub,_RC)
Expand All @@ -673,12 +675,12 @@ module subroutine regrid_accumulate_append_file(this,current_time,rc)
p_dst_3d(m) = p_src_3d(ix, iy, k)
end do
end do
call MPI_Barrier(mpic, status)
!! write(6,'(2x,a,2x,i5,3x,10f8.1)') 'pet, p_dst_3d(j)', mypet, p_dst_3d(::10)
nsend = nx * nz
call MPI_gatherv ( p_dst_3d, nsend, MPI_REAL, &
p_dst_3d_full, recvcounts_3d, displs_3d, MPI_REAL,&
iroot, mpic, ierr )
call MAPL_TimerOn(this%GENSTATE,"put3D")
if (mapl_am_i_root()) then
allocate(arr(nz, this%npt_mask_tot), _STAT)
arr=reshape(p_dst_3d_full,[nz,this%npt_mask_tot],order=[1,2])
Expand All @@ -687,6 +689,7 @@ module subroutine regrid_accumulate_append_file(this,current_time,rc)
!note: lev,station,time
deallocate(arr, _STAT)
end if
call MAPL_TimerOff(this%GENSTATE,"put3D")
else
_FAIL('grid2LS regridder: rank > 3 not implemented')
end if
Expand All @@ -696,7 +699,7 @@ module subroutine regrid_accumulate_append_file(this,current_time,rc)
end do

_RETURN(_SUCCESS)
end subroutine regrid_accumulate_append_file
end subroutine regrid_append_file



Expand Down
Loading

0 comments on commit d60d6f2

Please sign in to comment.