Skip to content

Commit

Permalink
Merge pull request #42 from NOAA-GFDL/dev/gfdl
Browse files Browse the repository at this point in the history
Merge in latest dev/gfdl updates
  • Loading branch information
wrongkindofdoctor authored Dec 17, 2019
2 parents 075ab81 + d23a1f9 commit abaf004
Show file tree
Hide file tree
Showing 12 changed files with 187 additions and 162 deletions.
20 changes: 13 additions & 7 deletions config_src/coupled_driver/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -205,7 +205,7 @@ module MOM_surface_forcing_gfdl
!> This subroutine translates the Ice_ocean_boundary_type into a MOM
!! thermodynamic forcing type, including changes of units, sign conventions,
!! and putting the fields into arrays with MOM-standard halos.
subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc_state)
subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G, US, CS, sfc_state)
type(ice_ocean_boundary_type), &
target, intent(in) :: IOB !< An ice-ocean boundary type with fluxes to drive
!! the ocean in a coupled model
Expand All @@ -215,6 +215,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc
integer, dimension(4), intent(in) :: index_bounds !< The i- and j- size of the arrays in IOB.
type(time_type), intent(in) :: Time !< The time of the fluxes, used for interpolating the
!! salinity to the right time, when it is being restored.
real, intent(in) :: valid_time !< The amount of time over which these fluxes
!! should be applied [s].
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(surface_forcing_CS),pointer :: CS !< A pointer to the control structure returned by a
Expand Down Expand Up @@ -307,7 +309,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc

if (CS%restore_temp) call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)

fluxes%dt_buoy_accum = 0.0
endif ! endif for allocation and initialization


Expand All @@ -324,11 +325,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc
! ocean model, rather than using haloless arrays, in which case the last line
! would be: ( (/isd,is,ie,ied/), (/jsd,js,je,jed/))

if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif

! allocation and initialization on first call to this routine
if (CS%area_surf < 0.0) then
do j=js,je ; do i=is,ie
Expand All @@ -337,6 +333,16 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc
CS%area_surf = reproducing_sum(work_sum, isr, ier, jsr, jer)
endif ! endif for allocation and initialization


! Indicate that there are new unused fluxes.
fluxes%fluxes_used = .false.
fluxes%dt_buoy_accum = US%s_to_T*valid_time

if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif

do j=js,je ; do i=is,ie
fluxes%salt_flux(i,j) = 0.0
fluxes%vprec(i,j) = 0.0
Expand Down
18 changes: 5 additions & 13 deletions config_src/coupled_driver/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -513,7 +513,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda

if (do_thermo) then
if (OS%fluxes%fluxes_used) then
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%fluxes, index_bnds, OS%Time, &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%fluxes, index_bnds, OS%Time, dt_coupling, &
OS%grid, OS%US, OS%forcing_CSp, OS%sfc_state)

! Add ice shelf fluxes
Expand All @@ -528,14 +528,11 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda
call MOM_generic_tracer_fluxes_accumulate(OS%fluxes, 1.0) ! Here weight=1, so just store the current fluxes
call disable_averaging(OS%diag)
#endif
! Indicate that there are new unused fluxes.
OS%fluxes%fluxes_used = .false.
OS%fluxes%dt_buoy_accum = dt_coupling
else
! The previous fluxes have not been used yet, so translate the input fluxes
! into a temporary type and then accumulate them in about 20 lines.
OS%flux_tmp%C_p = OS%fluxes%C_p
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%flux_tmp, index_bnds, OS%Time, &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%flux_tmp, index_bnds, OS%Time, dt_coupling, &
OS%grid, OS%US, OS%forcing_CSp, OS%sfc_state)

if (OS%use_ice_shelf) &
Expand All @@ -544,7 +541,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda
call iceberg_fluxes(OS%grid, OS%US, OS%flux_tmp, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)

call fluxes_accumulate(OS%flux_tmp, OS%fluxes, dt_coupling, OS%grid, weight)
call fluxes_accumulate(OS%flux_tmp, OS%fluxes, OS%grid, weight)
#ifdef _USE_GENERIC_TRACER
! Incorporate the current tracer fluxes into the running averages
call MOM_generic_tracer_fluxes_accumulate(OS%flux_tmp, weight)
Expand Down Expand Up @@ -646,16 +643,11 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda
if (do_thermo) OS%nstep_thermo = OS%nstep_thermo + 1

if (do_dyn) then
call enable_averaging(dt_coupling, OS%Time_dyn, OS%diag)
call mech_forcing_diags(OS%forces, dt_coupling, OS%grid, OS%diag, OS%forcing_CSp%handles)
call disable_averaging(OS%diag)
call mech_forcing_diags(OS%forces, dt_coupling, OS%grid, OS%Time_dyn, OS%diag, OS%forcing_CSp%handles)
endif

if (OS%fluxes%fluxes_used .and. do_thermo) then
call enable_averaging(OS%fluxes%dt_buoy_accum, OS%Time, OS%diag)
call forcing_diagnostics(OS%fluxes, OS%sfc_state, OS%fluxes%dt_buoy_accum, &
OS%grid, OS%US, OS%diag, OS%forcing_CSp%handles)
call disable_averaging(OS%diag)
call forcing_diagnostics(OS%fluxes, OS%sfc_state, OS%grid, OS%US, OS%Time, OS%diag, OS%forcing_CSp%handles)
endif

! Translate state into Ocean.
Expand Down
19 changes: 5 additions & 14 deletions config_src/mct_driver/mom_ocean_model_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -515,7 +515,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call enable_averaging(dt_coupling, OS%Time + Ocean_coupling_time_step, OS%diag)

if (do_thermo) &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%fluxes, index_bnds, OS%Time, &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%fluxes, index_bnds, OS%Time, dt_coupling, &
OS%grid, OS%US, OS%forcing_CSp, OS%sfc_state, &
OS%restore_salinity, OS%restore_temp)

Expand Down Expand Up @@ -543,16 +543,12 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call MOM_generic_tracer_fluxes_accumulate(OS%fluxes, weight) !here weight=1, just saving the current fluxes
#endif

! Indicate that there are new unused fluxes.
OS%fluxes%fluxes_used = .false.
OS%fluxes%dt_buoy_accum = dt_coupling

else

OS%flux_tmp%C_p = OS%fluxes%C_p

if (do_thermo) &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%flux_tmp, index_bnds, OS%Time, &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%flux_tmp, index_bnds, OS%Time, dt_coupling, &
OS%grid, OS%US, OS%forcing_CSp, OS%sfc_state, OS%restore_salinity,OS%restore_temp)

if (OS%use_ice_shelf) then
Expand All @@ -570,7 +566,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
endif

call forcing_accumulate(OS%flux_tmp, OS%forces, OS%fluxes, dt_coupling, OS%grid, weight)
call forcing_accumulate(OS%flux_tmp, OS%forces, OS%fluxes, OS%grid, weight)

! Some of the fields that exist in both the forcing and mech_forcing types
! (e.g., ustar) are time-averages must be copied back to the forces type.
Expand Down Expand Up @@ -669,15 +665,10 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
OS%Time = Master_time + Ocean_coupling_time_step
OS%nstep = OS%nstep + 1

call enable_averaging(dt_coupling, OS%Time, OS%diag)
call mech_forcing_diags(OS%forces, dt_coupling, OS%grid, OS%diag, OS%forcing_CSp%handles)
call disable_averaging(OS%diag)
call mech_forcing_diags(OS%forces, dt_coupling, OS%grid, OS%Time, OS%diag, OS%forcing_CSp%handles)

if (OS%fluxes%fluxes_used) then
call enable_averaging(OS%fluxes%dt_buoy_accum, OS%Time, OS%diag)
call forcing_diagnostics(OS%fluxes, OS%sfc_state, OS%fluxes%dt_buoy_accum, &
OS%grid, OS%US, OS%diag, OS%forcing_CSp%handles)
call disable_averaging(OS%diag)
call forcing_diagnostics(OS%fluxes, OS%sfc_state, OS%grid, OS%US, OS%Time, OS%diag, OS%forcing_CSp%handles)
endif

! Translate state into Ocean.
Expand Down
20 changes: 13 additions & 7 deletions config_src/mct_driver/mom_surface_forcing_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -192,7 +192,7 @@ module MOM_surface_forcing_mct
!> This subroutine translates the Ice_ocean_boundary_type into a MOM
!! thermodynamic forcing type, including changes of units, sign conventions,
!! and putting the fields into arrays with MOM-standard halos.
subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G, US, CS, &
sfc_state, restore_salt, restore_temp)

type(ice_ocean_boundary_type), &
Expand All @@ -205,6 +205,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
integer, dimension(4), intent(in) :: index_bounds !< The i- and j- size of the arrays in IOB.
type(time_type), intent(in) :: Time !< The time of the fluxes, used for interpolating the
!! salinity to the right time, when it is being restored.
real, intent(in) :: valid_time !< The amount of time over which these fluxes
!! should be applied [s].
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(surface_forcing_CS),pointer :: CS !< A pointer to the control structure returned by a
Expand Down Expand Up @@ -309,7 +311,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &

if (restore_temp) call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)

fluxes%dt_buoy_accum = 0.0
endif ! endif for allocation and initialization


Expand All @@ -326,11 +327,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
! ocean model, rather than using haloless arrays, in which case the last line
! would be: ( (/isd,is,ie,ied/), (/jsd,js,je,jed/))

if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif

! allocation and initialization on first call to this routine
if (CS%area_surf < 0.0) then
do j=js,je ; do i=is,ie
Expand All @@ -339,6 +335,16 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
CS%area_surf = reproducing_sum(work_sum, isr, ier, jsr, jer)
endif ! endif for allocation and initialization


! Indicate that there are new unused fluxes.
fluxes%fluxes_used = .false.
fluxes%dt_buoy_accum = US%s_to_T*valid_time

if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif

do j=js,je ; do i=is,ie
fluxes%salt_flux(i,j) = 0.0
fluxes%vprec(i,j) = 0.0
Expand Down
18 changes: 5 additions & 13 deletions config_src/nuopc_driver/mom_ocean_model_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -517,7 +517,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &

if (OS%fluxes%fluxes_used) then
if (do_thermo) &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%fluxes, index_bnds, OS%Time, &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%fluxes, index_bnds, OS%Time, dt_coupling, &
OS%grid, OS%US, OS%forcing_CSp, OS%sfc_state, &
OS%restore_salinity, OS%restore_temp)

Expand All @@ -544,13 +544,10 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call enable_averaging(dt_coupling, OS%Time + Ocean_coupling_time_step, OS%diag) !Is this needed?
call MOM_generic_tracer_fluxes_accumulate(OS%fluxes, weight) !here weight=1, just saving the current fluxes
#endif
! Indicate that there are new unused fluxes.
OS%fluxes%fluxes_used = .false.
OS%fluxes%dt_buoy_accum = dt_coupling
else
OS%flux_tmp%C_p = OS%fluxes%C_p
if (do_thermo) &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%flux_tmp, index_bnds, OS%Time, &
call convert_IOB_to_fluxes(Ice_ocean_boundary, OS%flux_tmp, index_bnds, OS%Time, dt_coupling, &
OS%grid, OS%US, OS%forcing_CSp, OS%sfc_state, OS%restore_salinity,OS%restore_temp)

if (OS%use_ice_shelf) then
Expand All @@ -568,7 +565,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
endif

call forcing_accumulate(OS%flux_tmp, OS%forces, OS%fluxes, dt_coupling, OS%grid, weight)
call forcing_accumulate(OS%flux_tmp, OS%forces, OS%fluxes, OS%grid, weight)
! Some of the fields that exist in both the forcing and mech_forcing types
! (e.g., ustar) are time-averages must be copied back to the forces type.
call copy_back_forcing_fields(OS%fluxes, OS%forces, OS%grid)
Expand Down Expand Up @@ -664,15 +661,10 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
OS%Time = Master_time + Ocean_coupling_time_step
OS%nstep = OS%nstep + 1

call enable_averaging(dt_coupling, OS%Time, OS%diag)
call mech_forcing_diags(OS%forces, dt_coupling, OS%grid, OS%diag, OS%forcing_CSp%handles)
call disable_averaging(OS%diag)
call mech_forcing_diags(OS%forces, dt_coupling, OS%grid, OS%Time, OS%diag, OS%forcing_CSp%handles)

if (OS%fluxes%fluxes_used) then
call enable_averaging(OS%fluxes%dt_buoy_accum, OS%Time, OS%diag)
call forcing_diagnostics(OS%fluxes, OS%sfc_state, OS%fluxes%dt_buoy_accum, &
OS%grid, US%US, OS%diag, OS%forcing_CSp%handles)
call disable_averaging(OS%diag)
call forcing_diagnostics(OS%fluxes, OS%sfc_state, OS%grid, OS%US, OS%Time, OS%diag, OS%forcing_CSp%handles)
endif

! Translate state into Ocean.
Expand Down
22 changes: 13 additions & 9 deletions config_src/nuopc_driver/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -199,7 +199,7 @@ module MOM_surface_forcing_nuopc
!> This subroutine translates the Ice_ocean_boundary_type into a MOM
!! thermodynamic forcing type, including changes of units, sign conventions,
!! and putting the fields into arrays with MOM-standard halos.
subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G, US, CS, &
sfc_state, restore_salt, restore_temp)
type(ice_ocean_boundary_type), &
target, intent(in) :: IOB !< An ice-ocean boundary type with fluxes to drive
Expand All @@ -210,6 +210,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
integer, dimension(4), intent(in) :: index_bounds !< The i- and j- size of the arrays in IOB.
type(time_type), intent(in) :: Time !< The time of the fluxes, used for interpolating the
!! salinity to the right time, when it is being restored.
real, intent(in) :: valid_time !< The amount of time over which these fluxes
!! should be applied [s].
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(surface_forcing_CS),pointer :: CS !< A pointer to the control structure returned by a
Expand Down Expand Up @@ -314,10 +316,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &

if (restore_temp) call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)

fluxes%dt_buoy_accum = 0.0
endif ! endif for allocation and initialization


if (((associated(IOB%ustar_berg) .and. (.not.associated(fluxes%ustar_berg))) &
.or. (associated(IOB%area_berg) .and. (.not.associated(fluxes%area_berg)))) &
.or. (associated(IOB%mass_berg) .and. (.not.associated(fluxes%mass_berg)))) &
Expand All @@ -331,12 +331,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
! ocean model, rather than using haloless arrays, in which case the last line
! would be: ( (/isd,is,ie,ied/), (/jsd,js,je,jed/))


if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif

! allocation and initialization on first call to this routine
if (CS%area_surf < 0.0) then
do j=js,je ; do i=is,ie
Expand All @@ -345,6 +339,16 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &
CS%area_surf = reproducing_sum(work_sum, isr, ier, jsr, jer)
endif ! endif for allocation and initialization


! Indicate that there are new unused fluxes.
fluxes%fluxes_used = .false.
fluxes%dt_buoy_accum = US%s_to_T*valid_time

if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif

do j=js,je ; do i=is,ie
fluxes%salt_flux(i,j) = 0.0
fluxes%vprec(i,j) = 0.0
Expand Down
19 changes: 9 additions & 10 deletions config_src/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -133,12 +133,15 @@ program MOM_main
! if Time_step_ocean is not an exact
! representation of dt_forcing.
real :: dt_forcing ! The coupling time step [s].
real :: dt ! The baroclinic dynamics time step [s].
real :: dt ! The nominal baroclinic dynamics time step [s].
real :: dt_off ! Offline time step [s].
integer :: ntstep ! The number of baroclinic dynamics time steps
! within dt_forcing.
real :: dt_therm
real :: dt_dyn, dtdia, t_elapsed_seg
real :: dt_therm ! The thermodynamic timestep [s]
real :: dt_dyn ! The actual dynamic timestep used [s]. The value of dt_dyn is
! chosen so that dt_forcing is an integer multiple of dt_dyn.
real :: dtdia ! The diabatic timestep [s]
real :: t_elapsed_seg ! The elapsed time in this run segment [s]
integer :: n, n_max, nts, n_last_thermo
logical :: diabatic_first, single_step_call
type(time_type) :: Time2, time_chg
Expand Down Expand Up @@ -491,7 +494,7 @@ program MOM_main
call add_shelf_forces(grid, US, Ice_shelf_CSp, forces)
endif
fluxes%fluxes_used = .false.
fluxes%dt_buoy_accum = dt_forcing
fluxes%dt_buoy_accum = US%s_to_T*dt_forcing

if (use_waves) then
call Update_Surface_Waves(grid, GV, US, time, time_step_ocean, waves_csp)
Expand Down Expand Up @@ -573,16 +576,12 @@ program MOM_main
call write_cputime(Time, ns+ntstep-1, nmax, write_CPU_CSp)
endif ; endif

call enable_averaging(dt_forcing, Time, diag)
call mech_forcing_diags(forces, dt_forcing, grid, diag, surface_forcing_CSp%handles)
call disable_averaging(diag)
call mech_forcing_diags(forces, dt_forcing, grid, Time, diag, surface_forcing_CSp%handles)

if (.not. offline_tracer_mode) then
if (fluxes%fluxes_used) then
call enable_averaging(fluxes%dt_buoy_accum, Time, diag)
call forcing_diagnostics(fluxes, sfc_state, fluxes%dt_buoy_accum, grid, US, &
call forcing_diagnostics(fluxes, sfc_state, grid, US, Time, &
diag, surface_forcing_CSp%handles)
call disable_averaging(diag)
else
call MOM_error(FATAL, "The solo MOM_driver is not yet set up to handle "//&
"thermodynamic time steps that are longer than the coupling timestep.")
Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -626,7 +626,7 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_int_in, CS, &
elseif (thermo_does_span_coupling) then
dtdia = dt_therm
if ((fluxes%dt_buoy_accum > 0.0) .and. (dtdia > time_interval) .and. &
(abs(US%s_to_T*fluxes%dt_buoy_accum - dtdia) > 1e-6*dtdia)) then
(abs(fluxes%dt_buoy_accum - dtdia) > 1e-6*dtdia)) then
call MOM_error(FATAL, "step_MOM: Mismatch between long thermodynamic "//&
"timestep and time over which buoyancy fluxes have been accumulated.")
endif
Expand Down
Loading

0 comments on commit abaf004

Please sign in to comment.