Skip to content

Commit

Permalink
Merge pull request #311 from jedwards4b/add_rpointer_timestamp
Browse files Browse the repository at this point in the history
Add rpointer timestamp
  • Loading branch information
jedwards4b authored Oct 15, 2024
2 parents f6bc974 + c2c4274 commit 1eacdcc
Show file tree
Hide file tree
Showing 26 changed files with 346 additions and 700 deletions.
87 changes: 22 additions & 65 deletions datm/atm_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,60 +33,44 @@ module cdeps_datm_comp
use dshr_methods_mod , only : dshr_state_diagnose, chkerr, memcheck
use dshr_strdata_mod , only : shr_strdata_type, shr_strdata_init_from_config, shr_strdata_advance
use dshr_strdata_mod , only : shr_strdata_get_stream_pointer, shr_strdata_setOrbs
use dshr_mod , only : dshr_model_initphase, dshr_init
use dshr_mod , only : dshr_model_initphase, dshr_init, dshr_restart_write
use dshr_mod , only : dshr_state_setscalar, dshr_set_runclock, dshr_log_clock_advance
use dshr_mod , only : dshr_mesh_init, dshr_check_restart_alarm
use dshr_mod , only : dshr_mesh_init, dshr_check_restart_alarm, dshr_restart_read
use dshr_mod , only : dshr_orbital_init, dshr_orbital_update
use dshr_dfield_mod , only : dfield_type, dshr_dfield_add, dshr_dfield_copy
use dshr_fldlist_mod , only : fldlist_type, dshr_fldlist_add, dshr_fldlist_realize

use datm_datamode_core2_mod , only : datm_datamode_core2_advertise
use datm_datamode_core2_mod , only : datm_datamode_core2_init_pointers
use datm_datamode_core2_mod , only : datm_datamode_core2_advance
use datm_datamode_core2_mod , only : datm_datamode_core2_restart_write
use datm_datamode_core2_mod , only : datm_datamode_core2_restart_read

use datm_datamode_jra_mod , only : datm_datamode_jra_advertise
use datm_datamode_jra_mod , only : datm_datamode_jra_init_pointers
use datm_datamode_jra_mod , only : datm_datamode_jra_advance
use datm_datamode_jra_mod , only : datm_datamode_jra_restart_write
use datm_datamode_jra_mod , only : datm_datamode_jra_restart_read

use datm_datamode_clmncep_mod , only : datm_datamode_clmncep_advertise
use datm_datamode_clmncep_mod , only : datm_datamode_clmncep_init_pointers
use datm_datamode_clmncep_mod , only : datm_datamode_clmncep_advance
use datm_datamode_clmncep_mod , only : datm_datamode_clmncep_restart_write
use datm_datamode_clmncep_mod , only : datm_datamode_clmncep_restart_read

use datm_datamode_cplhist_mod , only : datm_datamode_cplhist_advertise
use datm_datamode_cplhist_mod , only : datm_datamode_cplhist_init_pointers
use datm_datamode_cplhist_mod , only : datm_datamode_cplhist_advance
use datm_datamode_cplhist_mod , only : datm_datamode_cplhist_restart_write
use datm_datamode_cplhist_mod , only : datm_datamode_cplhist_restart_read

use datm_datamode_era5_mod , only : datm_datamode_era5_advertise
use datm_datamode_era5_mod , only : datm_datamode_era5_init_pointers
use datm_datamode_era5_mod , only : datm_datamode_era5_advance
use datm_datamode_era5_mod , only : datm_datamode_era5_restart_write
use datm_datamode_era5_mod , only : datm_datamode_era5_restart_read

use datm_datamode_gefs_mod , only : datm_datamode_gefs_advertise
use datm_datamode_gefs_mod , only : datm_datamode_gefs_init_pointers
use datm_datamode_gefs_mod , only : datm_datamode_gefs_advance
use datm_datamode_gefs_mod , only : datm_datamode_gefs_restart_write
use datm_datamode_gefs_mod , only : datm_datamode_gefs_restart_read

use datm_datamode_cfsr_mod , only : datm_datamode_cfsr_advertise
use datm_datamode_cfsr_mod , only : datm_datamode_cfsr_init_pointers
use datm_datamode_cfsr_mod , only : datm_datamode_cfsr_advance
use datm_datamode_cfsr_mod , only : datm_datamode_cfsr_restart_write
use datm_datamode_cfsr_mod , only : datm_datamode_cfsr_restart_read

use datm_datamode_simple_mod , only : datm_datamode_simple_advertise
use datm_datamode_simple_mod , only : datm_datamode_simple_init_pointers
use datm_datamode_simple_mod , only : datm_datamode_simple_advance
use datm_datamode_simple_mod , only : datm_datamode_simple_restart_write
use datm_datamode_simple_mod , only : datm_datamode_simple_restart_read

implicit none
private ! except
Expand Down Expand Up @@ -157,7 +141,6 @@ module cdeps_datm_comp
integer :: idt ! integer model timestep
logical :: diagnose_data = .true.
integer , parameter :: main_task = 0 ! task number of main task
character(len=*) , parameter :: rpfile = 'rpointer.atm'
#ifdef CESMCOUPLED
character(*) , parameter :: modName = "(atm_comp_nuopc)"
#else
Expand Down Expand Up @@ -479,7 +462,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

! Run datm
call datm_comp_run(importstate, exportstate, current_ymd, current_tod, current_mon, &
call datm_comp_run(gcomp, importstate, exportstate, current_ymd, current_tod, current_mon, &
orbEccen, orbMvelpp, orbLambm0, orbObliqr, restart_write=.false., rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

Expand Down Expand Up @@ -561,7 +544,7 @@ subroutine ModelAdvance(gcomp, rc)

! Run datm
call ESMF_TraceRegionEnter('datm_run')
call datm_comp_run(importstate, exportstate, next_ymd, next_tod, mon, &
call datm_comp_run(gcomp, importstate, exportstate, next_ymd, next_tod, mon, &
orbEccen, orbMvelpp, orbLambm0, orbObliqr, restart_write, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
call ESMF_TraceRegionExit('datm_run')
Expand All @@ -579,14 +562,15 @@ subroutine ModelAdvance(gcomp, rc)
end subroutine ModelAdvance

!===============================================================================
subroutine datm_comp_run(importState, exportState, target_ymd, target_tod, target_mon, &
subroutine datm_comp_run(gcomp, importState, exportState, target_ymd, target_tod, target_mon, &
orbEccen, orbMvelpp, orbLambm0, orbObliqr, restart_write, rc)

use nuopc_shr_methods, only : shr_get_rpointer_name
! ----------------------------------
! run method for datm model
! ----------------------------------

! input/output variables
type(ESMF_GridComp) , intent(inout) :: gcomp
type(ESMF_State) , intent(inout) :: importState
type(ESMF_State) , intent(inout) :: exportState
integer , intent(in) :: target_ymd ! model date
Expand All @@ -601,6 +585,7 @@ subroutine datm_comp_run(importState, exportState, target_ymd, target_tod, targe

! local variables
logical :: first_time = .true.
character(len=CL) :: rpfile
character(*), parameter :: subName = '(datm_comp_run) '
!-------------------------------------------------------------------------------

Expand All @@ -613,7 +598,6 @@ subroutine datm_comp_run(importState, exportState, target_ymd, target_tod, targe
!--------------------

if (first_time) then

! Initialize dfields
call datm_init_dfields(rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
Expand Down Expand Up @@ -648,23 +632,14 @@ subroutine datm_comp_run(importState, exportState, target_ymd, target_tod, targe

! Read restart if needed
if (restart_read .and. .not. skip_restart_read) then
call shr_get_rpointer_name(gcomp, 'atm', target_ymd, target_tod, rpfile, 'read', rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
select case (trim(datamode))
case('CORE2_NYF','CORE2_IAF')
call datm_datamode_core2_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('CORE_IAF_JRA')
call datm_datamode_jra_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('CLMNCEP')
call datm_datamode_clmncep_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('CPLHIST')
call datm_datamode_cplhist_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('ERA5')
call datm_datamode_era5_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('GEFS')
call datm_datamode_gefs_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('CFSR')
call datm_datamode_cfsr_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('SIMPLE')
call datm_datamode_simple_restart_read(restfilm, inst_suffix, logunit, my_task, mpicom, sdat)
case('CORE2_NYF','CORE2_IAF','CORE_IAF_JRA','CLMNCEP','CPLHIST','ERA5','GEFS','CFSR','SIMPLE')
call dshr_restart_read(restfilm, rpfile, logunit, my_task, mpicom, sdat, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
case default
call shr_sys_abort(subName//'datamode '//trim(datamode)//' not recognized')
end select
end if

Expand Down Expand Up @@ -727,33 +702,15 @@ subroutine datm_comp_run(importState, exportState, target_ymd, target_tod, targe

! Write restarts if needed
if (restart_write) then
call shr_get_rpointer_name(gcomp, 'atm', target_ymd, target_tod, rpfile, 'write', rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
select case (trim(datamode))
case('CORE2_NYF','CORE2_IAF')
call datm_datamode_core2_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case('CORE_IAF_JRA')
call datm_datamode_jra_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case('CLMNCEP')
call datm_datamode_clmncep_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case('CPLHIST')
call datm_datamode_cplhist_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case('ERA5')
call datm_datamode_era5_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case('GEFS')
call datm_datamode_gefs_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case('CORE2_NYF','CORE2_IAF','CORE_IAF_JRA','CLMNCEP','CPLHIST','ERA5','GEFS','CFSR','SIMPLE')
call dshr_restart_write(rpfile, case_name, 'datm', inst_suffix, target_ymd, target_tod, logunit, &
my_task, sdat, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
case('CFSR')
call datm_datamode_cfsr_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
case('SIMPLE')
call datm_datamode_simple_restart_write(case_name, inst_suffix, target_ymd, target_tod, &
logunit, my_task, sdat)
case default
call shr_sys_abort(subName//'datamode '//trim(datamode)//' not recognized')
end select
end if

Expand Down
40 changes: 0 additions & 40 deletions datm/datm_datamode_cfsr_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ module datm_datamode_cfsr_mod
use shr_const_mod , only : shr_const_tkfrz, shr_const_rhofw, shr_const_rdair
use dshr_methods_mod , only : dshr_state_getfldptr, chkerr
use dshr_strdata_mod , only : shr_strdata_type, shr_strdata_get_stream_pointer
use dshr_mod , only : dshr_restart_read, dshr_restart_write
use dshr_strdata_mod , only : shr_strdata_type
use dshr_fldlist_mod , only : fldlist_type, dshr_fldlist_add

Expand All @@ -18,8 +17,6 @@ module datm_datamode_cfsr_mod
public :: datm_datamode_cfsr_advertise
public :: datm_datamode_cfsr_init_pointers
public :: datm_datamode_cfsr_advance
public :: datm_datamode_cfsr_restart_write
public :: datm_datamode_cfsr_restart_read

! export state data
real(r8), pointer :: Sa_z(:) => null()
Expand Down Expand Up @@ -51,8 +48,6 @@ module datm_datamode_cfsr_mod
real(r8) , parameter :: rdair = SHR_CONST_RDAIR ! dry air gas constant ~ J/K/kg
real(r8) , parameter :: rhofw = SHR_CONST_RHOFW ! density of fresh water ~ kg/m^3

character(*), parameter :: nullstr = 'undefined'
character(*), parameter :: rpfile = 'rpointer.atm'
character(*), parameter :: u_FILE_u = &
__FILE__

Expand Down Expand Up @@ -218,39 +213,4 @@ subroutine datm_datamode_cfsr_advance(exportstate, mainproc, logunit, mpicom, ta

end subroutine datm_datamode_cfsr_advance

!===============================================================================
subroutine datm_datamode_cfsr_restart_write(case_name, inst_suffix, ymd, tod, &
logunit, my_task, sdat)

! input/output variables
character(len=*) , intent(in) :: case_name
character(len=*) , intent(in) :: inst_suffix
integer , intent(in) :: ymd ! model date
integer , intent(in) :: tod ! model sec into model date
integer , intent(in) :: logunit
integer , intent(in) :: my_task
type(shr_strdata_type) , intent(inout) :: sdat
!-------------------------------------------------------------------------------

call dshr_restart_write(rpfile, case_name, 'datm', inst_suffix, ymd, tod, &
logunit, my_task, sdat)

end subroutine datm_datamode_cfsr_restart_write

!===============================================================================
subroutine datm_datamode_cfsr_restart_read(rest_filem, inst_suffix, logunit, my_task, mpicom, sdat)

! input/output arguments
character(len=*) , intent(inout) :: rest_filem
character(len=*) , intent(in) :: inst_suffix
integer , intent(in) :: logunit
integer , intent(in) :: my_task
integer , intent(in) :: mpicom
type(shr_strdata_type) , intent(inout) :: sdat
!-------------------------------------------------------------------------------

call dshr_restart_read(rest_filem, rpfile, inst_suffix, nullstr, logunit, my_task, mpicom, sdat)

end subroutine datm_datamode_cfsr_restart_read

end module datm_datamode_cfsr_mod
37 changes: 0 additions & 37 deletions datm/datm_datamode_clmncep_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ module datm_datamode_clmncep_mod
use shr_const_mod , only : shr_const_pstd, shr_const_stebol, shr_const_rdair
use dshr_methods_mod , only : dshr_state_getfldptr, chkerr
use dshr_strdata_mod , only : shr_strdata_type, shr_strdata_get_stream_pointer
use dshr_mod , only : dshr_restart_read, dshr_restart_write
use dshr_strdata_mod , only : shr_strdata_type
use dshr_fldlist_mod , only : fldlist_type, dshr_fldlist_add

Expand All @@ -20,8 +19,6 @@ module datm_datamode_clmncep_mod
public :: datm_datamode_clmncep_advertise
public :: datm_datamode_clmncep_init_pointers
public :: datm_datamode_clmncep_advance
public :: datm_datamode_clmncep_restart_write
public :: datm_datamode_clmncep_restart_read
private :: datm_esat ! determine saturation vapor pressure

! export state data
Expand Down Expand Up @@ -591,41 +588,7 @@ subroutine datm_datamode_clmncep_advance(mainproc, logunit, mpicom, rc)
end subroutine datm_datamode_clmncep_advance

!===============================================================================
subroutine datm_datamode_clmncep_restart_write(case_name, inst_suffix, ymd, tod, &
logunit, my_task, sdat)

! input/output variables
character(len=*) , intent(in) :: case_name
character(len=*) , intent(in) :: inst_suffix
integer , intent(in) :: ymd ! model date
integer , intent(in) :: tod ! model sec into model date
integer , intent(in) :: logunit
integer , intent(in) :: my_task
type(shr_strdata_type) , intent(inout) :: sdat
!-------------------------------------------------------------------------------

call dshr_restart_write(rpfile, case_name, 'datm', inst_suffix, ymd, tod, &
logunit, my_task, sdat)

end subroutine datm_datamode_clmncep_restart_write

!===============================================================================
subroutine datm_datamode_clmncep_restart_read(rest_filem, inst_suffix, logunit, my_task, mpicom, sdat)

! input/output arguments
character(len=*) , intent(inout) :: rest_filem
character(len=*) , intent(in) :: inst_suffix
integer , intent(in) :: logunit
integer , intent(in) :: my_task
integer , intent(in) :: mpicom
type(shr_strdata_type) , intent(inout) :: sdat
!-------------------------------------------------------------------------------

call dshr_restart_read(rest_filem, rpfile, inst_suffix, nullstr, logunit, my_task, mpicom, sdat)

end subroutine datm_datamode_clmncep_restart_read

!===============================================================================
real(r8) function datm_eSat(tK,tKbot)

!----------------------------------------------------------------------------
Expand Down
39 changes: 0 additions & 39 deletions datm/datm_datamode_core2_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@ module datm_datamode_core2_mod
use shr_const_mod , only : shr_const_tkfrz, shr_const_pi
use dshr_strdata_mod , only : shr_strdata_get_stream_pointer, shr_strdata_type
use dshr_methods_mod , only : dshr_state_getfldptr, dshr_fldbun_getfldptr, dshr_fldbun_regrid, chkerr
use dshr_mod , only : dshr_restart_read, dshr_restart_write
use dshr_strdata_mod , only : shr_strdata_type
use dshr_fldlist_mod , only : fldlist_type, dshr_fldlist_add

Expand All @@ -32,8 +31,6 @@ module datm_datamode_core2_mod
public :: datm_datamode_core2_advertise
public :: datm_datamode_core2_init_pointers
public :: datm_datamode_core2_advance
public :: datm_datamode_core2_restart_write
public :: datm_datamode_core2_restart_read

private :: datm_get_adjustment_factors

Expand Down Expand Up @@ -86,7 +83,6 @@ module datm_datamode_core2_mod
-1.99_R8,-0.91_R8, 1.72_R8, 2.30_R8, 1.81_R8, 1.06_R8/

character(*), parameter :: nullstr = 'null'
character(*), parameter :: rpfile = 'rpointer.atm'
character(*), parameter :: u_FILE_u = &
__FILE__

Expand Down Expand Up @@ -409,41 +405,6 @@ subroutine datm_datamode_core2_advance(datamode, target_ymd, target_tod, target_

end subroutine datm_datamode_core2_advance

!===============================================================================
subroutine datm_datamode_core2_restart_write(case_name, inst_suffix, ymd, tod, &
logunit, my_task, sdat)

! input/output variables
character(len=*) , intent(in) :: case_name
character(len=*) , intent(in) :: inst_suffix
integer , intent(in) :: ymd ! model date
integer , intent(in) :: tod ! model sec into model date
integer , intent(in) :: logunit
integer , intent(in) :: my_task
type(shr_strdata_type) , intent(inout) :: sdat
!-------------------------------------------------------------------------------

call dshr_restart_write(rpfile, case_name, 'datm', inst_suffix, ymd, tod, &
logunit, my_task, sdat)

end subroutine datm_datamode_core2_restart_write

!===============================================================================
subroutine datm_datamode_core2_restart_read(rest_filem, inst_suffix, logunit, my_task, mpicom, sdat)

! input/output arguments
character(len=*) , intent(inout) :: rest_filem
character(len=*) , intent(in) :: inst_suffix
integer , intent(in) :: logunit
integer , intent(in) :: my_task
integer , intent(in) :: mpicom
type(shr_strdata_type) , intent(inout) :: sdat
!-------------------------------------------------------------------------------

call dshr_restart_read(rest_filem, rpfile, inst_suffix, nullstr, logunit, my_task, mpicom, sdat)

end subroutine datm_datamode_core2_restart_read

!===============================================================================
subroutine datm_get_adjustment_factors(sdat, fileName_mesh, fileName_data, windF, winddF, qsatF, rc)

Expand Down
Loading

0 comments on commit 1eacdcc

Please sign in to comment.