Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into nonBous_barotropic
Browse files Browse the repository at this point in the history
  • Loading branch information
marshallward authored Jul 27, 2023
2 parents e3a9955 + 878fd1e commit 18b25fa
Show file tree
Hide file tree
Showing 32 changed files with 1,103 additions and 315 deletions.
8 changes: 4 additions & 4 deletions .testing/tc3/MOM_input
Original file line number Diff line number Diff line change
Expand Up @@ -283,10 +283,10 @@ HMIX_FIXED = 20.0 ! [m]
KV = 1.0E-04 ! [m2 s-1]
! The background kinematic viscosity in the interior.
! The molecular value, ~1e-6 m2 s-1, may be used.
KVML = 0.01 ! [m2 s-1] default = 1.0E-04
! The kinematic viscosity in the mixed layer. A typical
! value is ~1e-2 m2 s-1. KVML is not used if
! BULKMIXEDLAYER is true. The default is set by KV.
KV_ML_INVZ2 = 0.01 ! [m2 s-1] default = 0.0
! An extra kinematic viscosity in a mixed layer of thickness HMIX_FIXED, with
! the actual viscosity scaling as 1/(z*HMIX_FIXED)^2, where z is the distance
! from the surface, to allow for finite wind stresses to be transmitted through.
HBBL = 10.0 ! [m]
! The thickness of a bottom boundary layer with a
! viscosity of KVBBL if BOTTOMDRAGLAW is not defined, or
Expand Down
13 changes: 12 additions & 1 deletion config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ module MOM_surface_forcing_gfdl
!! from MOM_domains) to indicate the staggering of
!! the winds that are being provided in calls to
!! update_ocean_model.
logical :: use_temperature !< If true, temp and saln used as state variables
logical :: use_temperature !< If true, temp and saln used as state variables.
real :: wind_stress_multiplier !< A multiplier applied to incoming wind stress [nondim].

real :: Rho0 !< Boussinesq reference density [R ~> kg m-3]
Expand Down Expand Up @@ -175,6 +175,7 @@ module MOM_surface_forcing_gfdl
real, pointer, dimension(:,:) :: t_flux =>NULL() !< sensible heat flux [W m-2]
real, pointer, dimension(:,:) :: q_flux =>NULL() !< specific humidity flux [kg m-2 s-1]
real, pointer, dimension(:,:) :: salt_flux =>NULL() !< salt flux [kg m-2 s-1]
real, pointer, dimension(:,:) :: excess_salt =>NULL() !< salt left behind by brine rejection [kg m-2 s-1]
real, pointer, dimension(:,:) :: lw_flux =>NULL() !< long wave radiation [W m-2]
real, pointer, dimension(:,:) :: sw_flux_vis_dir =>NULL() !< direct visible sw radiation [W m-2]
real, pointer, dimension(:,:) :: sw_flux_vis_dif =>NULL() !< diffuse visible sw radiation [W m-2]
Expand Down Expand Up @@ -304,6 +305,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)
call safe_alloc_ptr(fluxes%salt_flux_added,isd,ied,jsd,jed)

if (associated(IOB%excess_salt)) call safe_alloc_ptr(fluxes%salt_left_behind,isd,ied,jsd,jed)

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) = CS%ustar_tidal(i,j)
Expand Down Expand Up @@ -576,6 +579,11 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
call check_mask_val_consistency(IOB%salt_flux(i-i0,j-j0), G%mask2dT(i,j), i, j, 'salt_flux', G)
enddo ; enddo
endif
if (associated(IOB%excess_salt)) then
do j=js,je ; do i=is,ie
fluxes%salt_left_behind(i,j) = G%mask2dT(i,j)*(kg_m2_s_conversion*IOB%excess_salt(i-i0,j-j0))
enddo ; enddo
endif

!#CTRL# if (associated(CS%ctrl_forcing_CSp)) then
!#CTRL# do j=js,je ; do i=is,ie
Expand Down Expand Up @@ -1729,6 +1737,9 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
if (associated(iobt%mass_berg)) then
chks = field_chksum( iobt%mass_berg ) ; if (root) write(outunit,100) 'iobt%mass_berg ', chks
endif
if (associated(iobt%excess_salt)) then
chks = field_chksum( iobt%excess_salt ) ; if (root) write(outunit,100) 'iobt%excess_salt ', chks
endif
100 FORMAT(" CHECKSUM::",A20," = ",Z20)

call coupler_type_write_chksums(iobt%fluxes, outunit, 'iobt%')
Expand Down
44 changes: 31 additions & 13 deletions config_src/external/drifters/MOM_particles.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,28 +11,29 @@ module MOM_particles_mod
implicit none ; private

public particles, particles_run, particles_init, particles_save_restart, particles_end
public particles_to_k_space, particles_to_z_space

contains

!> Initializes particles container "parts"
subroutine particles_init(parts, Grid, Time, dt, u, v)
subroutine particles_init(parts, Grid, Time, dt, u, v, h)
! Arguments
type(particles), pointer, intent(out) :: parts !< Container for all types and memory
type(ocean_grid_type), target, intent(in) :: Grid !< Grid type from parent model
type(time_type), intent(in) :: Time !< Time type from parent model
real, intent(in) :: dt !< particle timestep [s]
real, dimension(:,:,:), intent(in) :: u !< Zonal velocity field [m s-1]
real, dimension(:,:,:), intent(in) :: v !< Meridional velocity field [m s-1]

real, intent(in) :: dt !< particle timestep in seconds [T ~> s]
real, dimension(:,:,:),intent(in) :: u !< Zonal velocity field [L T-1 ~> m s-1]
real, dimension(:,:,:),intent(in) :: v !< Meridional velocity field [L T-1 ~> m s-1]
real, dimension(:,:,:),intent(in) :: h !< Thickness of each layer [H ~> m or kg m-2]
end subroutine particles_init

!> The main driver the steps updates particles
subroutine particles_run(parts, time, uo, vo, ho, tv, stagger)
! Arguments
type(particles), pointer :: parts !< Container for all types and memory
type(time_type), intent(in) :: time !< Model time
real, dimension(:,:,:), intent(in) :: uo !< Ocean zonal velocity [m s-1]
real, dimension(:,:,:), intent(in) :: vo !< Ocean meridional velocity [m s-1]
real, dimension(:,:,:), intent(in) :: uo !< Ocean zonal velocity [L T-1 ~>m s-1]
real, dimension(:,:,:), intent(in) :: vo !< Ocean meridional velocity [L T-1~> m s-1]
real, dimension(:,:,:), intent(in) :: ho !< Ocean layer thickness [H ~> m or kg m-2]
type(thermo_var_ptrs), intent(in) :: tv !< structure containing pointers to available thermodynamic fields
integer, optional, intent(in) :: stagger !< Flag for whether velocities are staggered
Expand All @@ -41,21 +42,38 @@ end subroutine particles_run


!>Save particle locations (and sometimes other vars) to restart file
subroutine particles_save_restart(parts, temp, salt)
subroutine particles_save_restart(parts, h, temp, salt)
! Arguments
type(particles), pointer :: parts !< Container for all types and memory
real, dimension(:,:,:), optional, intent(in) :: temp !< Optional container for temperature
real, dimension(:,:,:), optional, intent(in) :: salt !< Optional container for salinity
real, dimension(:,:,:),intent(in) :: h !< Thickness of each layer [H ~> m or kg m-2]
real, dimension(:,:,:), optional, intent(in) :: temp !< Optional container for temperature [C ~> degC]
real, dimension(:,:,:), optional, intent(in) :: salt !< Optional container for salinity [S ~> ppt]

end subroutine particles_save_restart

!> Deallocate all memory and disassociated pointer
subroutine particles_end(parts, temp, salt)
subroutine particles_end(parts, h, temp, salt)
! Arguments
type(particles), pointer :: parts !< Container for all types and memory
real, dimension(:,:,:), optional, intent(in) :: temp !< Optional container for temperature
real, dimension(:,:,:), optional, intent(in) :: salt !< Optional container for salinity
real, dimension(:,:,:),intent(in) :: h !< Thickness of each layer [H ~> m or kg m-2]
real, dimension(:,:,:), optional, intent(in) :: temp !< Optional container for temperature [C ~> degC]
real, dimension(:,:,:), optional, intent(in) :: salt !< Optional container for salinity [S ~> ppt]

end subroutine particles_end

subroutine particles_to_k_space(parts, h)
! Arguments
type(particles), pointer :: parts !< Container for all types and memory
real, dimension(:,:,:),intent(in) :: h !< Thickness of layers [H ~> m or kg m-2]

end subroutine particles_to_k_space


subroutine particles_to_z_space(parts, h)
! Arguments
type(particles), pointer :: parts !< Container for all types and memory
real, dimension(:,:,:),intent(in) :: h !< Thickness of layers [H ~> m or kg m-2]

end subroutine particles_to_z_space

end module MOM_particles_mod
24 changes: 23 additions & 1 deletion config_src/infra/FMS1/MOM_coms_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module MOM_coms_infra
!> Communicate an array, string or scalar from one PE to others
interface broadcast
module procedure broadcast_char, broadcast_int32_0D, broadcast_int64_0D, broadcast_int1D
module procedure broadcast_real0D, broadcast_real1D, broadcast_real2D
module procedure broadcast_real0D, broadcast_real1D, broadcast_real2D, broadcast_real3D
end interface broadcast

!> Compute a checksum for a field distributed over a PE list. If no PE list is
Expand Down Expand Up @@ -260,6 +260,28 @@ subroutine broadcast_real2D(dat, length, from_PE, PElist, blocking)

end subroutine broadcast_real2D


!> Communicate a 3-D array of reals from one PE to others
subroutine broadcast_real3D(dat, length, from_PE, PElist, blocking)
real, dimension(:,:,:), intent(inout) :: dat !< The data to communicate and destination
integer, intent(in) :: length !< The total number of data elements
integer, optional, intent(in) :: from_PE !< The source PE, by default the root PE
integer, optional, intent(in) :: PElist(:) !< The list of participating PEs, by default the
!! active PE set as previously set via Set_PElist.
logical, optional, intent(in) :: blocking !< If true, barriers are added around the call

integer :: src_PE ! The processor that is sending the data
logical :: do_block ! If true add synchronizing barriers

do_block = .false. ; if (present(blocking)) do_block = blocking
if (present(from_PE)) then ; src_PE = from_PE ; else ; src_PE = root_PE() ; endif

if (do_block) call mpp_sync(PElist)
call mpp_broadcast(dat, length, src_PE, PElist)
if (do_block) call mpp_sync_self(PElist)

end subroutine broadcast_real3D

! field_chksum wrappers

!> Compute a checksum for a field distributed over a PE list. If no PE list is
Expand Down
41 changes: 40 additions & 1 deletion config_src/infra/FMS1/MOM_io_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ module MOM_io_infra
!> Read a data field from a file
interface read_field
module procedure read_field_4d
module procedure read_field_3d
module procedure read_field_3d, read_field_3d_region
module procedure read_field_2d, read_field_2d_region
module procedure read_field_1d, read_field_1d_int
module procedure read_field_0d, read_field_0d_int
Expand Down Expand Up @@ -696,6 +696,45 @@ subroutine read_field_3d(filename, fieldname, data, MOM_Domain, &
endif ; endif
end subroutine read_field_3d

!> This routine uses the fms_io subroutine read_data to read a region from a distributed or
!! global 3-D data field named "fieldname" from file "filename".
subroutine read_field_3d_region(filename, fieldname, data, start, nread, MOM_domain, &
no_domain, scale)
character(len=*), intent(in) :: filename !< The name of the file to read
character(len=*), intent(in) :: fieldname !< The variable name of the data in the file
real, dimension(:,:,:), intent(inout) :: data !< The 3-dimensional array into which the data
!! should be read
integer, dimension(:), intent(in) :: start !< The starting index to read in each of 4
!! dimensions. For this 3-d read, the
!! 4th values are always 1.
integer, dimension(:), intent(in) :: nread !< The number of points to read in each of 4
!! dimensions. For this 3-d read, the
!! 4th values are always 1.
type(MOM_domain_type), &
optional, intent(in) :: MOM_Domain !< The MOM_Domain that describes the decomposition
logical, optional, intent(in) :: no_domain !< If present and true, this variable does not
!! use domain decomposion.
real, optional, intent(in) :: scale !< A scaling factor that the field is multiplied
!! by before it is returned.

if (present(MOM_Domain)) then
call read_data(filename, fieldname, data, start, nread, domain=MOM_Domain%mpp_domain, &
no_domain=no_domain)
else
call read_data(filename, fieldname, data, start, nread, no_domain=no_domain)
endif

if (present(scale)) then ; if (scale /= 1.0) then
if (present(MOM_Domain)) then
call rescale_comp_data(MOM_Domain, data, scale)
else
! Dangerously rescale the whole array
data(:,:,:) = scale*data(:,:,:)
endif
endif ; endif
end subroutine read_field_3d_region


!> This routine uses the fms_io subroutine read_data to read a distributed
!! 4-D data field named "fieldname" from file "filename". Valid values for
!! "position" include CORNER, CENTER, EAST_FACE and NORTH_FACE.
Expand Down
23 changes: 22 additions & 1 deletion config_src/infra/FMS2/MOM_coms_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module MOM_coms_infra
!> Communicate an array, string or scalar from one PE to others
interface broadcast
module procedure broadcast_char, broadcast_int32_0D, broadcast_int64_0D, broadcast_int1D
module procedure broadcast_real0D, broadcast_real1D, broadcast_real2D
module procedure broadcast_real0D, broadcast_real1D, broadcast_real2D, broadcast_real3D
end interface broadcast

!> Compute a checksum for a field distributed over a PE list. If no PE list is
Expand Down Expand Up @@ -260,6 +260,27 @@ subroutine broadcast_real2D(dat, length, from_PE, PElist, blocking)

end subroutine broadcast_real2D

!> Communicate a 3-D array of reals from one PE to others
subroutine broadcast_real3D(dat, length, from_PE, PElist, blocking)
real, dimension(:,:,:), intent(inout) :: dat !< The data to communicate and destination
integer, intent(in) :: length !< The total number of data elements
integer, optional, intent(in) :: from_PE !< The source PE, by default the root PE
integer, optional, intent(in) :: PElist(:) !< The list of participating PEs, by default the
!! active PE set as previously set via Set_PElist.
logical, optional, intent(in) :: blocking !< If true, barriers are added around the call

integer :: src_PE ! The processor that is sending the data
logical :: do_block ! If true add synchronizing barriers

do_block = .false. ; if (present(blocking)) do_block = blocking
if (present(from_PE)) then ; src_PE = from_PE ; else ; src_PE = root_PE() ; endif

if (do_block) call mpp_sync(PElist)
call mpp_broadcast(dat, length, src_PE, PElist)
if (do_block) call mpp_sync_self(PElist)

end subroutine broadcast_real3D

! field_chksum wrappers

!> Compute a checksum for a field distributed over a PE list. If no PE list is
Expand Down
70 changes: 69 additions & 1 deletion config_src/infra/FMS2/MOM_io_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ module MOM_io_infra
!> Read a data field from a file
interface read_field
module procedure read_field_4d
module procedure read_field_3d
module procedure read_field_3d, read_field_3d_region
module procedure read_field_2d, read_field_2d_region
module procedure read_field_1d, read_field_1d_int
module procedure read_field_0d, read_field_0d_int
Expand Down Expand Up @@ -1030,6 +1030,74 @@ subroutine read_field_3d(filename, fieldname, data, MOM_Domain, &

end subroutine read_field_3d

!> This routine uses the fms_io subroutine read_data to read a region from a distributed or
!! global 3-D data field named "fieldname" from file "filename".
subroutine read_field_3d_region(filename, fieldname, data, start, nread, MOM_domain, &
no_domain, scale)
character(len=*), intent(in) :: filename !< The name of the file to read
character(len=*), intent(in) :: fieldname !< The variable name of the data in the file
real, dimension(:,:,:), intent(inout) :: data !< The 3-dimensional array into which the data
!! should be read
integer, dimension(:), intent(in) :: start !< The starting index to read in each of 3
!! dimensions. For this 3-d read, the
!! 4th value is always 1.
integer, dimension(:), intent(in) :: nread !< The number of points to read in each of 4
!! dimensions. For this 3-d read, the
!! 4th values are always 1.
type(MOM_domain_type), &
optional, intent(in) :: MOM_Domain !< The MOM_Domain that describes the decomposition
logical, optional, intent(in) :: no_domain !< If present and true, this variable does not
!! use domain decomposion.
real, optional, intent(in) :: scale !< A scaling factor that the field is multiplied
!! by before it is returned.

! Local variables
type(FmsNetcdfFile_t) :: fileObj ! A handle to a non-domain-decomposed file
type(FmsNetcdfDomainFile_t) :: fileobj_DD ! A handle to a domain-decomposed file object
character(len=96) :: var_to_read ! Name of variable to read from the netcdf file
logical :: success ! True if the file was successfully opened

if (present(MOM_Domain)) then
! Open the FMS2 file-set.
success = fms2_open_file(fileobj_DD, filename, "read", MOM_domain%mpp_domain)
if (.not.success) call MOM_error(FATAL, "Failed to open "//trim(filename))

! Find the matching case-insensitive variable name in the file and prepare to read it.
call prepare_to_read_var(fileobj_DD, fieldname, "read_field_2d_region: ", &
filename, var_to_read)

! Read the data.
call fms2_read_data(fileobj_DD, var_to_read, data, corner=start(1:3), edge_lengths=nread(1:3))

! Close the file-set.
if (check_if_open(fileobj_DD)) call fms2_close_file(fileobj_DD)
else
! Open the FMS2 file-set.
success = fms2_open_file(fileObj, trim(filename), "read")
if (.not.success) call MOM_error(FATAL, "Failed to open "//trim(filename))

! Find the matching case-insensitive variable name in the file, and determine whether it
! has a time dimension.
call find_varname_in_file(fileObj, fieldname, "read_field_2d_region: ", filename, var_to_read)

! Read the data.
call fms2_read_data(fileobj, var_to_read, data, corner=start(1:3), edge_lengths=nread(1:3))

! Close the file-set.
if (check_if_open(fileobj)) call fms2_close_file(fileobj)
endif

if (present(scale)) then ; if (scale /= 1.0) then
if (present(MOM_Domain)) then
call rescale_comp_data(MOM_Domain, data, scale)
else
! Dangerously rescale the whole array
data(:,:,:) = scale*data(:,:,:)
endif
endif ; endif

end subroutine read_field_3d_region

!> This routine uses the fms_io subroutine read_data to read a distributed
!! 4-D data field named "fieldname" from file "filename". Valid values for
!! "position" include CORNER, CENTER, EAST_FACE and NORTH_FACE.
Expand Down
9 changes: 9 additions & 0 deletions docs/zotero.bib
Original file line number Diff line number Diff line change
Expand Up @@ -2738,3 +2738,12 @@ @article{kraus1967
journal = {Tellus}
}

@article{Nguyen2009,
doi = {10.1029/2008JC005121},
year = {2009},
journal = {JGR Oceans},
volume = {114},
author = {A. T. Nguyen and D. Menemenlis and R. Kwok},
title = {Improved modeling of the Arctic halocline with a subgrid-scale brine rejection parameterization},
pages = {C11014}
}
Loading

0 comments on commit 18b25fa

Please sign in to comment.