Skip to content

Commit

Permalink
Merge pull request #1523 from Hallberg-NOAA/opt_args_in_core
Browse files Browse the repository at this point in the history
+Make 37 optional arguments in src/core mandatory
  • Loading branch information
marshallward authored Oct 20, 2021
2 parents 39c0c34 + 1fb283b commit e291d32
Show file tree
Hide file tree
Showing 12 changed files with 176 additions and 256 deletions.
11 changes: 5 additions & 6 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3056,8 +3056,8 @@ subroutine adjust_ssh_for_p_atm(tv, G, GV, US, ssh, p_atm, use_EOS)
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: ssh !< time mean surface height [m]
real, dimension(:,:), optional, pointer :: p_atm !< Ocean surface pressure [R L2 T-2 ~> Pa]
logical, optional, intent(in) :: use_EOS !< If true, calculate the density for
real, dimension(:,:), pointer :: p_atm !< Ocean surface pressure [R L2 T-2 ~> Pa]
logical, intent(in) :: use_EOS !< If true, calculate the density for
!! the SSH correction using the equation of state.

real :: Rho_conv(SZI_(G)) ! The density used to convert surface pressure to
Expand All @@ -3069,9 +3069,8 @@ subroutine adjust_ssh_for_p_atm(tv, G, GV, US, ssh, p_atm, use_EOS)

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec
EOSdom(:) = EOS_domain(G%HI)
if (present(p_atm)) then ; if (associated(p_atm)) then
calc_rho = associated(tv%eqn_of_state)
if (present(use_EOS) .and. calc_rho) calc_rho = use_EOS
if (associated(p_atm)) then
calc_rho = use_EOS .and. associated(tv%eqn_of_state)
! Correct the output sea surface height for the contribution from the ice pressure.
do j=js,je
if (calc_rho) then
Expand All @@ -3087,7 +3086,7 @@ subroutine adjust_ssh_for_p_atm(tv, G, GV, US, ssh, p_atm, use_EOS)
enddo
endif
enddo
endif ; endif
endif

end subroutine adjust_ssh_for_p_atm

Expand Down
5 changes: 2 additions & 3 deletions src/core/MOM_PressureForce.F90
Original file line number Diff line number Diff line change
Expand Up @@ -50,8 +50,7 @@ subroutine PressureForce(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_atm, pbce, e
intent(out) :: PFv !< Meridional pressure force acceleration [L T-2 ~> m s-2]
type(PressureForce_CS), pointer :: CS !< Pressure force control structure
type(ALE_CS), pointer :: ALE_CSp !< ALE control structure
real, dimension(:,:), &
optional, pointer :: p_atm !< The pressure at the ice-ocean or
real, dimension(:,:), pointer :: p_atm !< The pressure at the ice-ocean or
!! atmosphere-ocean interface [R L2 T-2 ~> Pa].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
optional, intent(out) :: pbce !< The baroclinic pressure anomaly in each layer
Expand Down Expand Up @@ -89,7 +88,7 @@ subroutine PressureForce_init(Time, G, GV, US, param_file, diag, CS, tides_CSp)
type(param_file_type), intent(in) :: param_file !< Parameter file handles
type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure
type(PressureForce_CS), pointer :: CS !< Pressure force control structure
type(tidal_forcing_CS), optional, pointer :: tides_CSp !< Tide control structure
type(tidal_forcing_CS), pointer :: tides_CSp !< Tide control structure
#include "version_variable.h"
character(len=40) :: mdl = "MOM_PressureForce" ! This module's name.

Expand Down
16 changes: 6 additions & 10 deletions src/core/MOM_PressureForce_FV.F90
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ subroutine PressureForce_FV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: PFv !< Meridional acceleration [L T-2 ~> m s-2]
type(PressureForce_FV_CS), pointer :: CS !< Finite volume PGF control structure
type(ALE_CS), pointer :: ALE_CSp !< ALE control structure
real, dimension(:,:), optional, pointer :: p_atm !< The pressure at the ice-ocean
real, dimension(:,:), pointer :: p_atm !< The pressure at the ice-ocean
!! or atmosphere-ocean interface [R L2 T-2 ~> Pa].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), optional, intent(out) :: pbce !< The baroclinic pressure
!! anomaly in each layer due to eta anomalies
Expand Down Expand Up @@ -167,8 +167,7 @@ subroutine PressureForce_FV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_
"MOM_PressureForce_FV_nonBouss: The Stanley parameterization is not yet"//&
"implemented in non-Boussinesq mode.")

use_p_atm = .false.
if (present(p_atm)) then ; if (associated(p_atm)) use_p_atm = .true. ; endif
use_p_atm = associated(p_atm)
use_EOS = associated(tv%eqn_of_state)
use_ALE = .false.
if (associated(ALE_CSp)) use_ALE = CS%reconstruct .and. use_EOS
Expand Down Expand Up @@ -425,7 +424,7 @@ subroutine PressureForce_FV_Bouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_atm
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: PFv !< Meridional acceleration [L T-2 ~> m s-2]
type(PressureForce_FV_CS), pointer :: CS !< Finite volume PGF control structure
type(ALE_CS), pointer :: ALE_CSp !< ALE control structure
real, dimension(:,:), optional, pointer :: p_atm !< The pressure at the ice-ocean
real, dimension(:,:), pointer :: p_atm !< The pressure at the ice-ocean
!! or atmosphere-ocean interface [R L2 T-2 ~> Pa].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), optional, intent(out) :: pbce !< The baroclinic pressure
!! anomaly in each layer due to eta anomalies
Expand Down Expand Up @@ -501,8 +500,7 @@ subroutine PressureForce_FV_Bouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_atm
if (.not.associated(CS)) call MOM_error(FATAL, &
"MOM_PressureForce_FV_Bouss: Module must be initialized before it is used.")

use_p_atm = .false.
if (present(p_atm)) then ; if (associated(p_atm)) use_p_atm = .true. ; endif
use_p_atm = associated(p_atm)
use_EOS = associated(tv%eqn_of_state)
do i=Isq,Ieq+1 ; p0(i) = 0.0 ; enddo
use_ALE = .false.
Expand Down Expand Up @@ -808,7 +806,7 @@ subroutine PressureForce_FV_init(Time, G, GV, US, param_file, diag, CS, tides_CS
type(param_file_type), intent(in) :: param_file !< Parameter file handles
type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure
type(PressureForce_FV_CS), pointer :: CS !< Finite volume PGF control structure
type(tidal_forcing_CS), optional, pointer :: tides_CSp !< Tides control structure
type(tidal_forcing_CS), pointer :: tides_CSp !< Tides control structure
! This include declares and sets the variable "version".
# include "version_variable.h"
character(len=40) :: mdl ! This module's name.
Expand All @@ -821,9 +819,7 @@ subroutine PressureForce_FV_init(Time, G, GV, US, param_file, diag, CS, tides_CS
else ; allocate(CS) ; endif

CS%diag => diag ; CS%Time => Time
if (present(tides_CSp)) then
if (associated(tides_CSp)) CS%tides_CSp => tides_CSp
endif
if (associated(tides_CSp)) CS%tides_CSp => tides_CSp

mdl = "MOM_PressureForce_FV"
call log_version(param_file, mdl, version, "")
Expand Down
22 changes: 9 additions & 13 deletions src/core/MOM_PressureForce_Montgomery.F90
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ subroutine PressureForce_Mont_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, p_atm, pb
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: PFv !< Meridional acceleration due to pressure gradients
!! (equal to -dM/dy) [L T-2 ~> m s-2].
type(PressureForce_Mont_CS), pointer :: CS !< Control structure for Montgomery potential PGF
real, dimension(:,:), optional, pointer :: p_atm !< The pressure at the ice-ocean or
real, dimension(:,:), pointer :: p_atm !< The pressure at the ice-ocean or
!! atmosphere-ocean [R L2 T-2 ~> Pa].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
optional, intent(out) :: pbce !< The baroclinic pressure anomaly in
Expand Down Expand Up @@ -133,9 +133,8 @@ subroutine PressureForce_Mont_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, p_atm, pb
Isq = G%IscB ; Ieq = G%IecB ; Jsq = G%JscB ; Jeq = G%JecB
EOSdom(1) = Isq - (G%isd-1) ; EOSdom(2) = G%iec+1 - (G%isd-1)

use_p_atm = .false.
if (present(p_atm)) then ; if (associated(p_atm)) use_p_atm = .true. ; endif
is_split = .false. ; if (present(pbce)) is_split = .true.
use_p_atm = associated(p_atm)
is_split = present(pbce)
use_EOS = associated(tv%eqn_of_state)

if (.not.associated(CS)) call MOM_error(FATAL, &
Expand Down Expand Up @@ -368,7 +367,7 @@ subroutine PressureForce_Mont_Bouss(h, tv, PFu, PFv, G, GV, US, CS, p_atm, pbce,
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: PFv !< Meridional acceleration due to pressure gradients
!! (equal to -dM/dy) [L T-2 ~> m s2].
type(PressureForce_Mont_CS), pointer :: CS !< Control structure for Montgomery potential PGF
real, dimension(:,:), optional, pointer :: p_atm !< The pressure at the ice-ocean or
real, dimension(:,:), pointer :: p_atm !< The pressure at the ice-ocean or
!! atmosphere-ocean [R L2 T-2 ~> Pa].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), optional, intent(out) :: pbce !< The baroclinic pressure anomaly in
!! each layer due to free surface height anomalies
Expand Down Expand Up @@ -421,9 +420,8 @@ subroutine PressureForce_Mont_Bouss(h, tv, PFu, PFv, G, GV, US, CS, p_atm, pbce,
Isq = G%IscB ; Ieq = G%IecB ; Jsq = G%JscB ; Jeq = G%JecB
EOSdom(1) = Isq - (G%isd-1) ; EOSdom(2) = G%iec+1 - (G%isd-1)

use_p_atm = .false.
if (present(p_atm)) then ; if (associated(p_atm)) use_p_atm = .true. ; endif
is_split = .false. ; if (present(pbce)) is_split = .true.
use_p_atm = associated(p_atm)
is_split = present(pbce)
use_EOS = associated(tv%eqn_of_state)

if (.not.associated(CS)) call MOM_error(FATAL, &
Expand Down Expand Up @@ -826,8 +824,8 @@ subroutine PressureForce_Mont_init(Time, G, GV, US, param_file, diag, CS, tides_
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(param_file_type), intent(in) :: param_file !< Parameter file handles
type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure
type(PressureForce_Mont_CS), pointer :: CS !< Montgomery PGF control structure
type(tidal_forcing_CS), optional, pointer :: tides_CSp !< Tides control structure
type(PressureForce_Mont_CS), pointer :: CS !< Montgomery PGF control structure
type(tidal_forcing_CS), pointer :: tides_CSp !< Tides control structure

! Local variables
logical :: use_temperature, use_EOS
Expand All @@ -842,9 +840,7 @@ subroutine PressureForce_Mont_init(Time, G, GV, US, param_file, diag, CS, tides_
else ; allocate(CS) ; endif

CS%diag => diag ; CS%Time => Time
if (present(tides_CSp)) then
if (associated(tides_CSp)) CS%tides_CSp => tides_CSp
endif
if (associated(tides_CSp)) CS%tides_CSp => tides_CSp

mdl = "MOM_PressureForce_Mont"
call log_version(param_file, mdl, version, "")
Expand Down
Loading

0 comments on commit e291d32

Please sign in to comment.