Skip to content

Commit

Permalink
Merge branch 'raphaeldussin-mask_checks' into dev/gfdl
Browse files Browse the repository at this point in the history
  • Loading branch information
adcroft committed Aug 28, 2019
2 parents b3a53c7 + d23d1b0 commit adf6665
Showing 1 changed file with 104 additions and 16 deletions.
120 changes: 104 additions & 16 deletions config_src/coupled_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,7 @@ module MOM_surface_forcing
logical :: answers_2018 !< If true, use the order of arithmetic and expressions that recover
!! the answers from the end of 2018. Otherwise, use a simpler
!! expression to calculate gustiness.
logical :: check_no_land_fluxes !< Return warning if IOB flux over land is non-zero

type(diag_ctrl), pointer :: diag => NULL() !< Structure to regulate diagnostic output timing
character(len=200) :: inputdir !< Directory where NetCDF input files are
Expand Down Expand Up @@ -406,41 +407,77 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc
i0 = is - isc_bnd ; j0 = js - jsc_bnd
do j=js,je ; do i=is,ie

if (associated(IOB%lprec)) &
if (associated(IOB%lprec)) then
fluxes%lprec(i,j) = IOB%lprec(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%lprec(i-i0,j-j0), G%mask2dT(i,j), i, j, 'lprec', G)
endif

if (associated(IOB%fprec)) &
if (associated(IOB%fprec)) then
fluxes%fprec(i,j) = IOB%fprec(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%fprec(i-i0,j-j0), G%mask2dT(i,j), i, j, 'fprec', G)
endif

if (associated(IOB%q_flux)) &
if (associated(IOB%q_flux)) then
fluxes%evap(i,j) = - IOB%q_flux(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%q_flux(i-i0,j-j0), G%mask2dT(i,j), i, j, 'q_flux', G)
endif

if (associated(IOB%runoff)) &
if (associated(IOB%runoff)) then
fluxes%lrunoff(i,j) = IOB%runoff(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%runoff(i-i0,j-j0), G%mask2dT(i,j), i, j, 'runoff', G)
endif

if (associated(IOB%calving)) &
if (associated(IOB%calving)) then
fluxes%frunoff(i,j) = IOB%calving(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%calving(i-i0,j-j0), G%mask2dT(i,j), i, j, 'calving', G)
endif

if (associated(IOB%ustar_berg)) &
if (associated(IOB%ustar_berg)) then
fluxes%ustar_berg(i,j) = US%m_to_Z*US%T_to_s * IOB%ustar_berg(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%ustar_berg(i-i0,j-j0), G%mask2dT(i,j), i, j, 'ustar_berg', G)
endif

if (associated(IOB%area_berg)) &
if (associated(IOB%area_berg)) then
fluxes%area_berg(i,j) = IOB%area_berg(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%area_berg(i-i0,j-j0), G%mask2dT(i,j), i, j, 'area_berg', G)
endif

if (associated(IOB%mass_berg)) &
if (associated(IOB%mass_berg)) then
fluxes%mass_berg(i,j) = IOB%mass_berg(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%mass_berg(i-i0,j-j0), G%mask2dT(i,j), i, j, 'mass_berg', G)
endif

if (associated(IOB%runoff_hflx)) &
if (associated(IOB%runoff_hflx)) then
fluxes%heat_content_lrunoff(i,j) = IOB%runoff_hflx(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%runoff_hflx(i-i0,j-j0), G%mask2dT(i,j), i, j, 'runoff_hflx', G)
endif

if (associated(IOB%calving_hflx)) &
if (associated(IOB%calving_hflx)) then
fluxes%heat_content_frunoff(i,j) = IOB%calving_hflx(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%calving_hflx(i-i0,j-j0), G%mask2dT(i,j), i, j, 'calving_hflx', G)
endif

if (associated(IOB%lw_flux)) &
if (associated(IOB%lw_flux)) then
fluxes%LW(i,j) = IOB%lw_flux(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%lw_flux(i-i0,j-j0), G%mask2dT(i,j), i, j, 'lw_flux', G)
endif

if (associated(IOB%t_flux)) &
if (associated(IOB%t_flux)) then
fluxes%sens(i,j) = - IOB%t_flux(i-i0,j-j0) * G%mask2dT(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%t_flux(i-i0,j-j0), G%mask2dT(i,j), i, j, 't_flux', G)
endif

fluxes%latent(i,j) = 0.0
if (associated(IOB%fprec)) then
Expand All @@ -458,14 +495,26 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc

fluxes%latent(i,j) = G%mask2dT(i,j) * fluxes%latent(i,j)

if (associated(IOB%sw_flux_vis_dir)) &
if (associated(IOB%sw_flux_vis_dir)) then
fluxes%sw_vis_dir(i,j) = G%mask2dT(i,j) * IOB%sw_flux_vis_dir(i-i0,j-j0)
if (associated(IOB%sw_flux_vis_dif)) &
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%sw_flux_vis_dir(i-i0,j-j0), G%mask2dT(i,j), i, j, 'sw_flux_vis_dir', G)
endif
if (associated(IOB%sw_flux_vis_dif)) then
fluxes%sw_vis_dif(i,j) = G%mask2dT(i,j) * IOB%sw_flux_vis_dif(i-i0,j-j0)
if (associated(IOB%sw_flux_nir_dir)) &
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%sw_flux_vis_dif(i-i0,j-j0), G%mask2dT(i,j), i, j, 'sw_flux_vis_dif', G)
endif
if (associated(IOB%sw_flux_nir_dir)) then
fluxes%sw_nir_dir(i,j) = G%mask2dT(i,j) * IOB%sw_flux_nir_dir(i-i0,j-j0)
if (associated(IOB%sw_flux_nir_dif)) &
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%sw_flux_nir_dir(i-i0,j-j0), G%mask2dT(i,j), i, j, 'sw_flux_nir_dir', G)
endif
if (associated(IOB%sw_flux_nir_dif)) then
fluxes%sw_nir_dif(i,j) = G%mask2dT(i,j) * IOB%sw_flux_nir_dif(i-i0,j-j0)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%sw_flux_nir_dif(i-i0,j-j0), G%mask2dT(i,j), i, j, 'sw_flux_nir_dif', G)
endif
fluxes%sw(i,j) = fluxes%sw_vis_dir(i,j) + fluxes%sw_vis_dif(i,j) + &
fluxes%sw_nir_dir(i,j) + fluxes%sw_nir_dif(i,j)

Expand All @@ -477,11 +526,15 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc
do j=js,je ; do i=is,ie
fluxes%p_surf_full(i,j) = G%mask2dT(i,j) * IOB%p(i-i0,j-j0)
fluxes%p_surf(i,j) = MIN(fluxes%p_surf_full(i,j),CS%max_p_surf)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%p(i-i0,j-j0), G%mask2dT(i,j), i, j, 'p', G)
enddo ; enddo
else
do j=js,je ; do i=is,ie
fluxes%p_surf_full(i,j) = G%mask2dT(i,j) * IOB%p(i-i0,j-j0)
fluxes%p_surf(i,j) = fluxes%p_surf_full(i,j)
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%p(i-i0,j-j0), G%mask2dT(i,j), i, j, 'p', G)
enddo ; enddo
endif
fluxes%accumulate_p_surf = .true. ! Multiple components may contribute to surface pressure.
Expand All @@ -492,6 +545,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, G, US, CS, sfc
do j=js,je ; do i=is,ie
fluxes%salt_flux(i,j) = G%mask2dT(i,j)*(fluxes%salt_flux(i,j) - IOB%salt_flux(i-i0,j-j0))
fluxes%salt_flux_in(i,j) = G%mask2dT(i,j)*( -IOB%salt_flux(i-i0,j-j0) )
if (CS%check_no_land_fluxes) &
call check_mask_val_consistency(IOB%salt_flux(i-i0,j-j0), G%mask2dT(i,j), i, j, 'salt_flux', G)
enddo ; enddo
endif

Expand Down Expand Up @@ -1446,6 +1501,11 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS)
"If true, allows flux adjustments to specified via the "//&
"data_table using the component name 'OCN'.", default=.false.)

call get_param(param_file, mdl, "CHECK_NO_LAND_FLUXES", CS%check_no_land_fluxes, &
"If true, checks that values from IOB fluxes are zero "//&
"above land points (i.e. G%mask2dT = 0).", default=.false., &
debuggingParam=.true.)

call data_override_init(Ocean_domain_in=G%Domain%mpp_domain)

if (CS%restore_salt) then
Expand Down Expand Up @@ -1551,4 +1611,32 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)

end subroutine ice_ocn_bnd_type_chksum

!> Check the values passed by IOB over land are zero
subroutine check_mask_val_consistency(val, mask, i, j, varname, G)

real, intent(in) :: val !< value of flux/variable passed by IOB
real, intent(in) :: mask !< value of ocean mask
integer, intent(in) :: i, j !< model grid cell indices
character(len=*), intent(in) :: varname !< variable name
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
! Local variables
character(len=48) :: ci, cj !< model local grid cell indices as strings
character(len=48) :: ciglo, cjglo !< model global grid cell indices as strings
character(len=48) :: cval !< value to be displayed
character(len=256) :: error_message !< error message to be displayed

if ((mask == 0.) .and. (val /= 0.)) then
write(ci, '(I8)') i
write(cj, '(I8)') j
write(ciglo, '(I8)') i + G%HI%idg_offset
write(cjglo, '(I8)') j + G%HI%jdg_offset
write(cval, '(E22.16)') val
error_message = "MOM_surface_forcing: found non-zero value (="//trim(cval)//") over land "//&
"for variable "//trim(varname)//" at local point (i, j) = ("//trim(ci)//", "//trim(cj)//&
", global point (iglo, jglo) = ("//trim(ciglo)//", "//trim(cjglo)//")"
call MOM_error(WARNING, error_message)
endif

end subroutine

end module MOM_surface_forcing

0 comments on commit adf6665

Please sign in to comment.