Skip to content

Commit

Permalink
Merge branch 'dev/ncar' into merge_main_20230406
Browse files Browse the repository at this point in the history
  • Loading branch information
gustavo-marques committed Jul 7, 2023
2 parents 400bd21 + 2e77200 commit 3c457c3
Show file tree
Hide file tree
Showing 21 changed files with 623 additions and 491 deletions.
64 changes: 45 additions & 19 deletions config_src/drivers/nuopc_cap/mom_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,9 +28,11 @@ module MOM_cap_mod
use MOM_cap_methods, only: mom_import, mom_export, mom_set_geomtype, mod2med_areacor
use MOM_cap_methods, only: med2mod_areacor, state_diagnose
use MOM_cap_methods, only: ChkErr
use MOM_ensemble_manager, only: ensemble_manager_init

#ifdef CESMCOUPLED
use shr_log_mod, only: shr_log_setLogUnit
use nuopc_shr_methods, only: get_component_instance
#endif
use time_utils_mod, only: esmf2fms_time

Expand Down Expand Up @@ -146,7 +148,8 @@ module MOM_cap_mod
logical :: cesm_coupled = .false.
type(ESMF_GeomType_Flag) :: geomtype
#endif
character(len=8) :: restart_mode = 'alarms'
character(len=8) :: restart_mode = 'alarms'
character(len=16) :: inst_suffix = ''

contains

Expand Down Expand Up @@ -422,6 +425,8 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
! (same as restartfile if single restart file)
character(len=*), parameter :: subname='(MOM_cap:InitializeAdvertise)'
character(len=32) :: calendar
character(len=:), allocatable :: rpointer_filename
integer :: inst_index
!--------------------------------

rc = ESMF_SUCCESS
Expand Down Expand Up @@ -451,6 +456,13 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
CALL ESMF_TimeIntervalGet(TINT, S=DT_OCEAN, RC=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

#ifdef CESMCOUPLED
call get_component_instance(gcomp, inst_suffix, inst_index, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
call ensemble_manager_init(inst_suffix)
rpointer_filename = 'rpointer.ocn'//trim(inst_suffix)
#endif

! reset shr logging to my log file
if (localPet==0) then
call NUOPC_CompAttributeGet(gcomp, name="diro", &
Expand All @@ -460,11 +472,19 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
isPresent=isPresentLogfile, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
if (isPresentDiro .and. isPresentLogfile) then
call NUOPC_CompAttributeGet(gcomp, name="diro", value=diro, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
call NUOPC_CompAttributeGet(gcomp, name="logfile", value=logfile, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
open(newunit=stdout,file=trim(diro)//"/"//trim(logfile))
call NUOPC_CompAttributeGet(gcomp, name="diro", value=diro, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
call NUOPC_CompAttributeGet(gcomp, name="logfile", value=logfile, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

if (cesm_coupled) then
! Multiinstance logfile name needs a correction
if(logfile(4:4) == '_') then
logfile = logfile(1:3)//trim(inst_suffix)//logfile(9:)
endif
endif

open(newunit=stdout,file=trim(diro)//"/"//trim(logfile))
else
stdout = output_unit
endif
Expand Down Expand Up @@ -521,12 +541,6 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)

time0 = set_date (YEAR,MONTH,DAY,HOUR,MINUTE,SECOND)


! rsd need to figure out how to get this without share code
!call shr_nuopc_get_component_instance(gcomp, inst_suffix, inst_index)
!inst_name = "OCN"//trim(inst_suffix)


if (is_root_pe()) then
write(stdout,*) subname//'start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,second
endif
Expand Down Expand Up @@ -581,9 +595,9 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)

if (localPet == 0) then
! this hard coded for rpointer.ocn right now
open(newunit=readunit, file='rpointer.ocn', form='formatted', status='old', iostat=iostat)
open(newunit=readunit, file=rpointer_filename, form='formatted', status='old', iostat=iostat)
if (iostat /= 0) then
call ESMF_LogSetError(ESMF_RC_FILE_OPEN, msg=subname//' ERROR opening rpointer.ocn', &
call ESMF_LogSetError(ESMF_RC_FILE_OPEN, msg=subname//' ERROR opening '//rpointer_filename, &
line=__LINE__, file=u_FILE_u, rcToReturn=rc)
return
endif
Expand All @@ -593,7 +607,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
if (len(trim(restartfiles))>1 .and. iostat<0) then
exit ! done reading restart files list.
else
call ESMF_LogSetError(ESMF_RC_FILE_READ, msg=subname//' ERROR reading rpointer.ocn', &
call ESMF_LogSetError(ESMF_RC_FILE_READ, msg=subname//' ERROR reading '//rpointer_filename, &
line=__LINE__, file=u_FILE_u, rcToReturn=rc)
return
endif
Expand All @@ -616,7 +630,12 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
endif

ocean_public%is_ocean_pe = .true.
call ocean_model_init(ocean_public, ocean_state, time0, time_start, input_restart_file=trim(adjustl(restartfiles)))
if (cesm_coupled .and. len_trim(inst_suffix)>0) then
call ocean_model_init(ocean_public, ocean_state, time0, time_start, &
input_restart_file=trim(adjustl(restartfiles)), inst_index=inst_index)
else
call ocean_model_init(ocean_public, ocean_state, time0, time_start, input_restart_file=trim(adjustl(restartfiles)))
endif

! GMM, this call is not needed in CESM. Check with EMC if it can be deleted.
call ocean_model_flux_init(ocean_state)
Expand Down Expand Up @@ -1489,6 +1508,7 @@ subroutine ModelAdvance(gcomp, rc)
character(len=128) :: fldname
character(len=*),parameter :: subname='(MOM_cap:ModelAdvance)'
character(len=8) :: suffix
character(len=:), allocatable :: rpointer_filename
integer :: num_rest_files

rc = ESMF_SUCCESS
Expand Down Expand Up @@ -1658,20 +1678,26 @@ subroutine ModelAdvance(gcomp, rc)
call ESMF_VMGet(vm, localPet=localPet, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

rpointer_filename = 'rpointer.ocn'//trim(inst_suffix)

write(restartname,'(A,".mom6.r.",I4.4,"-",I2.2,"-",I2.2,"-",I5.5)') &
trim(casename), year, month, day, seconds
call ESMF_LogWrite("MOM_cap: Writing restart : "//trim(restartname), ESMF_LOGMSG_INFO)
! write restart file(s)
call ocean_model_restart(ocean_state, restartname=restartname, num_rest_files=num_rest_files)
if (localPet == 0) then
! Write name of restart file in the rpointer file - this is currently hard-coded for the ocean
open(newunit=writeunit, file='rpointer.ocn', form='formatted', status='unknown', iostat=iostat)
open(newunit=writeunit, file=rpointer_filename, form='formatted', status='unknown', iostat=iostat)
if (iostat /= 0) then
call ESMF_LogSetError(ESMF_RC_FILE_OPEN, &
msg=subname//' ERROR opening rpointer.ocn', line=__LINE__, file=u_FILE_u, rcToReturn=rc)
msg=subname//' ERROR opening '//rpointer_filename, line=__LINE__, file=u_FILE_u, rcToReturn=rc)
return
endif
write(writeunit,'(a)') trim(restartname)//'.nc'
if (len_trim(inst_suffix) == 0) then
write(writeunit,'(a)') trim(restartname)//'.nc'
else
write(writeunit,'(a)') trim(restartname)//'.'//trim(inst_suffix)//'.nc'
endif

if (num_rest_files > 1) then
! append i.th restart file name to rpointer
Expand Down
20 changes: 13 additions & 7 deletions config_src/drivers/nuopc_cap/mom_ocean_model_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module MOM_ocean_model_nuopc
use MOM_time_manager, only : operator(/=), operator(<=), operator(>=)
use MOM_time_manager, only : operator(<), real_to_time_type, time_type_to_real
use MOM_interpolate, only : time_interp_external_init
use MOM_tracer_flow_control, only : call_tracer_flux_init
use MOM_tracer_flow_control, only : tracer_flow_control_CS, call_tracer_flux_init, call_tracer_set_forcing
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : surface
use MOM_verticalGrid, only : verticalGrid_type
Expand Down Expand Up @@ -210,6 +210,8 @@ module MOM_ocean_model_nuopc
type(marine_ice_CS), pointer :: &
marine_ice_CSp => NULL() !< A pointer to the control structure for the
!! marine ice effects module.
type(tracer_flow_control_CS), pointer :: &
tracer_flow_CSp => NULL() !< A pointer to the tracer flow control structure
type(wave_parameters_CS), pointer, public :: &
Waves => NULL() !< A pointer to the surface wave control structure
type(surface_forcing_CS), pointer :: &
Expand All @@ -229,7 +231,7 @@ module MOM_ocean_model_nuopc
!! This subroutine initializes both the ocean state and the ocean surface type.
!! Because of the way that indicies and domains are handled, Ocean_sfc must have
!! been used in a previous call to initialize_ocean_type.
subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, input_restart_file)
subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, input_restart_file, inst_index)
type(ocean_public_type), target, &
intent(inout) :: Ocean_sfc !< A structure containing various publicly
!! visible ocean surface properties after initialization,
Expand All @@ -246,6 +248,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
!! tracer fluxes, and can be used to spawn related
!! internal variables in the ice model.
character(len=*), optional, intent(in) :: input_restart_file !< If present, name of restart file to read
integer, optional :: inst_index !< Ensemble index provided by the cap (instead of FMS ensemble manager)

! Local variables
real :: Rho0 ! The Boussinesq ocean density, in kg m-3.
Expand All @@ -255,7 +258,6 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
!! min(HFrz, OBLD), where OBLD is the boundary layer depth.
!! If HFrz <= 0 (default), melt potential will not be computed.
logical :: use_melt_pot !< If true, allocate melt_potential array
logical :: use_CFC !< If true, allocated arrays for surface CFCs.


! This include declares and sets the variable "version".
Expand Down Expand Up @@ -283,7 +285,8 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
OS%restart_CSp, Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
input_restart_file=input_restart_file, &
diag_ptr=OS%diag, count_calls=.true., waves_CSp=OS%Waves)
diag_ptr=OS%diag, count_calls=.true., tracer_flow_CSp=OS%tracer_flow_CSp, &
waves_CSp=OS%Waves, ensemble_num=inst_index)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
C_p_scaled=OS%fluxes%C_p, use_temp=use_temperature)

Expand Down Expand Up @@ -376,16 +379,14 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
use_melt_pot=.false.
endif

call get_param(param_file, mdl, "USE_CFC_CAP", use_CFC, &
default=.false., do_not_log=.true.)
call get_param(param_file, mdl, "USE_WAVES", OS%Use_Waves, &
"If true, enables surface wave modules.", default=.false.)

! Consider using a run-time flag to determine whether to do the diagnostic
! vertical integrals, since the related 3-d sums are not negligible in cost.
call allocate_surface_state(OS%sfc_state, OS%grid, use_temperature, &
do_integrals=.true., gas_fields_ocn=gas_fields_ocn, &
use_meltpot=use_melt_pot, use_cfcs=use_CFC)
use_meltpot=use_melt_pot)

call surface_forcing_init(Time_in, OS%grid, OS%US, param_file, OS%diag, &
OS%forcing_CSp, OS%restore_salinity, OS%restore_temp, OS%use_waves)
Expand Down Expand Up @@ -611,6 +612,11 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, OS%restart_CSp)
endif

if (do_thermo) &
call call_tracer_set_forcing(OS%sfc_state, OS%fluxes, OS%Time, &
real_to_time_type(dt_coupling), OS%grid, OS%US, OS%GV%Rho0, &
OS%tracer_flow_CSp)

call disable_averaging(OS%diag)
Master_time = OS%Time ; Time1 = OS%Time

Expand Down
40 changes: 2 additions & 38 deletions config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ module MOM_surface_forcing_nuopc
use MOM_grid, only : ocean_grid_type
use MOM_interpolate, only : init_external_field, time_interp_external
use MOM_interpolate, only : time_interp_external_init
use MOM_CFC_cap, only : CFC_cap_fluxes
use MOM_io, only : slasher, write_version_number, MOM_read_data
use MOM_io, only : stdout
use MOM_restart, only : register_restart_field, restart_init, MOM_restart_CS
Expand Down Expand Up @@ -129,7 +128,6 @@ module MOM_surface_forcing_nuopc

type(diag_ctrl), pointer :: diag !< structure to regulate diagnostic output timing
character(len=200) :: inputdir !< directory where NetCDF input files are
character(len=200) :: CFC_BC_file !< filename with cfc11 and cfc12 data
character(len=200) :: salt_restore_file !< filename for salt restoring data
character(len=30) :: salt_restore_var_name !< name of surface salinity in salt_restore_file
logical :: mask_srestore !< if true, apply a 2-dimensional mask to the surface
Expand All @@ -143,13 +141,9 @@ module MOM_surface_forcing_nuopc
!! temperature restoring fluxes. The masking file should be
!! in inputdir/temp_restore_mask.nc and the field should
!! be named 'mask'
character(len=30) :: cfc11_var_name !< name of cfc11 in CFC_BC_file
character(len=30) :: cfc12_var_name !< name of cfc11 in CFC_BC_file
real, pointer, dimension(:,:) :: trestore_mask => NULL() !< mask for SST restoring
integer :: id_srestore = -1 !< id number for time_interp_external.
integer :: id_trestore = -1 !< id number for time_interp_external.
integer :: id_cfc11_atm = -1 !< id number for time_interp_external.
integer :: id_cfc12_atm = -1 !< id number for time_interp_external.
integer :: id_srestore = -1 !< id number for time_interp_external.
integer :: id_trestore = -1 !< id number for time_interp_external.

! Diagnostics handles
type(forcing_diags), public :: handles
Expand Down Expand Up @@ -245,8 +239,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,

! local variables
real, dimension(SZI_(G),SZJ_(G)) :: &
cfc11_atm, & !< CFC11 concentration in the atmopshere [???????]
cfc12_atm, & !< CFC11 concentration in the atmopshere [???????]
data_restore, & !< The surface value toward which to restore [S ~> ppt] or [C ~> degC]
PmE_adj, & !< The adjustment to PminusE that will cause the salinity
!! to be restored toward its target value [kg/(m^2 * s)]
Expand Down Expand Up @@ -594,11 +586,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%accumulate_p_surf = .true. ! Multiple components may contribute to surface pressure.
endif

! CFCs
if (CS%use_CFC) then
call CFC_cap_fluxes(fluxes, sfc_state, G, US, CS%Rho0, Time, CS%id_cfc11_atm, CS%id_cfc11_atm)
endif

if (associated(IOB%salt_flux)) then
do j=js,je ; do i=is,ie
fluxes%salt_flux(i,j) = G%mask2dT(i,j)*(fluxes%salt_flux(i,j) + kg_m2_s_conversion*IOB%salt_flux(i-i0,j-j0))
Expand Down Expand Up @@ -1412,29 +1399,6 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
endif
endif ; endif

! Do not log these params here since they are logged in the CFC cap module
if (CS%use_CFC) then
call get_param(param_file, mdl, "CFC_BC_FILE", CS%CFC_BC_file, &
"The file in which the CFC-11 and CFC-12 atm concentrations can be "//&
"found (units must be parts per trillion), or an empty string for "//&
"internal BC generation (TODO).", default=" ", do_not_log=.true.)
if ((len_trim(CS%CFC_BC_file) > 0) .and. (scan(CS%CFC_BC_file,'/') == 0)) then
! Add the directory if CFC_BC_file is not already a complete path.
CS%CFC_BC_file = trim(CS%inputdir) // trim(CS%CFC_BC_file)
endif
if (len_trim(CS%CFC_BC_file) > 0) then
call get_param(param_file, mdl, "CFC11_VARIABLE", CS%cfc11_var_name, &
"The name of the variable representing CFC-11 in "//&
"CFC_BC_FILE.", default="CFC_11", do_not_log=.true.)
call get_param(param_file, mdl, "CFC12_VARIABLE", CS%cfc12_var_name, &
"The name of the variable representing CFC-12 in "//&
"CFC_BC_FILE.", default="CFC_12", do_not_log=.true.)

CS%id_cfc11_atm = init_external_field(CS%CFC_BC_file, CS%cfc11_var_name, domain=G%Domain%mpp_domain)
CS%id_cfc12_atm = init_external_field(CS%CFC_BC_file, CS%cfc12_var_name, domain=G%Domain%mpp_domain)
endif
endif

! Set up any restart fields associated with the forcing.
call restart_init(param_file, CS%restart_CSp, "MOM_forcing.res")
call restart_init_end(CS%restart_CSp)
Expand Down
3 changes: 2 additions & 1 deletion config_src/drivers/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -346,7 +346,8 @@ subroutine set_forcing(sfc_state, forces, fluxes, day_start, day_interval, G, US
endif

if (associated(CS%tracer_flow_CSp)) then
call call_tracer_set_forcing(sfc_state, fluxes, day_start, day_interval, G, CS%tracer_flow_CSp)
call call_tracer_set_forcing(sfc_state, fluxes, day_start, day_interval, G, US, CS%Rho0, &
CS%tracer_flow_CSp)
endif

! Allow for user-written code to alter the fluxes after all the above
Expand Down
13 changes: 10 additions & 3 deletions config_src/infra/FMS1/MOM_ensemble_manager_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module MOM_ensemble_manager_infra
use ensemble_manager_mod, only : FMS_get_ensemble_size => get_ensemble_size
use ensemble_manager_mod, only : FMS_get_ensemble_pelist => get_ensemble_pelist
use ensemble_manager_mod, only : FMS_get_ensemble_filter_pelist => get_ensemble_filter_pelist
use fms_io_mod, only : fms_io_set_filename_appendix=>set_filename_appendix

implicit none ; private

Expand All @@ -20,9 +21,15 @@ module MOM_ensemble_manager_infra

!> Initializes the ensemble manager which divides available resources
!! in order to concurrently execute an ensemble of model realizations.
subroutine ensemble_manager_init()

call FMS_ensemble_manager_init()
subroutine ensemble_manager_init(ensemble_suffix)
character(len=*), optional, intent(in) :: ensemble_suffix !> Ensemble suffix provided by the cap. This may be
!! provided to bypass FMS ensemble manager.

if (present(ensemble_suffix)) then
call fms_io_set_filename_appendix(trim(ensemble_suffix))
else
call FMS_ensemble_manager_init()
endif

end subroutine ensemble_manager_init

Expand Down
Loading

0 comments on commit 3c457c3

Please sign in to comment.