Skip to content

Commit

Permalink
Initial added files
Browse files Browse the repository at this point in the history
  • Loading branch information
metdyn committed Nov 14, 2024
1 parent ad0a569 commit 922e7ce
Show file tree
Hide file tree
Showing 8 changed files with 595 additions and 280 deletions.
4 changes: 2 additions & 2 deletions gridcomps/History/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@ set (srcs
MAPL_HistoryCollection.F90
MAPL_HistoryGridComp.F90
Sampler/MAPL_EpochSwathMod.F90
Sampler/MAPL_GeosatMaskMod.F90
Sampler/MAPL_GeosatMaskMod_smod.F90
Sampler/MAPL_MaskMod.F90
Sampler/MAPL_MaskMod_smod.F90
Sampler/MAPL_StationSamplerMod.F90
Sampler/MAPL_TrajectoryMod.F90
Sampler/MAPL_TrajectoryMod_smod.F90
Expand Down
4 changes: 2 additions & 2 deletions gridcomps/History/MAPL_HistoryCollection.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module MAPL_HistoryCollectionMod
use MAPL_VerticalDataMod
use MAPL_TimeDataMod
use HistoryTrajectoryMod
use MaskSamplerGeosatMod
use MaskSamplerMod
use StationSamplerMod
use gFTL_StringStringMap
use MAPL_EpochSwathMod
Expand Down Expand Up @@ -112,7 +112,7 @@ module MAPL_HistoryCollectionMod
logical :: timeseries_output = .false.
logical :: recycle_track = .false.
type(HistoryTrajectory) :: trajectory
type(MaskSamplerGeosat) :: mask_sampler
type(MaskSampler) :: mask_sampler
type(StationSampler) :: station_sampler
character(len=ESMF_MAXSTR) :: sampler_spec = ""
character(len=ESMF_MAXSTR) :: positive
Expand Down
43 changes: 30 additions & 13 deletions gridcomps/History/MAPL_HistoryGridComp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ module MAPL_HistoryGridCompMod
use pFIO_ConstantsMod
use HistoryTrajectoryMod
use StationSamplerMod
use MaskSamplerGeosatMod
use MaskSamplerMod
use MAPL_StringTemplate
use regex_module
use MAPL_TimeUtilsMod, only: is_valid_time, is_valid_date
Expand Down Expand Up @@ -2453,8 +2453,12 @@ subroutine Initialize ( gc, import, dumexport, clock, rc )
IntState%stampoffset(n) = list(n)%trajectory%epoch_frequency
elseif (list(n)%sampler_spec == 'mask') then
call MAPL_TimerOn(GENSTATE,"mask_init")
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)
list(n)%mask_sampler = MaskSampler(cfg,string,clock,genstate=GENSTATE,_RC)
! initialize + create metadata
call list(n)%mask_sampler%initialize(list(n)%duration,list(n)%frequency,items=list(n)%items,&
bundle=list(n)%bundle,timeinfo=list(n)%timeInfo,vdata=list(n)%vdata,_RC)
collection_id = o_Clients%add_hist_collection(list(n)%mask_sampler%metadata, mode = create_mode)
call list(n)%mask_sampler%set_param(write_collection_id=collection_id)
call MAPL_TimerOff(GENSTATE,"mask_init")
elseif (list(n)%sampler_spec == 'station') then
list(n)%station_sampler = StationSampler (list(n)%bundle, trim(list(n)%stationIdFile), nskip_line=list(n)%stationSkipLine, genstate=GENSTATE, _RC)
Expand Down Expand Up @@ -3494,7 +3498,7 @@ subroutine Run ( gc, import, export, clock, rc )
if (intState%allow_overwrite) create_mode = PFIO_CLOBBER
! add time to items
! true metadata comes here from mGriddedIO%metadata
! the mGriddedIO below only touches metadata, collection_id etc., it is safe.
! list(n)%mgriddedio for swath changed due to grid change
!
if (.NOT. list(n)%xsampler%have_initalized) then
list(n)%xsampler%have_initalized = .true.
Expand All @@ -3507,6 +3511,9 @@ subroutine Run ( gc, import, export, clock, rc )
call list(n)%mGriddedIO%destroy(_RC)
call list(n)%mGriddedIO%CreateFileMetaData(list(n)%items,list(n)%xsampler%acc_bundle,timeinfo_uninit,vdata=list(n)%vdata,global_attributes=global_attributes,_RC)
call list(n)%items%pop_back()
!
! we may have a memory leakage here: o_Clients should first delete the old metada
!
collection_id = o_Clients%add_hist_collection(list(n)%mGriddedIO%metadata, mode = create_mode)
call list(n)%mGriddedIO%set_param(write_collection_id=collection_id)
call MAPL_TimerOff(GENSTATE,"RegenGriddedio")
Expand Down Expand Up @@ -3587,13 +3594,19 @@ subroutine Run ( gc, import, export, clock, rc )
list(n)%unit = -1
end if
elseif (list(n)%sampler_spec == 'mask') then
if (list(n)%unit.eq.0) then
call lgr%debug('%a %a',&
"Mask_data output to new file:",trim(filename(n)))
call list(n)%mask_sampler%close_file_handle(_RC)
call list(n)%mask_sampler%create_file_handle(filename(n),_RC)
list(n)%currentFile = filename(n)
list(n)%unit = -1
if( list(n)%unit.eq.0 ) then
if (list(n)%format == 'CFIO') then
if (.not.intState%allow_overwrite) then
inquire (file=trim(filename(n)),exist=file_exists)
_ASSERT(.not.file_exists,trim(filename(n))//" being created for History output already exists")
end if
if (mapl_am_i_root()) write(6,*) 'this line for mask %modifyTime'
call list(n)%mask_sampler%modifyTime(oClients=o_Clients,_RC)
list(n)%currentFile = filename(n)
list(n)%unit = -1
else
list(n)%unit = GETFILE( trim(filename(n)),all_pes=.true.)
end if
end if
else
if( list(n)%unit.eq.0 ) then
Expand Down Expand Up @@ -3738,11 +3751,14 @@ subroutine Run ( gc, import, export, clock, rc )
elseif (list(n)%sampler_spec == 'mask') then
call ESMF_ClockGet(clock,currTime=current_time,_RC)
call MAPL_TimerOn(GENSTATE,"Mask_append")
call list(n)%mask_sampler%append_file(current_time,_RC)
if (list(n)%unit < 0) then ! CFIO
call list(n)%mask_sampler%output_to_server(current_time,&
list(n)%currentFile,oClients=o_Clients,_RC)
if (mapl_am_i_root()) write(6,*) 'af list(n)%mask_sampler%output_to_server'
end if
call MAPL_TimerOff(GENSTATE,"Mask_append")
endif


endif OUTTIME

if( NewSeg(n) .and. list(n)%unit /= 0 .and. list(n)%duration /= 0 ) then
Expand All @@ -3757,6 +3773,7 @@ subroutine Run ( gc, import, export, clock, rc )
enddo POSTLOOP



call MAPL_TimerOn(GENSTATE,"Done Wait")
if (any(writing)) then
call o_Clients%done_collective_stage(_RC)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module MaskSamplerGeosatMod
module MaskSamplerMod
use ESMF
use MAPL_ErrorHandlingMod
use MAPL_KeywordEnforcerMod
Expand Down Expand Up @@ -29,28 +29,30 @@ module MaskSamplerGeosatMod

private

public :: MaskSamplerGeosat
type :: MaskSamplerGeosat
public :: MaskSampler
type :: MaskSampler
private
! character(len=:), allocatable :: grid_file_name
character(len=ESMF_MAXSTR) :: grid_file_name
! we need on each PET
! 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
logical :: do_vertical_regrid
type(TimeData) :: time_info
type(TimeData) :: timeinfo
type(ESMF_Clock) :: clock
type(ESMF_Time) :: RingTime
type(ESMF_TimeInterval) :: epoch_frequency
type(FileMetadata) :: metadata
type(FileMetadata), allocatable, public:: metadata
type(NetCDF4_FileFormatter) :: formatter
character(len=ESMF_MAXSTR) :: ofile
character(len=ESMF_MAXSTR) :: ofile
integer :: write_collection_id
!
integer :: nobs
integer :: obs_written
Expand All @@ -76,10 +78,30 @@ module MaskSamplerGeosatMod
integer(kind=ESMF_KIND_I8) :: epoch_index(2)
real(kind=REAL64), allocatable :: lons(:)
real(kind=REAL64), allocatable :: lats(:)
real(kind=REAL64), allocatable :: lons_deg(:)
real(kind=REAL64), allocatable :: lats_deg(:)
! real, allocatable :: lons_deg(:)
! real, allocatable :: lats_deg(:)
real, allocatable :: times(:)
integer, allocatable :: recvcounts(:)
integer, allocatable :: displs(:)
type(MAPL_MetaComp), pointer :: GENSTATE

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

! real, target, allocatable :: array_scalar_2d(:,:,:) ! (nx, nitem, ntime_seg)
real, allocatable :: array_scalar_2d(:,:)
real, allocatable :: array_scalar_3d(:,:,:)
! real, target, allocatable :: array_vector_2d(:,:,:)
! real, target, allocatable :: array_vector_3d(:,:,:,:)
real, pointer :: x1(:) => null()
real, pointer :: p1d(:) => null()

integer :: call_count
integer :: tmax ! duration / freq

real(kind=ESMF_KIND_R8), pointer:: obsTime(:)
real(kind=ESMF_KIND_R8), allocatable:: t_alongtrack(:)
integer :: nobs_dur
Expand All @@ -92,34 +114,36 @@ module MaskSamplerGeosatMod
logical :: is_valid
contains
procedure :: initialize => initialize_
procedure :: add_metadata
procedure :: create_file_handle
procedure :: close_file_handle
procedure :: append_file => regrid_append_file
! procedure :: create_new_bundle
procedure :: create_metadata
!! procedure :: create_file_handle
procedure :: output_to_server
procedure :: create_grid => create_Geosat_grid_find_mask
procedure :: compute_time_for_current
end type MaskSamplerGeosat

interface MaskSamplerGeosat
module procedure MaskSamplerGeosat_from_config
end interface MaskSamplerGeosat
procedure :: set_param
procedure :: stage2dlatlon
procedure :: modifytime
end type MaskSampler

interface MaskSampler
module procedure MaskSampler_from_config
end interface MaskSampler

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

module subroutine initialize_(this,items,bundle,timeInfo,vdata,reinitialize,rc)
class(MaskSamplerGeosat), intent(inout) :: this
module subroutine initialize_(this,duration,frequency,items,bundle,timeInfo,vdata,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
Expand All @@ -132,47 +156,84 @@ module subroutine create_Geosat_grid_find_mask(this, rc)
use pflogger, only: Logger, logging
implicit none

class(MaskSamplerGeosat), intent(inout) :: this
class(MaskSampler), intent(inout) :: this
integer, optional, intent(out) :: rc
end subroutine create_Geosat_grid_find_mask

!! module function create_new_bundle(this,rc) result(new_bundle)
!! class(MaskSamplerGeosat), intent(inout) :: this
!! type(ESMF_FieldBundle) :: new_bundle
!! integer, optional, intent(out) :: rc
!! end function create_new_bundle

!! module subroutine add_metadata(this,currTime,rc)
module subroutine add_metadata(this,rc)
class(MaskSamplerGeosat), intent(inout) :: this
!! module subroutine set_param(this,deflation,quantize_algorithm,quantize_level,chunking,nbits_to_keep,regrid_method,itemOrder,write_collection_id,regrid_hints,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
!! integer, optional, intent(out) :: rc
!! end subroutine set_param

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

module subroutine create_file_handle(this,filename,rc)
class(MaskSamplerGeosat), intent(inout) :: this
class(MaskSampler), intent(inout) :: this
character(len=*), intent(in) :: filename
integer, optional, intent(out) :: rc
end subroutine create_file_handle

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

module subroutine regrid_append_file(this,current_time,rc)
class(MaskSamplerGeosat), intent(inout) :: this
module subroutine output_to_server(this,current_time,filename,oClients,rc)
class(MaskSampler), target, 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
end subroutine output_to_server

module subroutine set_param(this,deflation,quantize_algorithm,quantize_level,chunking,&
nbits_to_keep,regrid_method,itemOrder,write_collection_id,regrid_hints,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
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(MaskSamplerGeosat), intent(inout) :: this
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

end interface
end module MaskSamplerGeosatMod
end module MaskSamplerMod
Loading

0 comments on commit 922e7ce

Please sign in to comment.