Skip to content

Commit

Permalink
Merge pull request mom-ocean#13 from NOAA-EMC/dev/emc
Browse files Browse the repository at this point in the history
Merge with EMC fork
  • Loading branch information
pjpegion committed Jan 6, 2021
2 parents cd06356 + 593aecb commit 040e1f1
Show file tree
Hide file tree
Showing 19 changed files with 762 additions and 913 deletions.
32 changes: 13 additions & 19 deletions config_src/mct_driver/mom_ocean_model_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ module MOM_ocean_model_mct
use coupler_types_mod, only : coupler_type_set_diags, coupler_type_send_data
use mpp_domains_mod, only : domain2d, mpp_get_layout, mpp_get_global_domain
use mpp_domains_mod, only : mpp_define_domains, mpp_get_compute_domain, mpp_get_data_domain
use fms_mod, only : stdout
use MOM_io, only : stdout
use mpp_mod, only : mpp_chksum
use MOM_EOS, only : gsw_sp_from_sr, gsw_pt_from_ct
use MOM_wave_interface, only : wave_parameters_CS, MOM_wave_interface_init
Expand Down Expand Up @@ -409,10 +409,6 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i

call close_param_file(param_file)
call diag_mediator_close_registration(OS%diag)

if (is_root_pe()) &
write(*,'(/12x,a/)') '======== COMPLETED MOM INITIALIZATION ========'

call callTree_leave("ocean_model_init(")
end subroutine ocean_model_init

Expand Down Expand Up @@ -1053,20 +1049,18 @@ subroutine ocean_public_type_chksum(id, timestep, ocn)
integer, intent(in) :: timestep !< The number of elapsed timesteps
type(ocean_public_type), intent(in) :: ocn !< A structure containing various publicly
!! visible ocean surface fields.
integer :: n, m, outunit

outunit = stdout()

write(outunit,*) "BEGIN CHECKSUM(ocean_type):: ", id, timestep
write(outunit,100) 'ocean%t_surf ',mpp_chksum(ocn%t_surf )
write(outunit,100) 'ocean%s_surf ',mpp_chksum(ocn%s_surf )
write(outunit,100) 'ocean%u_surf ',mpp_chksum(ocn%u_surf )
write(outunit,100) 'ocean%v_surf ',mpp_chksum(ocn%v_surf )
write(outunit,100) 'ocean%sea_lev ',mpp_chksum(ocn%sea_lev)
write(outunit,100) 'ocean%frazil ',mpp_chksum(ocn%frazil )
write(outunit,100) 'ocean%melt_potential ',mpp_chksum(ocn%melt_potential)

call coupler_type_write_chksums(ocn%fields, outunit, 'ocean%')
integer :: n, m

write(stdout,*) "BEGIN CHECKSUM(ocean_type):: ", id, timestep
write(stdout,100) 'ocean%t_surf ',mpp_chksum(ocn%t_surf )
write(stdout,100) 'ocean%s_surf ',mpp_chksum(ocn%s_surf )
write(stdout,100) 'ocean%u_surf ',mpp_chksum(ocn%u_surf )
write(stdout,100) 'ocean%v_surf ',mpp_chksum(ocn%v_surf )
write(stdout,100) 'ocean%sea_lev ',mpp_chksum(ocn%sea_lev)
write(stdout,100) 'ocean%frazil ',mpp_chksum(ocn%frazil )
write(stdout,100) 'ocean%melt_potential ',mpp_chksum(ocn%melt_potential)

call coupler_type_write_chksums(ocn%fields, stdout, 'ocean%')
100 FORMAT(" CHECKSUM::",A20," = ",Z20)

end subroutine ocean_public_type_chksum
Expand Down
52 changes: 25 additions & 27 deletions config_src/mct_driver/mom_surface_forcing_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -34,10 +34,10 @@ module MOM_surface_forcing_mct
use coupler_types_mod, only : coupler_type_initialized, coupler_type_spawn
use coupler_types_mod, only : coupler_type_copy_data
use data_override_mod, only : data_override_init, data_override
use fms_mod, only : stdout
use mpp_mod, only : mpp_chksum
use time_interp_external_mod, only : init_external_field, time_interp_external
use time_interp_external_mod, only : time_interp_external_init
use MOM_io, only: stdout

implicit none ; private

Expand Down Expand Up @@ -1361,37 +1361,35 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
!! ocean in a coupled model whose checksums are reported

! local variables
integer :: n,m, outunit

outunit = stdout()

write(outunit,*) "BEGIN CHECKSUM(ice_ocean_boundary_type):: ", id, timestep
write(outunit,100) 'iobt%u_flux ' , mpp_chksum( iobt%u_flux )
write(outunit,100) 'iobt%v_flux ' , mpp_chksum( iobt%v_flux )
write(outunit,100) 'iobt%t_flux ' , mpp_chksum( iobt%t_flux )
write(outunit,100) 'iobt%q_flux ' , mpp_chksum( iobt%q_flux )
write(outunit,100) 'iobt%salt_flux ' , mpp_chksum( iobt%salt_flux )
write(outunit,100) 'iobt%seaice_melt_heat' , mpp_chksum( iobt%seaice_melt_heat)
write(outunit,100) 'iobt%seaice_melt ' , mpp_chksum( iobt%seaice_melt )
write(outunit,100) 'iobt%lw_flux ' , mpp_chksum( iobt%lw_flux )
write(outunit,100) 'iobt%sw_flux_vis_dir' , mpp_chksum( iobt%sw_flux_vis_dir)
write(outunit,100) 'iobt%sw_flux_vis_dif' , mpp_chksum( iobt%sw_flux_vis_dif)
write(outunit,100) 'iobt%sw_flux_nir_dir' , mpp_chksum( iobt%sw_flux_nir_dir)
write(outunit,100) 'iobt%sw_flux_nir_dif' , mpp_chksum( iobt%sw_flux_nir_dif)
write(outunit,100) 'iobt%lprec ' , mpp_chksum( iobt%lprec )
write(outunit,100) 'iobt%fprec ' , mpp_chksum( iobt%fprec )
write(outunit,100) 'iobt%runoff ' , mpp_chksum( iobt%runoff )
write(outunit,100) 'iobt%calving ' , mpp_chksum( iobt%calving )
write(outunit,100) 'iobt%p ' , mpp_chksum( iobt%p )
integer :: n,m

write(stdout,*) "BEGIN CHECKSUM(ice_ocean_boundary_type):: ", id, timestep
write(stdout,100) 'iobt%u_flux ' , mpp_chksum( iobt%u_flux )
write(stdout,100) 'iobt%v_flux ' , mpp_chksum( iobt%v_flux )
write(stdout,100) 'iobt%t_flux ' , mpp_chksum( iobt%t_flux )
write(stdout,100) 'iobt%q_flux ' , mpp_chksum( iobt%q_flux )
write(stdout,100) 'iobt%salt_flux ' , mpp_chksum( iobt%salt_flux )
write(stdout,100) 'iobt%seaice_melt_heat' , mpp_chksum( iobt%seaice_melt_heat)
write(stdout,100) 'iobt%seaice_melt ' , mpp_chksum( iobt%seaice_melt )
write(stdout,100) 'iobt%lw_flux ' , mpp_chksum( iobt%lw_flux )
write(stdout,100) 'iobt%sw_flux_vis_dir' , mpp_chksum( iobt%sw_flux_vis_dir)
write(stdout,100) 'iobt%sw_flux_vis_dif' , mpp_chksum( iobt%sw_flux_vis_dif)
write(stdout,100) 'iobt%sw_flux_nir_dir' , mpp_chksum( iobt%sw_flux_nir_dir)
write(stdout,100) 'iobt%sw_flux_nir_dif' , mpp_chksum( iobt%sw_flux_nir_dif)
write(stdout,100) 'iobt%lprec ' , mpp_chksum( iobt%lprec )
write(stdout,100) 'iobt%fprec ' , mpp_chksum( iobt%fprec )
write(stdout,100) 'iobt%runoff ' , mpp_chksum( iobt%runoff )
write(stdout,100) 'iobt%calving ' , mpp_chksum( iobt%calving )
write(stdout,100) 'iobt%p ' , mpp_chksum( iobt%p )
if (associated(iobt%ustar_berg)) &
write(outunit,100) 'iobt%ustar_berg ' , mpp_chksum( iobt%ustar_berg )
write(stdout,100) 'iobt%ustar_berg ' , mpp_chksum( iobt%ustar_berg )
if (associated(iobt%area_berg)) &
write(outunit,100) 'iobt%area_berg ' , mpp_chksum( iobt%area_berg )
write(stdout,100) 'iobt%area_berg ' , mpp_chksum( iobt%area_berg )
if (associated(iobt%mass_berg)) &
write(outunit,100) 'iobt%mass_berg ' , mpp_chksum( iobt%mass_berg )
write(stdout,100) 'iobt%mass_berg ' , mpp_chksum( iobt%mass_berg )
100 FORMAT(" CHECKSUM::",A20," = ",Z20)

call coupler_type_write_chksums(iobt%fluxes, outunit, 'iobt%')
call coupler_type_write_chksums(iobt%fluxes, stdout, 'iobt%')

end subroutine ice_ocn_bnd_type_chksum

Expand Down
50 changes: 25 additions & 25 deletions config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ module ocn_comp_mct
use MOM_constants, only: CELSIUS_KELVIN_OFFSET
use MOM_domains, only: AGRID, BGRID_NE, CGRID_NE, pass_vector
use mpp_domains_mod, only: mpp_get_compute_domain
use MOM_io, only: stdout

! Previously inlined - now in separate modules
use MOM_ocean_model_mct, only: ocean_public_type, ocean_state_type
Expand Down Expand Up @@ -88,7 +89,6 @@ module ocn_comp_mct
type(cpl_indices_type) :: ind !< Variable IDs
logical :: sw_decomp !< Controls whether shortwave is decomposed into 4 components
real :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition i/o
integer :: stdout !< standard output unit. (by default, points to ocn.log.* )
character(len=384) :: pointer_filename !< Name of the ascii file that contains the path
!! and filename of the latest restart file.
end type MCT_MOM_Data
Expand Down Expand Up @@ -194,14 +194,14 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
call shr_file_getLogUnit (shrlogunit)
call shr_file_getLogLevel(shrloglev)

glb%stdout = shr_file_getUnit() ! get an unused unit number
stdout = shr_file_getUnit() ! get an unused unit number

! open the ocn_modelio.nml file and then open a log file associated with stdout
ocn_modelio_name = 'ocn_modelio.nml' // trim(inst_suffix)
call shr_file_setIO(ocn_modelio_name,glb%stdout)
call shr_file_setIO(ocn_modelio_name,stdout)

! set the shr log io unit number
call shr_file_setLogUnit(glb%stdout)
call shr_file_setLogUnit(stdout)
end if

call set_calendar_type(NOLEAP) !TODO: confirm this
Expand All @@ -218,23 +218,23 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )

! Debugging clocks
if (debug .and. is_root_pe()) then
write(glb%stdout,*) 'ocn_init_mct, current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_init_mct, current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds

call ESMF_ClockGet(EClock, StartTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_init_mct, start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_init_mct, start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds

call ESMF_ClockGet(EClock, StopTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_init_mct, stop time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_init_mct, stop time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds

call ESMF_ClockGet(EClock, PrevTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_init_mct, previous time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_init_mct, previous time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds

call ESMF_ClockGet(EClock, TimeStep=ocn_cpl_interval, rc=rc)
call ESMF_TimeIntervalGet(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
write(glb%stdout,*) 'ocn_init_mct, time step: y,m,d-',year,month,day,'s,sn,sd=',seconds,seconds_n,seconds_d
write(stdout,*) 'ocn_init_mct, time step: y,m,d-',year,month,day,'s,sn,sd=',seconds,seconds_n,seconds_d
endif

npes = num_pes()
Expand Down Expand Up @@ -298,7 +298,7 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
! read name of restart file in the pointer file
nu = shr_file_getUnit()
restart_pointer_file = trim(glb%pointer_filename)
if (is_root_pe()) write(glb%stdout,*) 'Reading ocn pointer file: ',restart_pointer_file
if (is_root_pe()) write(stdout,*) 'Reading ocn pointer file: ',restart_pointer_file
restartfile = ""; restartfiles = "";
open(nu, file=restart_pointer_file, form='formatted', status='unknown')
do
Expand All @@ -316,13 +316,13 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
enddo
close(nu)
if (is_root_pe()) then
write(glb%stdout,*) 'Reading restart file(s): ',trim(restartfiles)
write(stdout,*) 'Reading restart file(s): ',trim(restartfiles)
end if
call shr_file_freeUnit(nu)
call ocean_model_init(glb%ocn_public, glb%ocn_state, time0, time_start, input_restart_file=trim(restartfiles))
endif
if (is_root_pe()) then
write(glb%stdout,'(/12x,a/)') '======== COMPLETED MOM INITIALIZATION ========'
write(stdout,'(/12x,a/)') '======== COMPLETED MOM INITIALIZATION ========'
end if

! Initialize ocn_state%sfc_state out of sight
Expand Down Expand Up @@ -383,7 +383,7 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
ncouple_per_day = seconds_in_day / ocn_cpl_dt
mom_cpl_dt = seconds_in_day / ncouple_per_day
if (mom_cpl_dt /= ocn_cpl_dt) then
write(glb%stdout,*) 'ERROR mom_cpl_dt and ocn_cpl_dt must be identical'
write(stdout,*) 'ERROR mom_cpl_dt and ocn_cpl_dt must be identical'
call exit(0)
end if

Expand Down Expand Up @@ -457,7 +457,7 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
if (is_root_pe()) then
call shr_file_getLogUnit(shrlogunit)
call shr_file_getLogLevel(shrloglev)
call shr_file_setLogUnit(glb%stdout)
call shr_file_setLogUnit(stdout)
endif

! Query the beginning time of the current coupling interval
Expand All @@ -484,7 +484,7 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
if (runtype /= "continue" .and. runtype /= "branch") then

if (debug .and. is_root_pe()) then
write(glb%stdout,*) 'doubling first interval duration!'
write(stdout,*) 'doubling first interval duration!'
endif

! shift back the start time by one coupling interval (to align the start time with other components)
Expand All @@ -500,19 +500,19 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
if (debug .and. is_root_pe()) then
call ESMF_ClockGet(EClock, CurrTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_run_mct, current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_run_mct, current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
call ESMF_ClockGet(EClock, StartTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_run_mct, start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_run_mct, start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
call ESMF_ClockGet(EClock, StopTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_run_mct, stop time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_run_mct, stop time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
call ESMF_ClockGet(EClock, PrevTime=time_var, rc=rc)
call ESMF_TimeGet(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
write(glb%stdout,*) 'ocn_run_mct, previous time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
write(stdout,*) 'ocn_run_mct, previous time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
call ESMF_ClockGet(EClock, TimeStep=ocn_cpl_interval, rc=rc)
call ESMF_TimeIntervalGet(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
write(glb%stdout,*) 'ocn_init_mct, time step: y,m,d-',year,month,day,'s,sn,sd=',seconds,seconds_n,seconds_d
write(stdout,*) 'ocn_init_mct, time step: y,m,d-',year,month,day,'s,sn,sd=',seconds,seconds_n,seconds_d
endif

! set the cdata pointers:
Expand All @@ -525,10 +525,10 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
!glb%sw_decomp = .false.
!END TODO:
if (glb%sw_decomp) then
call ocn_import(x2o_o%rattr, glb%ind, glb%grid, Ice_ocean_boundary, glb%ocn_public, glb%stdout, Eclock, &
call ocn_import(x2o_o%rattr, glb%ind, glb%grid, Ice_ocean_boundary, glb%ocn_public, stdout, Eclock, &
c1=glb%c1, c2=glb%c2, c3=glb%c3, c4=glb%c4)
else
call ocn_import(x2o_o%rattr, glb%ind, glb%grid, Ice_ocean_boundary, glb%ocn_public, glb%stdout, Eclock )
call ocn_import(x2o_o%rattr, glb%ind, glb%grid, Ice_ocean_boundary, glb%ocn_public, stdout, Eclock )
end if

! Update internal ocean
Expand All @@ -540,7 +540,7 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
!--- write out intermediate restart file when needed.
! Check alarms for flag to write restart at end of day
write_restart_at_eod = seq_timemgr_RestartAlarmIsOn(EClock)
if (debug .and. is_root_pe()) write(glb%stdout,*) 'ocn_run_mct, write_restart_at_eod=', write_restart_at_eod
if (debug .and. is_root_pe()) write(stdout,*) 'ocn_run_mct, write_restart_at_eod=', write_restart_at_eod

if (write_restart_at_eod) then
! case name
Expand Down Expand Up @@ -575,7 +575,7 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
endif

close(nu)
write(glb%stdout,*) 'ocn restart pointer file written: ',trim(restartname)
write(stdout,*) 'ocn restart pointer file written: ',trim(restartname)
endif
call shr_file_freeUnit(nu)

Expand Down Expand Up @@ -761,7 +761,7 @@ end subroutine ocn_domain_mct
else if (trim(starttype) == trim(seq_infodata_start_type_brnch)) then
get_runtype = "branch"
else
write(glb%stdout,*) 'ocn_comp_mct ERROR: unknown starttype'
write(stdout,*) 'ocn_comp_mct ERROR: unknown starttype'
call exit(0)
end if
return
Expand Down
4 changes: 2 additions & 2 deletions config_src/nuopc_driver/mom_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1215,11 +1215,11 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
!---------------------------------

if (len_trim(scalar_field_name) > 0) then
call State_SetScalar(dble(nxg),scalar_field_idx_grid_nx, exportState, localPet, &
call State_SetScalar(real(nxg,ESMF_KIND_R8),scalar_field_idx_grid_nx, exportState, localPet, &
scalar_field_name, scalar_field_count, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

call State_SetScalar(dble(nyg),scalar_field_idx_grid_ny, exportState, localPet, &
call State_SetScalar(real(nyg,ESMF_KIND_R8),scalar_field_idx_grid_ny, exportState, localPet, &
scalar_field_name, scalar_field_count, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
endif
Expand Down
Loading

0 comments on commit 040e1f1

Please sign in to comment.