Skip to content

Commit

Permalink
+Changed units of fluxes%TKE_tidal to [R Z3 T-3]
Browse files Browse the repository at this point in the history
  Changed the units of fluxes%TKE_tidal to [R Z3 T-3] and rescaled the internal
representation of the tidal velocities to [Z T-1] in varoius forcing routines
for dimensional consistency testing.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Oct 4, 2019
1 parent fb47d7b commit dfd5278
Show file tree
Hide file tree
Showing 5 changed files with 38 additions and 37 deletions.
20 changes: 10 additions & 10 deletions config_src/coupled_driver/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -89,14 +89,14 @@ module MOM_surface_forcing_gfdl
logical :: read_gust_2d !< If true, use a 2-dimensional gustiness supplied from an input file.
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL() !< Turbulent kinetic energy introduced to the bottom boundary layer
!! by drag on the tidal flows [W m-2].
!! by drag on the tidal flows [R Z3 T-3 ~> W m-2].
real, pointer, dimension(:,:) :: &
gust => NULL() !< A spatially varying unresolved background gustiness that
!! contributes to ustar [R L Z T-1 ~> Pa]. gust is used when read_gust_2d is true.
real, pointer, dimension(:,:) :: &
ustar_tidal => NULL() !< Tidal contribution to the bottom friction velocity [m s-1]
ustar_tidal => NULL() !< Tidal contribution to the bottom friction velocity [Z T-1 ~> m s-1]
real :: cd_tides !< Drag coefficient that applies to the tides (nondimensional)
real :: utide !< Constant tidal velocity to use if read_tideamp is false [m s-1].
real :: utide !< Constant tidal velocity to use if read_tideamp is false [Z T-1 ~> m s-1].
logical :: read_tideamp !< If true, spatially varying tidal amplitude read from a file.

logical :: rigid_sea_ice !< If true, sea-ice exerts a rigidity that acts to damp surface
Expand Down Expand Up @@ -298,7 +298,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc

do j=js-2,je+2 ; do i=is-2,ie+2
fluxes%TKE_tidal(i,j) = CS%TKE_tidal(i,j)
fluxes%ustar_tidal(i,j) = US%m_to_Z*US%T_to_s*CS%ustar_tidal(i,j)
fluxes%ustar_tidal(i,j) = CS%ustar_tidal(i,j)
enddo ; enddo

if (CS%restore_temp) call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)
Expand Down Expand Up @@ -1218,7 +1218,7 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS)
!! structure for this module

! Local variables
real :: utide ! The RMS tidal velocity [m s-1].
real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1].
type(directories) :: dirs
logical :: new_sim, iceberg_flux_diags
logical :: default_2018_answers
Expand Down Expand Up @@ -1429,24 +1429,24 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS)
else
call get_param(param_file, mdl, "UTIDE", CS%utide, &
"The constant tidal amplitude used with INT_TIDE_DISSIPATION.", &
units="m s-1", default=0.0)
units="m s-1", default=0.0, scale=US%m_to_Z*US%T_to_s)
endif

call safe_alloc_ptr(CS%TKE_tidal,isd,ied,jsd,jed)
call safe_alloc_ptr(CS%ustar_tidal,isd,ied,jsd,jed)

if (CS%read_TIDEAMP) then
TideAmp_file = trim(CS%inputdir) // trim(TideAmp_file)
call MOM_read_data(TideAmp_file,'tideamp',CS%TKE_tidal,G%domain,timelevel=1)
call MOM_read_data(TideAmp_file,'tideamp',CS%TKE_tidal,G%domain,timelevel=1, scale=US%m_to_Z*US%T_to_s)
do j=jsd, jed; do i=isd, ied
utide = CS%TKE_tidal(i,j)
CS%TKE_tidal(i,j) = G%mask2dT(i,j)*US%R_to_kg_m3*CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%TKE_tidal(i,j) = G%mask2dT(i,j)*CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%ustar_tidal(i,j) = sqrt(CS%cd_tides)*utide
enddo ; enddo
else
do j=jsd,jed; do i=isd,ied
utide=CS%utide
CS%TKE_tidal(i,j) = US%R_to_kg_m3*CS%Rho0*CS%cd_tides*(utide*utide*utide)
utide = CS%utide
CS%TKE_tidal(i,j) = CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%ustar_tidal(i,j) = sqrt(CS%cd_tides)*utide
enddo ; enddo
endif
Expand Down
20 changes: 10 additions & 10 deletions config_src/mct_driver/mom_surface_forcing_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -83,14 +83,14 @@ module MOM_surface_forcing_mct
!! from an input file.
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL(), & !< turbulent kinetic energy introduced to the
!! bottom boundary layer by drag on the tidal flows [W m-2]
!! bottom boundary layer by drag on the tidal flows [R Z3 T-3 ~> W m-2]
gust => NULL(), & !< spatially varying unresolved background
!! gustiness that contributes to ustar [R L Z T-1 ~> Pa].
!! gust is used when read_gust_2d is true.
ustar_tidal => NULL() !< tidal contribution to the bottom friction velocity [m/s]
ustar_tidal => NULL() !< tidal contribution to the bottom friction velocity [Z T-1 ~> m s-1]
real :: cd_tides !< drag coefficient that applies to the tides (nondimensional)
real :: utide !< constant tidal velocity to use if read_tideamp
!! is false [m s-1]
!! is false [Z T-1 ~> m s-1]
logical :: read_tideamp !< If true, spatially varying tidal amplitude read from a file.
logical :: rigid_sea_ice !< If true, sea-ice exerts a rigidity that acts
!! to damp surface deflections (especially surface
Expand Down Expand Up @@ -301,7 +301,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &

do j=js-2,je+2 ; do i=is-2,ie+2
fluxes%TKE_tidal(i,j) = CS%TKE_tidal(i,j)
fluxes%ustar_tidal(i,j) = US%m_to_Z*US%T_to_s*CS%ustar_tidal(i,j)
fluxes%ustar_tidal(i,j) = CS%ustar_tidal(i,j)
enddo; enddo

if (restore_temp) call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)
Expand Down Expand Up @@ -1002,7 +1002,7 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
!! restoring will be applied in this model.

! Local variables
real :: utide ! The RMS tidal velocity, in m s-1.
real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1].
type(directories) :: dirs
logical :: new_sim, iceberg_flux_diags
type(time_type) :: Time_frc
Expand Down Expand Up @@ -1199,24 +1199,24 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
else
call get_param(param_file, mdl, "UTIDE", CS%utide, &
"The constant tidal amplitude used with INT_TIDE_DISSIPATION.", &
units="m s-1", default=0.0)
units="m s-1", default=0.0, scale=US%m_to_Z*US%T_to_s)
endif

call safe_alloc_ptr(CS%TKE_tidal,isd,ied,jsd,jed)
call safe_alloc_ptr(CS%ustar_tidal,isd,ied,jsd,jed)

if (CS%read_TIDEAMP) then
TideAmp_file = trim(CS%inputdir) // trim(TideAmp_file)
call MOM_read_data(TideAmp_file,'tideamp',CS%TKE_tidal,G%domain,timelevel=1)
call MOM_read_data(TideAmp_file,'tideamp',CS%TKE_tidal,G%domain,timelevel=1, scale=US%m_to_Z*US%T_to_s)
do j=jsd, jed; do i=isd, ied
utide = CS%TKE_tidal(i,j)
CS%TKE_tidal(i,j) = G%mask2dT(i,j)*US%R_to_kg_m3*CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%TKE_tidal(i,j) = G%mask2dT(i,j)*CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%ustar_tidal(i,j) = sqrt(CS%cd_tides)*utide
enddo ; enddo
else
do j=jsd,jed; do i=isd,ied
utide=CS%utide
CS%TKE_tidal(i,j) = US%R_to_kg_m3*CS%Rho0*CS%cd_tides*(utide*utide*utide)
utide = CS%utide
CS%TKE_tidal(i,j) = CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%ustar_tidal(i,j) = sqrt(CS%cd_tides)*utide
enddo ; enddo
endif
Expand Down
20 changes: 10 additions & 10 deletions config_src/nuopc_driver/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -85,14 +85,14 @@ module MOM_surface_forcing_nuopc
!! from an input file.
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL(), & !< turbulent kinetic energy introduced to the
!! bottom boundary layer by drag on the tidal flows [W m-2]
!! bottom boundary layer by drag on the tidal flows [R Z3 T-3 ~> W m-2]
gust => NULL(), & !< spatially varying unresolved background
!! gustiness that contributes to ustar [R L Z T-1 ~> Pa].
!! gust is used when read_gust_2d is true.
ustar_tidal => NULL() !< tidal contribution to the bottom friction velocity [m s-1]
ustar_tidal => NULL() !< tidal contribution to the bottom friction velocity [Z T-1 ~> m s-1]
real :: cd_tides !< drag coefficient that applies to the tides (nondimensional)
real :: utide !< constant tidal velocity to use if read_tideamp
!! is false [m s-1]
!! is false [Z T-1 ~> m s-1]
logical :: read_tideamp !< If true, spatially varying tidal amplitude read from a file.

logical :: rigid_sea_ice !< If true, sea-ice exerts a rigidity that acts
Expand Down Expand Up @@ -306,7 +306,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, &

do j=js-2,je+2 ; do i=is-2,ie+2
fluxes%TKE_tidal(i,j) = CS%TKE_tidal(i,j)
fluxes%ustar_tidal(i,j) = US%m_to_Z*US%T_to_s*CS%ustar_tidal(i,j)
fluxes%ustar_tidal(i,j) = CS%ustar_tidal(i,j)
enddo ; enddo

if (restore_temp) call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)
Expand Down Expand Up @@ -998,7 +998,7 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
!! restoring will be applied in this model.

! Local variables
real :: utide ! The RMS tidal velocity, in m s-1.
real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1].
type(directories) :: dirs
logical :: new_sim, iceberg_flux_diags
type(time_type) :: Time_frc
Expand Down Expand Up @@ -1195,24 +1195,24 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
else
call get_param(param_file, mdl, "UTIDE", CS%utide, &
"The constant tidal amplitude used with INT_TIDE_DISSIPATION.", &
units="m s-1", default=0.0)
units="m s-1", default=0.0, scale=US%m_to_Z*US%T_to_s)
endif

call safe_alloc_ptr(CS%TKE_tidal,isd,ied,jsd,jed)
call safe_alloc_ptr(CS%ustar_tidal,isd,ied,jsd,jed)

if (CS%read_TIDEAMP) then
TideAmp_file = trim(CS%inputdir) // trim(TideAmp_file)
call MOM_read_data(TideAmp_file,'tideamp',CS%TKE_tidal,G%domain,timelevel=1)
call MOM_read_data(TideAmp_file,'tideamp',CS%TKE_tidal,G%domain,timelevel=1, scale=US%m_to_Z*US%T_to_s)
do j=jsd, jed; do i=isd, ied
utide = CS%TKE_tidal(i,j)
CS%TKE_tidal(i,j) = G%mask2dT(i,j)*US%R_to_kg_m3*CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%TKE_tidal(i,j) = G%mask2dT(i,j)*CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%ustar_tidal(i,j) = sqrt(CS%cd_tides)*utide
enddo ; enddo
else
do j=jsd,jed; do i=isd,ied
utide=CS%utide
CS%TKE_tidal(i,j) = US%R_to_kg_m3*CS%Rho0*CS%cd_tides*(utide*utide*utide)
utide = CS%utide
CS%TKE_tidal(i,j) = CS%Rho0*CS%cd_tides*(utide*utide*utide)
CS%ustar_tidal(i,j) = sqrt(CS%cd_tides)*utide
enddo ; enddo
endif
Expand Down
7 changes: 4 additions & 3 deletions src/core/MOM_forcing_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ module MOM_forcing_type

! tide related inputs
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL(), & !< tidal energy source driving mixing in bottom boundary layer [W m-2]
TKE_tidal => NULL(), & !< tidal energy source driving mixing in bottom boundary layer [R Z3 T-3 ~> W m-2]
ustar_tidal => NULL() !< tidal contribution to bottom ustar [Z T-1 ~> m s-1]

! iceberg related inputs
Expand Down Expand Up @@ -1061,7 +1061,8 @@ subroutine MOM_forcing_chksum(mesg, fluxes, G, US, haloshift)
if (associated(fluxes%salt_flux)) &
call hchksum(fluxes%salt_flux, mesg//" fluxes%salt_flux",G%HI,haloshift=hshift)
if (associated(fluxes%TKE_tidal)) &
call hchksum(fluxes%TKE_tidal, mesg//" fluxes%TKE_tidal",G%HI,haloshift=hshift)
call hchksum(fluxes%TKE_tidal, mesg//" fluxes%TKE_tidal",G%HI,haloshift=hshift, &
scale=US%R_to_kg_m3*US%Z_to_m**3*US%s_to_T**3)
if (associated(fluxes%ustar_tidal)) &
call hchksum(fluxes%ustar_tidal, mesg//" fluxes%ustar_tidal",G%HI,haloshift=hshift, scale=US%Z_to_m*US%s_to_T)
if (associated(fluxes%lrunoff)) &
Expand Down Expand Up @@ -1257,7 +1258,7 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
cmor_standard_name='sea_water_pressure_at_sea_water_surface')

handles%id_TKE_tidal = register_diag_field('ocean_model', 'TKE_tidal', diag%axesT1, Time, &
'Tidal source of BBL mixing', 'W m-2')
'Tidal source of BBL mixing', 'W m-2', conversion=US%R_to_kg_m3*US%Z_to_m**3*US%s_to_T**3)

if (.not. use_temperature) then
handles%id_buoy = register_diag_field('ocean_model', 'buoy', diag%axesT1, Time, &
Expand Down
8 changes: 4 additions & 4 deletions src/parameterizations/vertical/MOM_set_diffusivity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1202,7 +1202,7 @@ subroutine add_drag_diffusivity(h, u, v, tv, fluxes, visc, j, TKE_to_Kd, &
visc%TKE_BBL(i,j)

if (associated(fluxes%TKE_tidal)) &
TKE(i) = TKE(i) + (US%kg_m3_to_R * US%T_to_s**3 * US%m_to_Z**3 * fluxes%TKE_tidal(i,j)) * I_Rho0 * &
TKE(i) = TKE(i) + fluxes%TKE_tidal(i,j) * I_Rho0 * &
(CS%BBL_effic * exp(-I2decay(i)*(GV%H_to_Z*h(i,j,nz))))

! Distribute the work over a BBL of depth 20^2 ustar^2 / g' following
Expand Down Expand Up @@ -1418,10 +1418,10 @@ subroutine add_LOTW_BBL_diffusivity(h, u, v, tv, fluxes, visc, j, N2_int, &
! (Note that visc%TKE_BBL is in [Z3 T-3 ~> m3 s-3], set in set_BBL_TKE().)
! I am still unsure about sqrt(cdrag) in this expressions - AJA
TKE_column = cdrag_sqrt * visc%TKE_BBL(i,j)
! Add in tidal dissipation energy at the bottom [m3 s-3].
! Note that TKE_tidal is in [W m-2].
! Add in tidal dissipation energy at the bottom [R Z3 T-3 ~> m3 s-3].
! Note that TKE_tidal is in [R Z3 T-3 ~> W m-2].
if (associated(fluxes%TKE_tidal)) &
TKE_column = TKE_column + US%kg_m3_to_R*US%m_to_Z**3*US%T_to_s**3 * fluxes%TKE_tidal(i,j) * I_Rho0
TKE_column = TKE_column + fluxes%TKE_tidal(i,j) * I_Rho0
TKE_column = CS%BBL_effic * TKE_column ! Only use a fraction of the mechanical dissipation for mixing.

TKE_remaining = TKE_column
Expand Down

0 comments on commit dfd5278

Please sign in to comment.