Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into adiabatic_checks
Browse files Browse the repository at this point in the history
  • Loading branch information
adcroft authored Jul 28, 2021
2 parents d4305c3 + bf0b9cd commit d76af84
Show file tree
Hide file tree
Showing 13 changed files with 239 additions and 107 deletions.
4 changes: 2 additions & 2 deletions config_src/drivers/FMS_cap/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -195,8 +195,8 @@ module ocean_model_mod
type(unit_scale_type), pointer :: &
US => NULL() !< A pointer to a structure containing dimensional
!! unit scaling factors.
type(MOM_control_struct), pointer :: &
MOM_CSp => NULL() !< A pointer to the MOM control structure
type(MOM_control_struct) :: MOM_CSp
!< MOM control structure
type(ice_shelf_CS), pointer :: &
Ice_shelf_CSp => NULL() !< A pointer to the control structure for the
!! ice shelf model that couples with MOM6. This
Expand Down
4 changes: 2 additions & 2 deletions config_src/drivers/mct_cap/mom_ocean_model_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -195,8 +195,8 @@ module MOM_ocean_model_mct
!! about the vertical grid.
type(unit_scale_type), pointer :: US => NULL() !< A pointer to a structure containing
!! dimensional unit scaling factors.
type(MOM_control_struct), pointer :: &
MOM_CSp => NULL() !< A pointer to the MOM control structure
type(MOM_control_struct) :: MOM_CSp
!< MOM control structure
type(ice_shelf_CS), pointer :: &
Ice_shelf_CSp => NULL() !< A pointer to the control structure for the
!! ice shelf model that couples with MOM6. This
Expand Down
16 changes: 10 additions & 6 deletions config_src/drivers/nuopc_cap/mom_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,12 +28,12 @@ module MOM_cap_mod
use MOM_get_input, only: get_MOM_input, directories
use MOM_domains, only: pass_var
use MOM_error_handler, only: MOM_error, FATAL, is_root_pe
use MOM_ocean_model_nuopc, only: ice_ocean_boundary_type
use MOM_grid, only: ocean_grid_type, get_global_grid_size
use MOM_ocean_model_nuopc, only: ice_ocean_boundary_type
use MOM_ocean_model_nuopc, only: ocean_model_restart, ocean_public_type, ocean_state_type
use MOM_ocean_model_nuopc, only: ocean_model_init_sfc
use MOM_ocean_model_nuopc, only: ocean_model_init, update_ocean_model, ocean_model_end
use MOM_ocean_model_nuopc, only: get_ocean_grid, get_eps_omesh
use MOM_ocean_model_nuopc, only: get_ocean_grid, get_eps_omesh, query_ocean_state
use MOM_cap_time, only: AlarmInit
use MOM_cap_methods, only: mom_import, mom_export, mom_set_geomtype, mod2med_areacor
use MOM_cap_methods, only: med2mod_areacor, state_diagnose
Expand Down Expand Up @@ -421,6 +421,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
character(len=64) :: logmsg
logical :: isPresent, isPresentDiro, isPresentLogfile, isSet
logical :: existflag
logical :: use_waves ! If true, the wave modules are active.
integer :: userRc
integer :: localPet
integer :: localPeCount
Expand Down Expand Up @@ -695,19 +696,22 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
Ice_ocean_boundary%lrunoff = 0.0
Ice_ocean_boundary%frunoff = 0.0

if (ocean_state%use_waves) then
Ice_ocean_boundary%num_stk_bands=ocean_state%Waves%NumBands
call query_ocean_state(ocean_state, use_waves=use_waves)
if (use_waves) then
call query_ocean_state(ocean_state, NumWaveBands=Ice_ocean_boundary%num_stk_bands)
allocate ( Ice_ocean_boundary% ustk0 (isc:iec,jsc:jec), &
Ice_ocean_boundary% vstk0 (isc:iec,jsc:jec), &
Ice_ocean_boundary% ustkb (isc:iec,jsc:jec,Ice_ocean_boundary%num_stk_bands), &
Ice_ocean_boundary% vstkb (isc:iec,jsc:jec,Ice_ocean_boundary%num_stk_bands), &
Ice_ocean_boundary%stk_wavenumbers (Ice_ocean_boundary%num_stk_bands))
Ice_ocean_boundary%ustk0 = 0.0
Ice_ocean_boundary%vstk0 = 0.0
Ice_ocean_boundary%stk_wavenumbers = ocean_state%Waves%WaveNum_Cen
call query_ocean_state(ocean_state, WaveNumbers=Ice_ocean_boundary%stk_wavenumbers, unscale=.true.)
Ice_ocean_boundary%ustkb = 0.0
Ice_ocean_boundary%vstkb = 0.0
endif
! Consider adding this:
! if (.not.use_waves) Ice_ocean_boundary%num_stk_bands = 0

ocean_internalstate%ptr%ocean_state_type_ptr => ocean_state
call ESMF_GridCompSetInternalState(gcomp, ocean_internalstate, rc)
Expand Down Expand Up @@ -752,7 +756,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
!These are not currently used and changing requires a nuopc dictionary change
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_runoff_heat_flx" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_calving_heat_flx" , "will provide")
if (ocean_state%use_waves) then
if (use_waves) then
if (Ice_ocean_boundary%num_stk_bands > 3) then
call MOM_error(FATAL, "Number of Stokes Bands > 3, NUOPC cap not set up for this")
endif
Expand Down
39 changes: 29 additions & 10 deletions config_src/drivers/nuopc_cap/mom_ocean_model_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ module MOM_ocean_model_nuopc
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
use MOM_wave_interface, only : Update_Surface_Waves
use MOM_wave_interface, only : Update_Surface_Waves, query_wave_properties
use MOM_surface_forcing_nuopc, only : surface_forcing_init, convert_IOB_to_fluxes
use MOM_surface_forcing_nuopc, only : convert_IOB_to_forces, ice_ocn_bnd_type_chksum
use MOM_surface_forcing_nuopc, only : ice_ocean_boundary_type, surface_forcing_CS
Expand All @@ -80,7 +80,7 @@ module MOM_ocean_model_nuopc
public ocean_model_restart
public ice_ocn_bnd_type_chksum
public ocean_public_type_chksum
public get_ocean_grid
public get_ocean_grid, query_ocean_state
public get_eps_omesh

!> This type is used for communication with other components via the FMS coupler.
Expand Down Expand Up @@ -197,8 +197,8 @@ module MOM_ocean_model_nuopc
!! about the vertical grid.
type(unit_scale_type), pointer :: US => NULL() !< A pointer to a structure containing
!! dimensional unit scaling factors.
type(MOM_control_struct), pointer :: &
MOM_CSp => NULL() !< A pointer to the MOM control structure
type(MOM_control_struct) :: MOM_CSp
!< MOM control structure
type(ice_shelf_CS), pointer :: &
Ice_shelf_CSp => NULL() !< A pointer to the control structure for the
!! ice shelf model that couples with MOM6. This
Expand Down Expand Up @@ -391,12 +391,6 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
! MOM_wave_interface_init is called regardless of the value of USE_WAVES because
! it also initializes statistical waves.
call MOM_wave_interface_init(OS%Time, OS%grid, OS%GV, OS%US, param_file, OS%Waves, OS%diag)
if (OS%use_waves) then
! I do not know why this is being set here. It seems out of place. -RWH
call get_param(param_file,mdl,"SURFBAND_WAVENUMBERS", OS%Waves%WaveNum_Cen, &
"Central wavenumbers for surface Stokes drift bands.", &
units='rad/m', default=0.12566, scale=OS%US%Z_to_m)
endif

if (associated(OS%grid%Domain%maskmap)) then
call initialize_ocean_public_type(OS%grid%Domain%mpp_domain, Ocean_sfc, &
Expand Down Expand Up @@ -1006,6 +1000,31 @@ subroutine ocean_model_flux_init(OS, verbosity)

end subroutine ocean_model_flux_init

!> This interface allows certain properties that are stored in the ocean_state_type to be
!! obtained.
subroutine query_ocean_state(OS, use_waves, NumWaveBands, Wavenumbers, unscale)
type(ocean_state_type), intent(in) :: OS !< The structure with the complete ocean state
logical, optional, intent(out) :: use_waves !< Indicates whether surface waves are in use
integer, optional, intent(out) :: NumWaveBands !< If present, this gives the number of
!! wavenumber partitions in the wave discretization
real, dimension(:), optional, intent(out) :: Wavenumbers !< If present, this gives the characteristic
!! wavenumbers of the wave discretization [m-1 or Z-1 ~> m-1]
logical, optional, intent(in) :: unscale !< If present and true, undo any dimensional
!! rescaling and return dimensional values in MKS units

logical :: undo_scaling
undo_scaling = .false. ; if (present(unscale)) undo_scaling = unscale

if (present(use_waves)) use_waves = OS%use_waves
if (present(NumWaveBands)) call query_wave_properties(OS%Waves, NumBands=NumWaveBands)
if (present(Wavenumbers) .and. undo_scaling) then
call query_wave_properties(OS%Waves, WaveNumbers=WaveNumbers, US=OS%US)
elseif (present(Wavenumbers)) then
call query_wave_properties(OS%Waves, WaveNumbers=WaveNumbers)
endif

end subroutine query_ocean_state

!> Ocean_stock_pe - returns the integrated stocks of heat, water, etc. for conservation checks.
!! Because of the way FMS is coded, only the root PE has the integrated amount,
!! while all other PEs get 0.
Expand Down
3 changes: 1 addition & 2 deletions config_src/drivers/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -180,8 +180,7 @@ program MOM_main
! and diffusion equation are read in from files stored from
! a previous integration of the prognostic model

type(MOM_control_struct), pointer :: MOM_CSp => NULL()
!> A pointer to the tracer flow control structure.
type(MOM_control_struct) :: MOM_CSp !> MOM control structure
type(tracer_flow_control_CS), pointer :: &
tracer_flow_CSp => NULL() !< A pointer to the tracer flow control structure
type(surface_forcing_CS), pointer :: surface_forcing_CSp => NULL()
Expand Down
34 changes: 14 additions & 20 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -434,7 +434,7 @@ subroutine step_MOM(forces_in, fluxes_in, sfc_state, Time_start, time_int_in, CS
type(surface), target, intent(inout) :: sfc_state !< surface ocean state
type(time_type), intent(in) :: Time_start !< starting time of a segment, as a time type
real, intent(in) :: time_int_in !< time interval covered by this run segment [s].
type(MOM_control_struct), pointer :: CS !< control structure from initialize_MOM
type(MOM_control_struct), intent(inout), target :: CS !< control structure from initialize_MOM
type(Wave_parameters_CS), &
optional, pointer :: Waves !< An optional pointer to a wave property CS
logical, optional, intent(in) :: do_dynamics !< Present and false, do not do updates due
Expand Down Expand Up @@ -981,7 +981,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
real, intent(in) :: bbl_time_int !< time interval over which updates to the
!! bottom boundary layer properties will apply [T ~> s],
!! or zero not to update the properties.
type(MOM_control_struct), pointer :: CS !< control structure from initialize_MOM
type(MOM_control_struct), intent(inout), target :: CS !< control structure from initialize_MOM
type(time_type), intent(in) :: Time_local !< End time of a segment, as a time type
type(wave_parameters_CS), &
optional, pointer :: Waves !< Container for wave related parameters; the
Expand Down Expand Up @@ -1432,7 +1432,7 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
type(surface), intent(inout) :: sfc_state !< surface ocean state
type(time_type), intent(in) :: Time_start !< starting time of a segment, as a time type
real, intent(in) :: time_interval !< time interval
type(MOM_control_struct), pointer :: CS !< control structure from initialize_MOM
type(MOM_control_struct), intent(inout) :: CS !< control structure from initialize_MOM

! Local pointers
type(ocean_grid_type), pointer :: G => NULL() ! Pointer to a structure containing
Expand Down Expand Up @@ -1630,7 +1630,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
type(time_type), intent(in) :: Time_init !< The start time for the coupled model's calendar
type(param_file_type), intent(out) :: param_file !< structure indicating parameter file to parse
type(directories), intent(out) :: dirs !< structure with directory paths
type(MOM_control_struct), pointer :: CS !< pointer set in this routine to MOM control structure
type(MOM_control_struct), intent(inout), target :: CS !< pointer set in this routine to MOM control structure
type(MOM_restart_CS), pointer :: restart_CSp !< pointer set in this routine to the
!! restart control structure that will
!! be used for MOM.
Expand Down Expand Up @@ -1730,13 +1730,6 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
type(ocean_internal_state) :: MOM_internal_state
character(len=200) :: area_varname, ice_shelf_file, inputdir, filename

if (associated(CS)) then
call MOM_error(WARNING, "initialize_MOM called with an associated "// &
"control structure.")
return
endif
allocate(CS)

CS%Time => Time

id_clock_init = cpu_clock_id('Ocean Initialization', grain=CLOCK_SUBCOMPONENT)
Expand Down Expand Up @@ -2818,7 +2811,7 @@ end subroutine initialize_MOM
subroutine finish_MOM_initialization(Time, dirs, CS, restart_CSp)
type(time_type), intent(in) :: Time !< model time, used in this routine
type(directories), intent(in) :: dirs !< structure with directory paths
type(MOM_control_struct), pointer :: CS !< pointer to MOM control structure
type(MOM_control_struct), intent(inout) :: CS !< MOM control structure
type(MOM_restart_CS), pointer :: restart_CSp !< pointer to the restart control
!! structure that will be used for MOM.
! Local variables
Expand Down Expand Up @@ -3044,7 +3037,7 @@ end subroutine adjust_ssh_for_p_atm
!! setting the appropriate fields in sfc_state. Unused fields
!! are set to NULL or are unallocated.
subroutine extract_surface_state(CS, sfc_state_in)
type(MOM_control_struct), pointer :: CS !< Master MOM control structure
type(MOM_control_struct), intent(inout), target :: CS !< Master MOM control structure
type(surface), target, intent(inout) :: sfc_state_in !< transparent ocean surface state
!! structure shared with the calling routine
!! data in this structure is intent out.
Expand Down Expand Up @@ -3471,7 +3464,7 @@ end subroutine rotate_initial_state

!> Return true if all phases of step_MOM are at the same point in time.
function MOM_state_is_synchronized(CS, adv_dyn) result(in_synch)
type(MOM_control_struct), pointer :: CS !< MOM control structure
type(MOM_control_struct), intent(inout) :: CS !< MOM control structure
logical, optional, intent(in) :: adv_dyn !< If present and true, only check
!! whether the advection is up-to-date with
!! the dynamics.
Expand All @@ -3492,7 +3485,7 @@ end function MOM_state_is_synchronized
!> This subroutine offers access to values or pointers to other types from within
!! the MOM_control_struct, allowing the MOM_control_struct to be opaque.
subroutine get_MOM_state_elements(CS, G, GV, US, C_p, C_p_scaled, use_temp)
type(MOM_control_struct), pointer :: CS !< MOM control structure
type(MOM_control_struct), intent(inout), target :: CS !< MOM control structure
type(ocean_grid_type), optional, pointer :: G !< structure containing metrics and grid info
type(verticalGrid_type), optional, pointer :: GV !< structure containing vertical grid info
type(unit_scale_type), optional, pointer :: US !< A dimensional unit scaling type
Expand All @@ -3511,7 +3504,7 @@ end subroutine get_MOM_state_elements

!> Find the global integrals of various quantities.
subroutine get_ocean_stocks(CS, mass, heat, salt, on_PE_only)
type(MOM_control_struct), pointer :: CS !< MOM control structure
type(MOM_control_struct), intent(inout) :: CS !< MOM control structure
real, optional, intent(out) :: heat !< The globally integrated integrated ocean heat [J].
real, optional, intent(out) :: salt !< The globally integrated integrated ocean salt [kg].
real, optional, intent(out) :: mass !< The globally integrated integrated ocean mass [kg].
Expand All @@ -3528,7 +3521,7 @@ end subroutine get_ocean_stocks

!> End of ocean model, including memory deallocation
subroutine MOM_end(CS)
type(MOM_control_struct), pointer :: CS !< MOM control structure
type(MOM_control_struct), intent(inout) :: CS !< MOM control structure

call MOM_sum_output_end(CS%sum_output_CSp)

Expand Down Expand Up @@ -3604,7 +3597,6 @@ subroutine MOM_end(CS)
if (associated(CS%update_OBC_CSp)) call OBC_register_end(CS%update_OBC_CSp)

call verticalGridEnd(CS%GV)
call unit_scaling_end(CS%US)
call MOM_grid_end(CS%G)

if (CS%debug .or. CS%G%symmetric) &
Expand All @@ -3613,9 +3605,11 @@ subroutine MOM_end(CS)
if (CS%rotate_index) &
call deallocate_MOM_domain(CS%G%Domain)

call deallocate_MOM_domain(CS%G_in%domain)
! The MPP domains may be needed by an external coupler, so use `cursory`.
! TODO: This may create a domain memory leak, and needs investigation.
call deallocate_MOM_domain(CS%G_in%domain, cursory=.true.)

deallocate(CS)
call unit_scaling_end(CS%US)
end subroutine MOM_end

!> \namespace mom
Expand Down
4 changes: 4 additions & 0 deletions src/core/MOM_variables.F90
Original file line number Diff line number Diff line change
Expand Up @@ -169,6 +169,10 @@ module MOM_variables
PFv => NULL(), & !< Meridional acceleration due to pressure forces [L T-2 ~> m s-2]
du_dt_visc => NULL(), &!< Zonal acceleration due to vertical viscosity [L T-2 ~> m s-2]
dv_dt_visc => NULL(), &!< Meridional acceleration due to vertical viscosity [L T-2 ~> m s-2]
du_dt_str => NULL(), & !< Zonal acceleration due to the surface stress (included
!! in du_dt_visc) [L T-2 ~> m s-2]
dv_dt_str => NULL(), & !< Meridional acceleration due to the surface stress (included
!! in dv_dt_visc) [L T-2 ~> m s-2]
du_dt_dia => NULL(), & !< Zonal acceleration due to diapycnal mixing [L T-2 ~> m s-2]
dv_dt_dia => NULL(), & !< Meridional acceleration due to diapycnal mixing [L T-2 ~> m s-2]
u_accel_bt => NULL(), &!< Pointer to the zonal barotropic-solver acceleration [L T-2 ~> m s-2]
Expand Down
Loading

0 comments on commit d76af84

Please sign in to comment.