Skip to content

Commit

Permalink
Standardized syntax in mask2d logical tests
Browse files Browse the repository at this point in the history
  Modified the syntax of the logical comparisons with the various mask2d
variables to always check whether they are larger than 0.0, not 0.5 and use
similar syntax throughout the MOM6 code.  Because these arrays are always either
0.0 or 1.0, the answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA authored and marshallward committed Apr 11, 2022
1 parent 7f6dac2 commit e9fdf5d
Show file tree
Hide file tree
Showing 28 changed files with 143 additions and 145 deletions.
22 changes: 11 additions & 11 deletions config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -374,7 +374,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%salt_flux_added(is:ie,js:je) = fluxes%salt_flux(is:ie,js:je) ! Diagnostic
else
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0.5) then
if (G%mask2dT(i,j) > 0.0) then
delta_sss = sfc_state%SSS(i,j) - data_restore(i,j)
delta_sss = sign(1.0,delta_sss)*min(abs(delta_sss),CS%max_delta_srestore)
fluxes%vprec(i,j) = (CS%basin_mask(i,j)*open_ocn_mask(i,j)*CS%srestore_mask(i,j))* &
Expand Down Expand Up @@ -956,13 +956,13 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
if (present(taux).and.present(tauy)) then
do j=jsh,jeh ; do I=Isqh,Ieqh
taux(I,j) = 0.0
if ((G%mask2dBu(I,J) + G%mask2dBu(I,J-1)) > 0) &
if ((G%mask2dBu(I,J) + G%mask2dBu(I,J-1)) > 0.0) &
taux(I,j) = (G%mask2dBu(I,J)*taux_in_B(I,J) + G%mask2dBu(I,J-1)*taux_in_B(I,J-1)) / &
(G%mask2dBu(I,J) + G%mask2dBu(I,J-1))
enddo ; enddo
do J=Jsqh,Jeqh ; do i=ish,ieh
tauy(i,J) = 0.0
if ((G%mask2dBu(I,J) + G%mask2dBu(I-1,J)) > 0) &
if ((G%mask2dBu(I,J) + G%mask2dBu(I-1,J)) > 0.0) &
tauy(i,J) = (G%mask2dBu(I,J)*tauy_in_B(I,J) + G%mask2dBu(I-1,J)*tauy_in_B(I-1,J)) / &
(G%mask2dBu(I,J) + G%mask2dBu(I-1,J))
enddo ; enddo
Expand All @@ -984,14 +984,14 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,

if (present(taux)) then ; do j=jsh,jeh ; do I=Isqh,Ieqh
taux(I,j) = 0.0
if ((G%mask2dT(i,j) + G%mask2dT(i+1,j)) > 0) &
if ((G%mask2dT(i,j) + G%mask2dT(i+1,j)) > 0.0) &
taux(I,j) = (G%mask2dT(i,j)*taux_in_A(i,j) + G%mask2dT(i+1,j)*taux_in_A(i+1,j)) / &
(G%mask2dT(i,j) + G%mask2dT(i+1,j))
enddo ; enddo ; endif

if (present(tauy)) then ; do J=Jsqh,Jeqh ; do i=ish,ieh
tauy(i,J) = 0.0
if ((G%mask2dT(i,j) + G%mask2dT(i,j+1)) > 0) &
if ((G%mask2dT(i,j) + G%mask2dT(i,j+1)) > 0.0) &
tauy(i,J) = (G%mask2dT(i,j)*tauy_in_A(i,j) + G%mask2dT(i,J+1)*tauy_in_A(i,j+1)) / &
(G%mask2dT(i,j) + G%mask2dT(i,j+1))
enddo ; enddo ; endif
Expand Down Expand Up @@ -1029,10 +1029,10 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
gustiness = CS%gust_const
if (CS%read_gust_2d) then
if ((wind_stagger == CGRID_NE) .or. &
((wind_stagger == AGRID) .and. (G%mask2dT(i,j) > 0)) .or. &
((wind_stagger == AGRID) .and. (G%mask2dT(i,j) > 0.0)) .or. &
((wind_stagger == BGRID_NE) .and. &
(((G%mask2dBu(I,J) + G%mask2dBu(I-1,J-1)) + &
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0)) ) &
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0.0)) ) &
gustiness = CS%gust(i,j)
endif
ustar(i,j) = sqrt(gustiness*IRho0 + IRho0*Pa_conversion*IOB%stress_mag(i-i0,j-j0))
Expand All @@ -1050,7 +1050,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
do j=js,je ; do i=is,ie
tau_mag = 0.0 ; gustiness = CS%gust_const
if (((G%mask2dBu(I,J) + G%mask2dBu(I-1,J-1)) + &
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0) then
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0.0) then
tau_mag = sqrt(((G%mask2dBu(I,J)*(taux_in_B(I,J)**2 + tauy_in_B(I,J)**2) + &
G%mask2dBu(I-1,J-1)*(taux_in_B(I-1,J-1)**2 + tauy_in_B(I-1,J-1)**2)) + &
(G%mask2dBu(I,J-1)*(taux_in_B(I,J-1)**2 + tauy_in_B(I,J-1)**2) + &
Expand All @@ -1069,7 +1069,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
do j=js,je ; do i=is,ie
tau_mag = G%mask2dT(i,j) * sqrt(taux_in_A(i,j)**2 + tauy_in_A(i,j)**2)
gustiness = CS%gust_const
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0)) gustiness = CS%gust(i,j)
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0.0)) gustiness = CS%gust(i,j)
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
if (CS%answers_2018) then
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
Expand All @@ -1080,10 +1080,10 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
else ! C-grid wind stresses.
do j=js,je ; do i=is,ie
taux2 = 0.0 ; tauy2 = 0.0
if ((G%mask2dCu(I-1,j) + G%mask2dCu(I,j)) > 0) &
if ((G%mask2dCu(I-1,j) + G%mask2dCu(I,j)) > 0.0) &
taux2 = (G%mask2dCu(I-1,j)*taux_in_C(I-1,j)**2 + G%mask2dCu(I,j)*taux_in_C(I,j)**2) / &
(G%mask2dCu(I-1,j) + G%mask2dCu(I,j))
if ((G%mask2dCv(i,J-1) + G%mask2dCv(i,J)) > 0) &
if ((G%mask2dCv(i,J-1) + G%mask2dCv(i,J)) > 0.0) &
tauy2 = (G%mask2dCv(i,J-1)*tauy_in_C(i,J-1)**2 + G%mask2dCv(i,J)*tauy_in_C(i,J)**2) / &
(G%mask2dCv(i,J-1) + G%mask2dCv(i,J))
tau_mag = sqrt(taux2 + tauy2)
Expand Down
18 changes: 9 additions & 9 deletions config_src/drivers/mct_cap/mom_surface_forcing_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -385,7 +385,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%salt_flux_added(is:ie,js:je) = fluxes%salt_flux(is:ie,js:je) ! Diagnostic
else
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0.5) then
if (G%mask2dT(i,j) > 0.0) then
delta_sss = sfc_state%SSS(i,j) - data_restore(i,j)
delta_sss = sign(1.0,delta_sss)*min(abs(delta_sss),CS%max_delta_srestore)
fluxes%vprec(i,j) = (CS%basin_mask(i,j)*open_ocn_mask(i,j)*CS%srestore_mask(i,j))* &
Expand Down Expand Up @@ -749,15 +749,15 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)

do j=js,je ; do I=Isq,Ieq
forces%taux(I,j) = 0.0
if ((G%mask2dBu(I,J) + G%mask2dBu(I,J-1)) > 0) &
if ((G%mask2dBu(I,J) + G%mask2dBu(I,J-1)) > 0.0) &
forces%taux(I,j) = (G%mask2dBu(I,J)*taux_at_q(I,J) + &
G%mask2dBu(I,J-1)*taux_at_q(I,J-1)) / &
(G%mask2dBu(I,J) + G%mask2dBu(I,J-1))
enddo; enddo

do J=Jsq,Jeq ; do i=is,ie
forces%tauy(i,J) = 0.0
if ((G%mask2dBu(I,J) + G%mask2dBu(I-1,J)) > 0) &
if ((G%mask2dBu(I,J) + G%mask2dBu(I-1,J)) > 0.0) &
forces%tauy(i,J) = (G%mask2dBu(I,J)*tauy_at_q(I,J) + &
G%mask2dBu(I-1,J)*tauy_at_q(I-1,J)) / &
(G%mask2dBu(I,J) + G%mask2dBu(I-1,J))
Expand All @@ -770,7 +770,7 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)
do j=js,je ; do i=is,ie
tau_mag = 0.0 ; gustiness = CS%gust_const
if (((G%mask2dBu(I,J) + G%mask2dBu(I-1,J-1)) + &
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0) then
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0.0) then
tau_mag = sqrt(((G%mask2dBu(I,J)*(taux_at_q(I,J)**2 + tauy_at_q(I,J)**2) + &
G%mask2dBu(I-1,J-1)*(taux_at_q(I-1,J-1)**2 + tauy_at_q(I-1,J-1)**2)) + &
(G%mask2dBu(I,J-1)*(taux_at_q(I,J-1)**2 + tauy_at_q(I,J-1)**2) + &
Expand All @@ -786,23 +786,23 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)

do j=js,je ; do I=Isq,Ieq
forces%taux(I,j) = 0.0
if ((G%mask2dT(i,j) + G%mask2dT(i+1,j)) > 0) &
if ((G%mask2dT(i,j) + G%mask2dT(i+1,j)) > 0.0) &
forces%taux(I,j) = (G%mask2dT(i,j)*taux_at_h(i,j) + &
G%mask2dT(i+1,j)*taux_at_h(i+1,j)) / &
(G%mask2dT(i,j) + G%mask2dT(i+1,j))
enddo; enddo

do J=Jsq,Jeq ; do i=is,ie
forces%tauy(i,J) = 0.0
if ((G%mask2dT(i,j) + G%mask2dT(i,j+1)) > 0) &
if ((G%mask2dT(i,j) + G%mask2dT(i,j+1)) > 0.0) &
forces%tauy(i,J) = (G%mask2dT(i,j)*tauy_at_h(i,j) + &
G%mask2dT(i,J+1)*tauy_at_h(i,j+1)) / &
(G%mask2dT(i,j) + G%mask2dT(i,j+1))
enddo; enddo

do j=js,je ; do i=is,ie
gustiness = CS%gust_const
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0)) gustiness = CS%gust(i,j)
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0.0)) gustiness = CS%gust(i,j)
forces%ustar(i,j) = sqrt(gustiness*Irho0 + Irho0 * G%mask2dT(i,j) * &
sqrt(taux_at_h(i,j)**2 + tauy_at_h(i,j)**2))
enddo; enddo
Expand All @@ -814,12 +814,12 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)

do j=js,je ; do i=is,ie
taux2 = 0.0
if ((G%mask2dCu(I-1,j) + G%mask2dCu(I,j)) > 0) &
if ((G%mask2dCu(I-1,j) + G%mask2dCu(I,j)) > 0.0) &
taux2 = (G%mask2dCu(I-1,j)*forces%taux(I-1,j)**2 + &
G%mask2dCu(I,j)*forces%taux(I,j)**2) / (G%mask2dCu(I-1,j) + G%mask2dCu(I,j))

tauy2 = 0.0
if ((G%mask2dCv(i,J-1) + G%mask2dCv(i,J)) > 0) &
if ((G%mask2dCv(i,J-1) + G%mask2dCv(i,J)) > 0.0) &
tauy2 = (G%mask2dCv(i,J-1)*forces%tauy(i,J-1)**2 + &
G%mask2dCv(i,J)*forces%tauy(i,J)**2) / (G%mask2dCv(i,J-1) + G%mask2dCv(i,J))

Expand Down
18 changes: 9 additions & 9 deletions config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -410,7 +410,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%salt_flux_added(is:ie,js:je) = fluxes%salt_flux(is:ie,js:je) ! Diagnostic
else
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0.5) then
if (G%mask2dT(i,j) > 0.0) then
delta_sss = sfc_state%SSS(i,j) - data_restore(i,j)
delta_sss = sign(1.0,delta_sss)*min(abs(delta_sss),CS%max_delta_srestore)
fluxes%vprec(i,j) = (CS%basin_mask(i,j)*open_ocn_mask(i,j)*CS%srestore_mask(i,j))* &
Expand Down Expand Up @@ -806,15 +806,15 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)

do j=js,je ; do I=Isq,Ieq
forces%taux(I,j) = 0.0
if ((G%mask2dBu(I,J) + G%mask2dBu(I,J-1)) > 0) &
if ((G%mask2dBu(I,J) + G%mask2dBu(I,J-1)) > 0.0) &
forces%taux(I,j) = (G%mask2dBu(I,J)*taux_at_q(I,J) + &
G%mask2dBu(I,J-1)*taux_at_q(I,J-1)) / &
(G%mask2dBu(I,J) + G%mask2dBu(I,J-1))
enddo ; enddo

do J=Jsq,Jeq ; do i=is,ie
forces%tauy(i,J) = 0.0
if ((G%mask2dBu(I,J) + G%mask2dBu(I-1,J)) > 0) &
if ((G%mask2dBu(I,J) + G%mask2dBu(I-1,J)) > 0.0) &
forces%tauy(i,J) = (G%mask2dBu(I,J)*tauy_at_q(I,J) + &
G%mask2dBu(I-1,J)*tauy_at_q(I-1,J)) / &
(G%mask2dBu(I,J) + G%mask2dBu(I-1,J))
Expand All @@ -827,7 +827,7 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)
do j=js,je ; do i=is,ie
tau_mag = 0.0 ; gustiness = CS%gust_const
if (((G%mask2dBu(I,J) + G%mask2dBu(I-1,J-1)) + &
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0) then
(G%mask2dBu(I,J-1) + G%mask2dBu(I-1,J))) > 0.0) then
tau_mag = sqrt(((G%mask2dBu(I,J)*(taux_at_q(I,J)**2 + tauy_at_q(I,J)**2) + &
G%mask2dBu(I-1,J-1)*(taux_at_q(I-1,J-1)**2 + tauy_at_q(I-1,J-1)**2)) + &
(G%mask2dBu(I,J-1)*(taux_at_q(I,J-1)**2 + tauy_at_q(I,J-1)**2) + &
Expand All @@ -843,23 +843,23 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)

do j=js,je ; do I=Isq,Ieq
forces%taux(I,j) = 0.0
if ((G%mask2dT(i,j) + G%mask2dT(i+1,j)) > 0) &
if ((G%mask2dT(i,j) + G%mask2dT(i+1,j)) > 0.0) &
forces%taux(I,j) = (G%mask2dT(i,j)*taux_at_h(i,j) + &
G%mask2dT(i+1,j)*taux_at_h(i+1,j)) / &
(G%mask2dT(i,j) + G%mask2dT(i+1,j))
enddo ; enddo

do J=Jsq,Jeq ; do i=is,ie
forces%tauy(i,J) = 0.0
if ((G%mask2dT(i,j) + G%mask2dT(i,j+1)) > 0) &
if ((G%mask2dT(i,j) + G%mask2dT(i,j+1)) > 0.0) &
forces%tauy(i,J) = (G%mask2dT(i,j)*tauy_at_h(i,j) + &
G%mask2dT(i,J+1)*tauy_at_h(i,j+1)) / &
(G%mask2dT(i,j) + G%mask2dT(i,j+1))
enddo ; enddo

do j=js,je ; do i=is,ie
gustiness = CS%gust_const
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0)) gustiness = CS%gust(i,j)
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0.0)) gustiness = CS%gust(i,j)
forces%ustar(i,j) = sqrt(gustiness*Irho0 + Irho0 * G%mask2dT(i,j) * &
sqrt(taux_at_h(i,j)**2 + tauy_at_h(i,j)**2))
enddo ; enddo
Expand All @@ -871,12 +871,12 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, US, CS)

do j=js,je ; do i=is,ie
taux2 = 0.0
if ((G%mask2dCu(I-1,j) + G%mask2dCu(I,j)) > 0) &
if ((G%mask2dCu(I-1,j) + G%mask2dCu(I,j)) > 0.0) &
taux2 = (G%mask2dCu(I-1,j)*forces%taux(I-1,j)**2 + &
G%mask2dCu(I,j)*forces%taux(I,j)**2) / (G%mask2dCu(I-1,j) + G%mask2dCu(I,j))

tauy2 = 0.0
if ((G%mask2dCv(i,J-1) + G%mask2dCv(i,J)) > 0) &
if ((G%mask2dCv(i,J-1) + G%mask2dCv(i,J)) > 0.0) &
tauy2 = (G%mask2dCv(i,J-1)*forces%tauy(i,J-1)**2 + &
G%mask2dCv(i,J)*forces%tauy(i,J)**2) / (G%mask2dCv(i,J-1) + G%mask2dCv(i,J))

Expand Down
2 changes: 1 addition & 1 deletion config_src/drivers/solo_driver/MESO_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -172,7 +172,7 @@ subroutine MESO_buoyancy_forcing(sfc_state, fluxes, day, dt, G, US, CS)
do j=js,je ; do i=is,ie
! Set Temp_restore and Salin_restore to the temperature (in degC) and
! salinity (in ppt or PSU) that are being restored toward.
if (G%mask2dT(i,j) > 0) then
if (G%mask2dT(i,j) > 0.0) then
fluxes%heat_added(i,j) = G%mask2dT(i,j) * &
((CS%T_Restore(i,j) - sfc_state%SST(i,j)) * rhoXcp * CS%Flux_const)
fluxes%vprec(i,j) = - (CS%Rho0 * CS%Flux_const) * &
Expand Down
12 changes: 6 additions & 6 deletions config_src/drivers/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1125,7 +1125,7 @@ subroutine buoyancy_forcing_from_files(sfc_state, fluxes, day, dt, G, US, CS)

if (CS%use_temperature) then
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0) then
if (G%mask2dT(i,j) > 0.0) then
fluxes%heat_added(i,j) = G%mask2dT(i,j) * &
((CS%T_Restore(i,j) - sfc_state%SST(i,j)) * rhoXcp * CS%Flux_const_T)
fluxes%vprec(i,j) = - (CS%Rho0*CS%Flux_const_S) * &
Expand All @@ -1138,7 +1138,7 @@ subroutine buoyancy_forcing_from_files(sfc_state, fluxes, day, dt, G, US, CS)
enddo ; enddo
else
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0) then
if (G%mask2dT(i,j) > 0.0) then
fluxes%buoy(i,j) = (CS%Dens_Restore(i,j) - sfc_state%sfc_density(i,j)) * &
(CS%G_Earth * CS%Flux_const / CS%Rho0)
else
Expand Down Expand Up @@ -1231,7 +1231,7 @@ subroutine buoyancy_forcing_from_data_override(sfc_state, fluxes, day, dt, G, US
if (CS%restorebuoy) then
if (CS%use_temperature) then
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0) then
if (G%mask2dT(i,j) > 0.0) then
fluxes%heat_added(i,j) = G%mask2dT(i,j) * &
((CS%T_Restore(i,j) - sfc_state%SST(i,j)) * rhoXcp * CS%Flux_const_T)
fluxes%vprec(i,j) = - (CS%Rho0*CS%Flux_const_S) * &
Expand All @@ -1244,7 +1244,7 @@ subroutine buoyancy_forcing_from_data_override(sfc_state, fluxes, day, dt, G, US
enddo ; enddo
else
do j=js,je ; do i=is,ie
if (G%mask2dT(i,j) > 0) then
if (G%mask2dT(i,j) > 0.0) then
fluxes%buoy(i,j) = (CS%Dens_Restore(i,j) - sfc_state%sfc_density(i,j)) * &
(CS%G_Earth * CS%Flux_const / CS%Rho0)
else
Expand Down Expand Up @@ -1431,7 +1431,7 @@ subroutine buoyancy_forcing_linear(sfc_state, fluxes, day, dt, G, US, CS)
y = (G%geoLatCu(I,j)-CS%South_lat)/CS%len_lat
T_restore = CS%T_south + (CS%T_north-CS%T_south)*y
S_restore = CS%S_south + (CS%S_north-CS%S_south)*y
if (G%mask2dT(i,j) > 0) then
if (G%mask2dT(i,j) > 0.0) then
fluxes%heat_added(i,j) = G%mask2dT(i,j) * &
((T_Restore - sfc_state%SST(i,j)) * ((CS%Rho0 * fluxes%C_p) * CS%Flux_const))
fluxes%vprec(i,j) = - (CS%Rho0*CS%Flux_const) * &
Expand All @@ -1446,7 +1446,7 @@ subroutine buoyancy_forcing_linear(sfc_state, fluxes, day, dt, G, US, CS)
call MOM_error(FATAL, "buoyancy_forcing_linear in MOM_surface_forcing: "// &
"RESTOREBUOY to linear not written yet.")
!do j=js,je ; do i=is,ie
! if (G%mask2dT(i,j) > 0) then
! if (G%mask2dT(i,j) > 0.0) then
! fluxes%buoy(i,j) = (CS%Dens_Restore(i,j) - sfc_state%sfc_density(i,j)) * &
! (CS%G_Earth * CS%Flux_const / CS%Rho0)
! else
Expand Down
8 changes: 4 additions & 4 deletions src/ALE/coord_adapt.F90
Original file line number Diff line number Diff line change
Expand Up @@ -154,7 +154,7 @@ subroutine build_adapt_column(CS, G, GV, US, tv, i, j, zInt, tInt, sInt, h, zNex
! TODO: this needs to be adjusted to account for vanished layers near topography

! up (j-1)
if (G%mask2dT(i,j-1) > 0.) then
if (G%mask2dT(i,j-1) > 0.0) then
call calculate_density_derivs( &
0.5 * (tInt(i,j,2:nz) + tInt(i,j-1,2:nz)), &
0.5 * (sInt(i,j,2:nz) + sInt(i,j-1,2:nz)), &
Expand All @@ -166,7 +166,7 @@ subroutine build_adapt_column(CS, G, GV, US, tv, i, j, zInt, tInt, sInt, h, zNex
beta(2:nz) * (sInt(i,j-1,2:nz) - sInt(i,j,2:nz)))
endif
! down (j+1)
if (G%mask2dT(i,j+1) > 0.) then
if (G%mask2dT(i,j+1) > 0.0) then
call calculate_density_derivs( &
0.5 * (tInt(i,j,2:nz) + tInt(i,j+1,2:nz)), &
0.5 * (sInt(i,j,2:nz) + sInt(i,j+1,2:nz)), &
Expand All @@ -178,7 +178,7 @@ subroutine build_adapt_column(CS, G, GV, US, tv, i, j, zInt, tInt, sInt, h, zNex
beta(2:nz) * (sInt(i,j+1,2:nz) - sInt(i,j,2:nz)))
endif
! left (i-1)
if (G%mask2dT(i-1,j) > 0.) then
if (G%mask2dT(i-1,j) > 0.0) then
call calculate_density_derivs( &
0.5 * (tInt(i,j,2:nz) + tInt(i-1,j,2:nz)), &
0.5 * (sInt(i,j,2:nz) + sInt(i-1,j,2:nz)), &
Expand All @@ -190,7 +190,7 @@ subroutine build_adapt_column(CS, G, GV, US, tv, i, j, zInt, tInt, sInt, h, zNex
beta(2:nz) * (sInt(i-1,j,2:nz) - sInt(i,j,2:nz)))
endif
! right (i+1)
if (G%mask2dT(i+1,j) > 0.) then
if (G%mask2dT(i+1,j) > 0.0) then
call calculate_density_derivs( &
0.5 * (tInt(i,j,2:nz) + tInt(i+1,j,2:nz)), &
0.5 * (sInt(i,j,2:nz) + sInt(i+1,j,2:nz)), &
Expand Down
Loading

0 comments on commit e9fdf5d

Please sign in to comment.