Skip to content

Commit

Permalink
Fix ALE_sponge tendency diagnostic units
Browse files Browse the repository at this point in the history
  Corrected the units and conversion factor in init_ALE_sponge_diags for the
various sp_tendency_... diagnostics.  Previously they had only been correct for
the tendencies of nondimensional quantities.  The code also now stores the
scaling factor that is set in set_up_ALE_sponge_field_fixed for later use in
registering the sponge tendency diagnostics.  Several instances of unusual
spacing around semicolons in MOM_ALE_sponge were also standardized.  The
documented units and conversion factors for some diagnostics were corrected,
but all solutions are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Dec 30, 2024
1 parent 3c39818 commit 2ffd656
Showing 1 changed file with 30 additions and 22 deletions.
52 changes: 30 additions & 22 deletions src/parameterizations/vertical/MOM_ALE_sponge.F90
Original file line number Diff line number Diff line change
Expand Up @@ -306,7 +306,7 @@ subroutine initialize_ALE_sponge_fixed(Iresttime, G, GV, param_file, CS, data_h,
call pass_var(data_dz, G%Domain, To_All+Omit_Corners, halo=1)

! u points
CS%num_col_u = 0 ;
CS%num_col_u = 0
if (present(Iresttime_u_in)) then
Iresttime_u(:,:) = Iresttime_u_in(:,:)
else
Expand Down Expand Up @@ -350,15 +350,15 @@ subroutine initialize_ALE_sponge_fixed(Iresttime, G, GV, param_file, CS, data_h,
"The total number of columns where sponges are applied at u points.", like_default=.true.)

! v points
CS%num_col_v = 0 ;
CS%num_col_v = 0
if (present(Iresttime_v_in)) then
Iresttime_v(:,:) = Iresttime_v_in(:,:)
else
do J=G%jscB,G%jecB; do i=G%isc,G%iec
do J=G%jscB,G%jecB ; do i=G%isc,G%iec
Iresttime_v(i,J) = 0.5 * (Iresttime(i,j) + Iresttime(i,j+1))
enddo ; enddo
endif
do J=G%jscB,G%jecB; do i=G%isc,G%iec
do J=G%jscB,G%jecB ; do i=G%isc,G%iec
if ((Iresttime_v(i,J) > 0.0) .and. (G%mask2dCv(i,J) > 0.0)) &
CS%num_col_v = CS%num_col_v + 1
enddo ; enddo
Expand Down Expand Up @@ -594,8 +594,8 @@ subroutine initialize_ALE_sponge_varying(Iresttime, G, GV, US, param_file, CS, I
Iresttime_u(I,j) = 0.5 * (Iresttime(i,j) + Iresttime(i+1,j))
enddo ; enddo
endif
CS%num_col_u = 0 ;
do j=G%jsc,G%jec; do I=G%iscB,G%iecB
CS%num_col_u = 0
do j=G%jsc,G%jec ; do I=G%iscB,G%iecB
if ((Iresttime_u(I,j) > 0.0) .and. (G%mask2dCu(I,j) > 0.0)) &
CS%num_col_u = CS%num_col_u + 1
enddo ; enddo
Expand All @@ -622,12 +622,12 @@ subroutine initialize_ALE_sponge_varying(Iresttime, G, GV, US, param_file, CS, I
if (present(Iresttime_v_in)) then
Iresttime_v(:,:) = Iresttime_v_in(:,:)
else
do J=G%jscB,G%jecB; do i=G%isc,G%iec
do J=G%jscB,G%jecB ; do i=G%isc,G%iec
Iresttime_v(i,J) = 0.5 * (Iresttime(i,j) + Iresttime(i,j+1))
enddo ; enddo
endif
CS%num_col_v = 0 ;
do J=G%jscB,G%jecB; do i=G%isc,G%iec
CS%num_col_v = 0
do J=G%jscB,G%jecB ; do i=G%isc,G%iec
if ((Iresttime_v(i,J) > 0.0) .and. (G%mask2dCv(i,J) > 0.0)) &
CS%num_col_v = CS%num_col_v + 1
enddo ; enddo
Expand Down Expand Up @@ -663,16 +663,23 @@ subroutine init_ALE_sponge_diags(Time, G, diag, CS, US)
type(ALE_sponge_CS), intent(inout) :: CS !< ALE sponge control structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
! Local Variables
character(len=:), allocatable :: tend_unit ! The units for a sponge tendency diagnostic.
real :: tend_conv ! The conversion factor use for the sponge tendency [A T-1 ~> a s-1]
integer :: m

CS%diag => diag

do m=1,CS%fldno
CS%id_sp_tendency(m) = -1
CS%id_sp_tendency(m) = register_diag_field('ocean_model', &
'sp_tendency_' // CS%Ref_val(m)%name, diag%axesTL, Time, &
'Time tendency due to restoring ' // CS%Ref_val(m)%long_name, &
CS%Ref_val(m)%unit, conversion=US%s_to_T)
if (trim(CS%Ref_val(m)%unit) == 'none') then
tend_unit = "s-1"
else
tend_unit = trim(CS%Ref_val(m)%unit)//" s-1"
endif
tend_conv = US%s_to_T ; if (CS%Ref_val(m)%scale /= 0.0) tend_conv = US%s_to_T / CS%Ref_val(m)%scale
CS%id_sp_tendency(m) = register_diag_field('ocean_model', 'sp_tendency_'//CS%Ref_val(m)%name, &
diag%axesTL, Time, long_name='Time tendency due to restoring '//CS%Ref_val(m)%long_name, &
units=tend_unit, conversion=tend_conv)
enddo

CS%id_sp_u_tendency = -1
Expand Down Expand Up @@ -716,8 +723,8 @@ subroutine set_up_ALE_sponge_field_fixed(sp_val, G, GV, f_ptr, CS, &
if (.not.associated(CS)) return

scale_fac = 1.0 ; if (present(scale)) scale_fac = scale
long_name = sp_name; if (present(sp_long_name)) long_name = sp_long_name
unit = 'none'; if (present(sp_unit)) unit = sp_unit
long_name = sp_name ; if (present(sp_long_name)) long_name = sp_long_name
unit = 'none' ; if (present(sp_unit)) unit = sp_unit

CS%fldno = CS%fldno + 1
if (CS%fldno > MAX_FIELDS_) then
Expand All @@ -732,6 +739,7 @@ subroutine set_up_ALE_sponge_field_fixed(sp_val, G, GV, f_ptr, CS, &
CS%Ref_val(CS%fldno)%name = sp_name
CS%Ref_val(CS%fldno)%long_name = long_name
CS%Ref_val(CS%fldno)%unit = unit
CS%Ref_val(CS%fldno)%scale = scale_fac
allocate(CS%Ref_val(CS%fldno)%p(CS%nz_data,CS%num_col), source=0.0)
do col=1,CS%num_col
do k=1,CS%nz_data
Expand Down Expand Up @@ -775,15 +783,15 @@ subroutine set_up_ALE_sponge_field_varying(filename, fieldname, Time, G, GV, US,
character(len=256) :: mesg ! String for error messages
character(len=256) :: long_name ! The long name of the tracer field
character(len=256) :: unit ! The unit of the tracer field
long_name = sp_name; if (present(sp_long_name)) long_name = sp_long_name
unit = 'none'; if (present(sp_unit)) unit = sp_unit
long_name = sp_name ; if (present(sp_long_name)) long_name = sp_long_name
unit = 'none' ; if (present(sp_unit)) unit = sp_unit

! Local variables for ALE remapping

if (.not.associated(CS)) return
! initialize time interpolator module
call time_interp_external_init()
isd = G%isd; ied = G%ied; jsd = G%jsd; jed = G%jed
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
CS%fldno = CS%fldno + 1
if (CS%fldno > MAX_FIELDS_) then
write(mesg, '("Increase MAX_FIELDS_ to at least ",I3," in MOM_memory.h or decrease "//&
Expand Down Expand Up @@ -888,8 +896,8 @@ subroutine set_up_ALE_sponge_vel_field_varying(filename_u, fieldname_u, filename

override =.true.

isd = G%isd; ied = G%ied; jsd = G%jsd; jed = G%jed
isdB = G%isdB; iedB = G%iedB; jsdB = G%jsdB; jedB = G%jedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
isdB = G%isdB ; iedB = G%iedB ; jsdB = G%jsdB ; jedB = G%jedB
! get a unique id for this field which will allow us to return an array
! containing time-interpolated values from an external file corresponding
! to the current model date.
Expand Down Expand Up @@ -1081,7 +1089,7 @@ subroutine apply_ALE_sponge(h, tv, dt, G, GV, US, CS, Time)
call pass_var(mask_z, G%Domain, To_All+Omit_Corners, halo=1)

allocate(mask_u(G%isdB:G%iedB,G%jsd:G%jed,1:nz_data))
do j=G%jsc,G%jec; do I=G%iscB,G%iecB
do j=G%jsc,G%jec ; do I=G%iscB,G%iecB
mask_u(I,j,1:nz_data) = min(mask_z(i,j,1:nz_data),mask_z(i+1,j,1:nz_data))
enddo ; enddo

Expand Down Expand Up @@ -1128,7 +1136,7 @@ subroutine apply_ALE_sponge(h, tv, dt, G, GV, US, CS, Time)
call pass_var(mask_z, G%Domain, To_All+Omit_Corners, halo=1)

allocate(mask_v(G%isd:G%ied,G%jsdB:G%jedB,1:nz_data))
do J=G%jscB,G%jecB; do i=G%isc,G%iec
do J=G%jscB,G%jecB ; do i=G%isc,G%iec
mask_v(i,J,1:nz_data) = min(mask_z(i,j,1:nz_data),mask_z(i,j+1,1:nz_data))
enddo ; enddo

Expand Down

0 comments on commit 2ffd656

Please sign in to comment.