Skip to content

Commit

Permalink
Fix ALE sponge diagnostics (#188)
Browse files Browse the repository at this point in the history
* Change dumbbell initialization
* Change in Dumbbell Layer Mode
* Fix sponge diagnostics
* Fix ALE Sponge Diagnostics
* A minor style change removing spaces around = in optional. function arguments.
* Fix ALE sponge diagnostics
* character declaration fix
  • Loading branch information
WenhaoChen89 authored Aug 19, 2022
1 parent 1f1b8ad commit a22f691
Show file tree
Hide file tree
Showing 8 changed files with 79 additions and 34 deletions.
12 changes: 8 additions & 4 deletions src/initialization/MOM_state_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2135,9 +2135,11 @@ subroutine initialize_sponges_file(G, GV, US, use_temperature, tv, u, v, depth_t
if (use_temperature) then
allocate(tmp_tr(isd:ied,jsd:jed,nz_data))
call MOM_read_data(filename, potemp_var, tmp_tr(:,:,:), G%Domain, scale=US%degC_to_C)
call set_up_ALE_sponge_field(tmp_tr, G, GV, tv%T, ALE_CSp)
call set_up_ALE_sponge_field(tmp_tr, G, GV, tv%T, ALE_CSp, 'temp', &
sp_long_name='temperature', sp_unit='degC s-1')
call MOM_read_data(filename, salin_var, tmp_tr(:,:,:), G%Domain, scale=US%ppt_to_S)
call set_up_ALE_sponge_field(tmp_tr, G, GV, tv%S, ALE_CSp)
call set_up_ALE_sponge_field(tmp_tr, G, GV, tv%S, ALE_CSp, 'salt', &
sp_long_name='salinity', sp_unit='g kg-1 s-1')
deallocate(tmp_tr)
endif
if (sponge_uv) then
Expand All @@ -2160,8 +2162,10 @@ subroutine initialize_sponges_file(G, GV, US, use_temperature, tv, u, v, depth_t
endif
! The remaining calls to set_up_sponge_field can be in any order.
if ( use_temperature) then
call set_up_ALE_sponge_field(filename, potemp_var, Time, G, GV, US, tv%T, ALE_CSp, scale=US%degC_to_C)
call set_up_ALE_sponge_field(filename, salin_var, Time, G, GV, US, tv%S, ALE_CSp, scale=US%ppt_to_S)
call set_up_ALE_sponge_field(filename, potemp_var, Time, G, GV, US, tv%T, ALE_CSp, &
'temp', sp_long_name='temperature', sp_unit='degC s-1', scale=US%degC_to_C)
call set_up_ALE_sponge_field(filename, salin_var, Time, G, GV, US, tv%S, ALE_CSp, &
'salt', sp_long_name='salinity', sp_unit='g kg-1 s-1', scale=US%ppt_to_S)
endif
if (sponge_uv) then
filename = trim(inputdir)//trim(state_uv_file)
Expand Down
59 changes: 49 additions & 10 deletions src/parameterizations/vertical/MOM_ALE_sponge.F90
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,9 @@ module MOM_ALE_sponge
real :: scale = 1.0 !< A multiplicative factor by which to rescale input data
real, dimension(:,:), pointer :: p => NULL() !< pointer the data.
real, dimension(:,:), pointer :: h => NULL() !< pointer the data grid.
character(len=:), allocatable :: name !< The name of the input field
character(len=:), allocatable :: long_name !< The long name of the input field
character(len=:), allocatable :: unit !< The unit of the input field
end type p2d

!> ALE sponge control structure
Expand Down Expand Up @@ -134,7 +137,7 @@ module MOM_ALE_sponge
logical :: tripolar_N !< grid is folded at its north edge

!>@{ Diagnostic IDs
integer, dimension(2) :: id_sp_tendency !< Diagnostic ids for temperature and salinity
integer, dimension(MAX_FIELDS_) :: id_sp_tendency !< Diagnostic ids for tracers
!! tendency due to sponges
integer :: id_sp_u_tendency !< Diagnostic id for zonal momentum tendency due to
!! Rayleigh damping
Expand Down Expand Up @@ -666,15 +669,19 @@ subroutine init_ALE_sponge_diags(Time, G, diag, CS, US)
!! output.
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
integer :: m

CS%diag => diag

CS%id_sp_tendency(1) = -1
CS%id_sp_tendency(1) = register_diag_field('ocean_model', 'sp_tendency_temp', diag%axesTL, Time, &
'Time tendency due to temperature restoring', 'degC s-1', conversion=US%s_to_T)
CS%id_sp_tendency(2) = -1
CS%id_sp_tendency(2) = register_diag_field('ocean_model', 'sp_tendency_salt', diag%axesTL, Time, &
'Time tendency due to salinity restoring', 'g kg-1 s-1', conversion=US%s_to_T)
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)
enddo

CS%id_sp_u_tendency = -1
CS%id_sp_u_tendency = register_diag_field('ocean_model', 'sp_tendency_u', diag%axesCuL, Time, &
'Zonal acceleration due to sponges', 'm s-2', conversion=US%L_T2_to_m_s2)
Expand All @@ -686,7 +693,8 @@ end subroutine init_ALE_sponge_diags

!> This subroutine stores the reference profile at h points for the variable
!! whose address is given by f_ptr.
subroutine set_up_ALE_sponge_field_fixed(sp_val, G, GV, f_ptr, CS, scale)
subroutine set_up_ALE_sponge_field_fixed(sp_val, G, GV, f_ptr, CS, &
sp_name, sp_long_name, sp_unit, scale)
type(ocean_grid_type), intent(in) :: G !< Grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(ALE_sponge_CS), pointer :: CS !< ALE sponge control structure (in/out).
Expand All @@ -695,16 +703,27 @@ subroutine set_up_ALE_sponge_field_fixed(sp_val, G, GV, f_ptr, CS, scale)
!! arbitrary number of layers.
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
target, intent(in) :: f_ptr !< Pointer to the field to be damped
character(len=*), intent(in) :: sp_name !< The name of the tracer field
character(len=*), optional, &
intent(in) :: sp_long_name !< The long name of the tracer field
!! if not given, use the sp_name
character(len=*), optional, &
intent(in) :: sp_unit !< The unit of the tracer field
!! if not given, use the none
real, optional, intent(in) :: scale !< A factor by which to rescale the input data, including any
!! contributions due to dimensional rescaling. The default is 1.

real :: scale_fac ! A factor by which to scale sp_val before storing it.
integer :: k, col
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

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

CS%fldno = CS%fldno + 1
if (CS%fldno > MAX_FIELDS_) then
Expand All @@ -716,6 +735,9 @@ subroutine set_up_ALE_sponge_field_fixed(sp_val, G, GV, f_ptr, CS, scale)

! stores the reference profile
CS%Ref_val(CS%fldno)%nz_data = CS%nz_data
CS%Ref_val(CS%fldno)%name = sp_name
CS%Ref_val(CS%fldno)%long_name = long_name
CS%Ref_val(CS%fldno)%unit = unit
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 All @@ -729,7 +751,8 @@ end subroutine set_up_ALE_sponge_field_fixed

!> This subroutine stores the reference profile at h points for the variable
!! whose address is given by filename and fieldname.
subroutine set_up_ALE_sponge_field_varying(filename, fieldname, Time, G, GV, US, f_ptr, CS, scale)
subroutine set_up_ALE_sponge_field_varying(filename, fieldname, Time, G, GV, US, f_ptr, CS, &
sp_name, sp_long_name, sp_unit, scale)
character(len=*), intent(in) :: filename !< The name of the file with the
!! time varying field data
character(len=*), intent(in) :: fieldname !< The name of the field in the file
Expand All @@ -741,6 +764,13 @@ subroutine set_up_ALE_sponge_field_varying(filename, fieldname, Time, G, GV, US,
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
target, intent(in) :: f_ptr !< Pointer to the field to be damped (in).
type(ALE_sponge_CS), pointer :: CS !< Sponge control structure (in/out).
character(len=*), intent(in) :: sp_name !< The name of the tracer field
character(len=*), optional, &
intent(in) :: sp_long_name !< The long name of the tracer field
!! if not given, use the sp_name
character(len=*), optional, &
intent(in) :: sp_unit !< The unit of the tracer field
!! if not given, use 'none'
real, optional, intent(in) :: scale !< A factor by which to rescale the input data, including any
!! contributions due to dimensional rescaling. The default is 1.

Expand All @@ -749,6 +779,11 @@ subroutine set_up_ALE_sponge_field_varying(filename, fieldname, Time, G, GV, US,
integer, dimension(4) :: fld_sz
integer :: nz_data !< the number of vertical levels in this input field
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

! Local variables for ALE remapping

if (.not.associated(CS)) return
Expand All @@ -768,6 +803,9 @@ subroutine set_up_ALE_sponge_field_varying(filename, fieldname, Time, G, GV, US,
else
CS%Ref_val(CS%fldno)%id = init_external_field(filename, fieldname)
endif
CS%Ref_val(CS%fldno)%name = sp_name
CS%Ref_val(CS%fldno)%long_name = long_name
CS%Ref_val(CS%fldno)%unit = unit
fld_sz(1:4) = -1
call get_external_field_info(CS%Ref_val(CS%fldno)%id, size=fld_sz)
nz_data = fld_sz(3)
Expand Down Expand Up @@ -1290,7 +1328,8 @@ subroutine rotate_ALE_sponge(sponge_in, G_in, sponge, G, GV, turns, param_file)
call rotate_array(sp_val_in, turns, sp_val)

! NOTE: This points sp_val with the unrotated field. See note below.
call set_up_ALE_sponge_field(sp_val, G, GV, sp_ptr, sponge)
call set_up_ALE_sponge_field(sp_val, G, GV, sp_ptr, sponge, &
sponge_in%Ref_val(n)%name, sp_long_name=sponge_in%Ref_val(n)%long_name, sp_unit=sponge_in%Ref_val(n)%unit)

deallocate(sp_val_in)
else
Expand Down
2 changes: 1 addition & 1 deletion src/tracer/RGC_tracer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -231,7 +231,7 @@ subroutine initialize_RGC_tracer(restart, day, G, GV, h, diag, OBC, CS, &
do m=1,1
! This is needed to force the compiler not to do a copy in the sponge calls.
tr_ptr => CS%tr(:,:,:,m)
call set_up_ALE_sponge_field(temp, G, GV, tr_ptr, sponge_CSp)
call set_up_ALE_sponge_field(temp, G, GV, tr_ptr, sponge_CSp, 'RGC_tracer')
enddo
deallocate(temp)
endif
Expand Down
10 changes: 4 additions & 6 deletions src/user/DOME2d_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -473,12 +473,10 @@ subroutine DOME2d_initialize_sponges(G, GV, US, tv, depth_tot, param_file, use_A
enddo
enddo ; enddo

if ( associated(tv%T) ) then
call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp)
endif
if ( associated(tv%S) ) then
call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp)
endif
if ( associated(tv%T) ) call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp, 'temp', &
sp_long_name='temperature', sp_unit='degC s-1')
if ( associated(tv%S) ) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp, 'salt', &
sp_long_name='salinity', sp_unit='g kg-1 s-1')

else

Expand Down
11 changes: 5 additions & 6 deletions src/user/ISOMIP_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -626,12 +626,11 @@ subroutine ISOMIP_initialize_sponges(G, GV, US, tv, depth_tot, PF, use_ALE, CSp,
! momentum is typically not damped within the sponge. !

! The remaining calls to set_up_sponge_field can be in any order. !
if ( associated(tv%T) ) then
call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp)
endif
if ( associated(tv%S) ) then
call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp)
endif
if ( associated(tv%T) ) call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp, 'temp', &
sp_long_name='temperature', sp_unit='degC s-1')
if ( associated(tv%S) ) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp, 'salt', &
sp_long_name='salinity', sp_unit='g kg-1 s-1')


else ! layer mode
! 1) Read eta, salt and temp from IC file
Expand Down
6 changes: 4 additions & 2 deletions src/user/RGC_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -168,8 +168,10 @@ subroutine RGC_initialize_sponges(G, GV, US, tv, u, v, depth_tot, PF, use_ALE, C
call initialize_ALE_sponge(Idamp, G, GV, PF, ACSp, h, nz)

! The remaining calls to set_up_sponge_field can be in any order.
if ( associated(tv%T) ) call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp)
if ( associated(tv%S) ) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp)
if ( associated(tv%T) ) call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp, 'temp', &
sp_long_name='temperature', sp_unit='degC s-1')
if ( associated(tv%S) ) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp, 'salt', &
sp_long_name='salinity', sp_unit='g kg-1 s-1')

if (sponge_uv) then
U1(:,:,:) = 0.0 ; V1(:,:,:) = 0.0
Expand Down
6 changes: 4 additions & 2 deletions src/user/dense_water_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -279,8 +279,10 @@ subroutine dense_water_initialize_sponges(G, GV, US, tv, depth_tot, param_file,
enddo
enddo

if (associated(tv%T)) call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp)
if (associated(tv%S)) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp)
if ( associated(tv%T) ) call set_up_ALE_sponge_field(T, G, GV, tv%T, ACSp, 'temp', &
sp_long_name='temperature', sp_unit='degC s-1')
if ( associated(tv%S) ) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp, 'salt', &
sp_long_name='salinity', sp_unit='g kg-1 s-1')
else
call MOM_error(FATAL, "dense_water_initialize_sponges: trying to use non ALE sponge")
endif
Expand Down
7 changes: 4 additions & 3 deletions src/user/dumbbell_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -446,12 +446,13 @@ subroutine dumbbell_initialize_sponges(G, GV, US, tv, h_in, depth_tot, param_fil
enddo
endif
enddo ; enddo
if (associated(tv%S)) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp)
if (associated(tv%S)) call set_up_ALE_sponge_field(S, G, GV, tv%S, ACSp, 'salt', &
sp_long_name='salinity', sp_unit='g kg-1 s-1')
else
do j=G%jsc,G%jec ; do i=G%isc,G%iec
eta(i,j,1) = 0.0
do k=2,nz
eta(i,j,k) = eta(i,j,k-1)- GV%H_to_Z * h_in(i,j,k-1)
eta(i,j,k) = eta(i,j,k-1) - GV%H_to_Z * h_in(i,j,k-1)
enddo
eta(i,j,nz+1) = -depth_tot(i,j)
do k=1,nz
Expand All @@ -469,4 +470,4 @@ subroutine dumbbell_initialize_sponges(G, GV, US, tv, h_in, depth_tot, param_fil

end subroutine dumbbell_initialize_sponges

end module dumbbell_initialization
end module dumbbell_initialization

0 comments on commit a22f691

Please sign in to comment.