MAPL_HistoryTrajectoryMod.F90 Source File


This file depends on

sourcefile~~mapl_historytrajectorymod.f90~~EfferentGraph sourcefile~mapl_historytrajectorymod.f90 MAPL_HistoryTrajectoryMod.F90 sourcefile~filemetadatautilities.f90 FileMetadataUtilities.F90 sourcefile~mapl_historytrajectorymod.f90->sourcefile~filemetadatautilities.f90 sourcefile~griddedioitem.f90 GriddedIOitem.F90 sourcefile~mapl_historytrajectorymod.f90->sourcefile~griddedioitem.f90 sourcefile~mapl_locstreamfactorymod.f90 MAPL_LocStreamFactoryMod.F90 sourcefile~mapl_historytrajectorymod.f90->sourcefile~mapl_locstreamfactorymod.f90 sourcefile~mapl_locstreamregridder.f90 MAPL_LocstreamRegridder.F90 sourcefile~mapl_historytrajectorymod.f90->sourcefile~mapl_locstreamregridder.f90 sourcefile~mapl_timemethods.f90 MAPL_TimeMethods.F90 sourcefile~mapl_historytrajectorymod.f90->sourcefile~mapl_timemethods.f90 sourcefile~mapl_verticalmethods.f90 MAPL_VerticalMethods.F90 sourcefile~mapl_historytrajectorymod.f90->sourcefile~mapl_verticalmethods.f90 sourcefile~mapl_abstractgridfactory.f90 MAPL_AbstractGridFactory.F90 sourcefile~filemetadatautilities.f90->sourcefile~mapl_abstractgridfactory.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~filemetadatautilities.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_gridmanager.f90 MAPL_GridManager.F90 sourcefile~filemetadatautilities.f90->sourcefile~mapl_gridmanager.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~filemetadatautilities.f90->sourcefile~pfio.f90 sourcefile~constants.f90 Constants.F90 sourcefile~mapl_locstreamfactorymod.f90->sourcefile~constants.f90 sourcefile~mapl_errorhandling.f90 MAPL_ErrorHandling.F90 sourcefile~mapl_locstreamfactorymod.f90->sourcefile~mapl_errorhandling.f90 sourcefile~mapl_keywordenforcer.f90 MAPL_KeywordEnforcer.F90 sourcefile~mapl_locstreamfactorymod.f90->sourcefile~mapl_keywordenforcer.f90 sourcefile~mapl_locstreamregridder.f90->sourcefile~mapl_errorhandling.f90 sourcefile~mapl_locstreamregridder.f90->sourcefile~mapl_keywordenforcer.f90 sourcefile~base_base.f90 Base_Base.F90 sourcefile~mapl_timemethods.f90->sourcefile~base_base.f90 sourcefile~mapl_esmftimevectormod.f90 MAPL_ESMFTimeVectorMod.F90 sourcefile~mapl_timemethods.f90->sourcefile~mapl_esmftimevectormod.f90 sourcefile~mapl_timemethods.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_timemethods.f90->sourcefile~pfio.f90 sourcefile~mapl_verticalmethods.f90->sourcefile~base_base.f90 sourcefile~mapl_abstractregridder.f90 MAPL_AbstractRegridder.F90 sourcefile~mapl_verticalmethods.f90->sourcefile~mapl_abstractregridder.f90 sourcefile~mapl_verticalmethods.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl_verticalmethods.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl_verticalmethods.f90->sourcefile~pfio.f90

Files dependent on this one

sourcefile~~mapl_historytrajectorymod.f90~~AfferentGraph sourcefile~mapl_historytrajectorymod.f90 MAPL_HistoryTrajectoryMod.F90 sourcefile~mapl_historycollection.f90 MAPL_HistoryCollection.F90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_historytrajectorymod.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_historytrajectorymod.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_historycollection.f90 sourcefile~mapl_historytrajectorymod_smod.f90 MAPL_HistoryTrajectoryMod_smod.F90 sourcefile~mapl_historytrajectorymod_smod.f90->sourcefile~mapl_historytrajectorymod.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 HistoryTrajectoryMod
  use ESMF
  use MAPL_FileMetadataUtilsMod
  use MAPL_GriddedIOItemVectorMod
  use MAPL_TimeDataMod
  use MAPL_VerticalDataMod
  use LocStreamFactoryMod
  use MAPL_LocstreamRegridderMod
  use, intrinsic :: iso_fortran_env, only: REAL32, REAL64
  implicit none
  private

  public :: obs_unit
  type :: obs_unit
     integer :: nobs_epoch
     type(FileMetadata), allocatable            :: metadata
     type(NetCDF4_FileFormatter), allocatable   :: file_handle
     character(len=ESMF_MAXSTR)                 :: name
     character(len=ESMF_MAXSTR)                 :: obsFile_output
     character(len=ESMF_MAXSTR)                 :: input_template
     real(kind=REAL64), allocatable :: lons(:)
     real(kind=REAL64), allocatable :: lats(:)
     real(kind=REAL64), allocatable :: times_R8(:)
     real(kind=REAL32), allocatable :: p2d(:)
     real(kind=REAL32), allocatable :: p3d(:,:)
  end type obs_unit

  public :: HistoryTrajectory

  type :: HistoryTrajectory
     private
     type(ESMF_LocStream)   :: LS_rt
     type(ESMF_LocStream)   :: LS_ds
     type(LocStreamFactory) :: locstream_factory
     type(obs_unit), allocatable    :: obs(:)
     type(ESMF_Time),   allocatable :: times(:)
     real(kind=REAL64), allocatable :: lons(:)
     real(kind=REAL64), allocatable :: lats(:)
     real(kind=REAL64), allocatable :: times_R8(:)
     integer,           allocatable :: obstype_id(:)

     type(ESMF_FieldBundle) :: bundle
     type(ESMF_FieldBundle) :: output_bundle
     type(ESMF_FieldBundle) :: acc_bundle
     type(ESMF_Field)       :: fieldA
     type(ESMF_Field)       :: fieldB

     type(GriddedIOitemVector) :: items
     type(VerticalData) :: vdata
     logical :: do_vertical_regrid

     type(LocstreamRegridder) :: regridder
     type(TimeData) :: time_info
     logical :: recycle_track
     type(ESMF_Clock)         :: clock
     type(ESMF_Alarm), public :: alarm
     type(ESMF_Time)          :: RingTime
     type(ESMF_TimeInterval)  :: epoch_frequency

     integer                        :: nobs_type
     character(len=ESMF_MAXSTR)     :: nc_index
     character(len=ESMF_MAXSTR)     :: nc_time
     character(len=ESMF_MAXSTR)     :: nc_latitude
     character(len=ESMF_MAXSTR)     :: nc_longitude
     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)     :: datetime_units
     integer                        :: epoch        ! unit: second
     integer(kind=ESMF_KIND_I8)     :: epoch_index(2)
     real(kind=ESMF_KIND_R8), pointer:: obsTime(:)
     integer                        :: nobs_epoch
     integer                        :: nobs_epoch_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 :: reinitialize
     procedure :: create_variable => create_metadata_variable
     procedure :: create_file_handle
     procedure :: close_file_handle
     procedure :: append_file
     procedure :: create_new_bundle
     procedure :: reset_times_to_current_day
     procedure :: time_real_to_ESMF
     procedure :: create_grid
     procedure :: regrid_accumulate => regrid_accumulate_on_xsubset
     procedure :: destroy_rh_regen_LS
     procedure :: get_x_subset
     procedure :: get_obsfile_Tbracket_from_epoch
     procedure :: get_filename_from_template_use_index
  end type HistoryTrajectory

  interface HistoryTrajectory
     module procedure HistoryTrajectory_from_config
  end interface HistoryTrajectory

  interface sort_multi_arrays_by_time
     module procedure  sort_three_arrays_by_time
     module procedure  sort_four_arrays_by_time
  end interface sort_multi_arrays_by_time

  interface
     module function HistoryTrajectory_from_config(config,string,clock,rc) result(traj)
       type(HistoryTrajectory) :: traj
       type(ESMF_Config), intent(inout)        :: config
       character(len=*),  intent(in)           :: string
       type(ESMF_Clock),  intent(in)           :: clock
       integer, optional, intent(out)          :: rc
     end function HistoryTrajectory_from_config

     module subroutine initialize(this,items,bundle,timeInfo,vdata,recycle_track,rc)
       class(HistoryTrajectory), intent(inout) :: this
       type(GriddedIOitemVector), target, intent(inout) :: items
       type(ESMF_FieldBundle), intent(inout)   :: bundle
       type(TimeData), intent(inout)           :: timeInfo
       type(VerticalData), optional, intent(inout) :: vdata
       logical, optional, intent(inout)        :: recycle_track
       integer, optional, intent(out)          :: rc
     end subroutine initialize

     module subroutine reinitialize(this,rc)
       class(HistoryTrajectory), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine reinitialize

     module subroutine  create_metadata_variable(this,vname,rc)
       class(HistoryTrajectory), intent(inout) :: this
       character(len=*), intent(in)            :: vname
       integer, optional, intent(out)          :: rc
     end subroutine create_metadata_variable

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

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

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

     module subroutine append_file(this,current_time,rc)
       class(HistoryTrajectory), intent(inout) :: this
       type(ESMF_Time), intent(inout)          :: current_time
       integer, optional, intent(out)          :: rc
     end subroutine append_file

     module subroutine reset_times_to_current_day(this,rc)
       class(HistoryTrajectory), intent(Inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine reset_times_to_current_day

     module subroutine sort_three_arrays_by_time(U,V,T,rc)
       real(ESMF_KIND_R8) :: U(:), V(:), T(:)
       integer, optional, intent(out)          :: rc
     end subroutine sort_three_arrays_by_time

     module subroutine sort_four_arrays_by_time(U,V,T,ID,rc)
       real(ESMF_KIND_R8) :: U(:), V(:), T(:)
       integer :: ID(:)
       integer, optional, intent(out)          :: rc
     end subroutine sort_four_arrays_by_time

     module subroutine time_real_to_ESMF (this,rc)
       class(HistoryTrajectory), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine time_real_to_ESMF

     module subroutine create_grid(this, rc)
       class(HistoryTrajectory), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine create_grid

     module subroutine regrid_accumulate_on_xsubset (this, rc)
       implicit none
       class(HistoryTrajectory), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine regrid_accumulate_on_xsubset

     module subroutine get_x_subset(this, interval, x_subset, rc)
       class(HistoryTrajectory), intent(inout) :: this
       type(ESMF_Time), intent(in)             :: interval(2)
       integer, intent(out)                    :: x_subset(2)
       integer, optional, intent(out)          :: rc
     end subroutine get_x_subset

     module subroutine destroy_rh_regen_LS (this, rc)
       class(HistoryTrajectory), intent(inout) :: this
       integer, optional, intent(out)          :: rc
     end subroutine destroy_rh_regen_LS

     module subroutine get_obsfile_Tbracket_from_epoch(this, currTime, rc)
       class(HistoryTrajectory), intent(inout) :: this
       type(ESMF_Time), intent(in)             :: currTime
       integer, optional, intent(out)          :: rc
     end subroutine get_obsfile_Tbracket_from_epoch

     module function get_filename_from_template (time, file_template, rc) result(filename)
       type(ESMF_Time), intent(in)             :: time
       character(len=*), intent(in)            :: file_template
       character(len=ESMF_MAXSTR)              :: filename
       integer, optional, intent(out)          :: rc
     end function get_filename_from_template

     module function get_filename_from_template_use_index (this, f_index, file_template, rc) result(filename)
       class(HistoryTrajectory), intent(inout) :: this
       character(len=*), intent(in)            :: file_template
       character(len=ESMF_MAXSTR)              :: filename
       integer, intent(in)                     :: f_index
       integer, optional, intent(out)          :: rc
     end function get_filename_from_template_use_index

  end interface
end module HistoryTrajectoryMod