Skip to content

Commit

Permalink
dOxyGenized MESO_surface_forcing.F90
Browse files Browse the repository at this point in the history
  Added dOxyGen comments for all routines and arguments in
MESO_surface_forcing.F90.  Also replaced calls to alloc_if_needed with calls to
the functionally equivalent safe_alloc_ptr.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 8, 2018
1 parent 7ff278e commit 01b434e
Showing 1 changed file with 38 additions and 41 deletions.
79 changes: 38 additions & 41 deletions config_src/solo_driver/MESO_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module MESO_surface_forcing
!* *
!********+*********+*********+*********+*********+*********+*********+**
use MOM_diag_mediator, only : post_data, query_averaging_enabled
use MOM_diag_mediator, only : register_diag_field, diag_ctrl
use MOM_diag_mediator, only : register_diag_field, diag_ctrl, safe_alloc_ptr
use MOM_domains, only : pass_var, pass_vector, AGRID
use MOM_error_handler, only : MOM_error, FATAL, WARNING, is_root_pe
use MOM_file_parser, only : get_param, log_version, param_file_type
Expand Down Expand Up @@ -97,11 +97,13 @@ module MESO_surface_forcing

contains

!### This subroutine sets zero surface wind stresses, but it is not even
!### used by the MESO experimeents. This subroutine can be deleted. -RWH
subroutine MESO_wind_forcing(sfc_state, forces, day, G, CS)
type(surface), intent(inout) :: sfc_state !< A structure containing fields that
!! describe the surface state of the ocean.
type(mech_forcing), intent(inout) :: forces !< A structure with the driving mechanical forces
type(time_type), intent(in) :: day
type(time_type), intent(in) :: day !< The time of the fluxes
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(MESO_surface_forcing_CS), pointer :: CS !< A pointer to the control structure returned by a previous
!! call to MESO_surface_forcing_init
Expand Down Expand Up @@ -160,15 +162,18 @@ subroutine MESO_wind_forcing(sfc_state, forces, day, G, CS)

end subroutine MESO_wind_forcing

!> This subroutine sets up the MESO buoyancy forcing, which uses control-theory style
!! specification restorative buoyancy fluxes at large scales.
subroutine MESO_buoyancy_forcing(sfc_state, fluxes, day, dt, G, CS)
type(surface), intent(inout) :: sfc_state !< A structure containing fields that
!! describe the surface state of the ocean.
type(forcing), intent(inout) :: fluxes
type(time_type), intent(in) :: day
type(forcing), intent(inout) :: fluxes !< A structure containing thermodynamic forcing fields
type(time_type), intent(in) :: day !< The time of the fluxes
real, intent(in) :: dt !< The amount of time over which
!! the fluxes apply, in s
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(MESO_surface_forcing_CS), pointer :: CS
type(MESO_surface_forcing_CS), pointer :: CS !< A pointer to the control structure returned by
!! a previous call to MESO_surface_forcing_init

! This subroutine specifies the current surface fluxes of buoyancy or
! temperature and fresh water. It may also be modified to add
Expand Down Expand Up @@ -215,30 +220,30 @@ subroutine MESO_buoyancy_forcing(sfc_state, fluxes, day, dt, G, CS)
! Allocate and zero out the forcing arrays, as necessary. This portion is
! usually not changed.
if (CS%use_temperature) then
call alloc_if_needed(fluxes%evap, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%lprec, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%fprec, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%lrunoff, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%frunoff, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%vprec, isd, ied, jsd, jed)

call alloc_if_needed(fluxes%sw, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%lw, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%latent, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%sens, isd, ied, jsd, jed)
call alloc_if_needed(fluxes%heat_content_lprec, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%evap, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%lprec, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%fprec, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%lrunoff, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%frunoff, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%vprec, isd, ied, jsd, jed)

call safe_alloc_ptr(fluxes%sw, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%lw, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%latent, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%sens, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%heat_content_lprec, isd, ied, jsd, jed)
else ! This is the buoyancy only mode.
call alloc_if_needed(fluxes%buoy, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%buoy, isd, ied, jsd, jed)
endif


! MODIFY THE CODE IN THE FOLLOWING LOOPS TO SET THE BUOYANCY FORCING TERMS.
if (CS%restorebuoy .and. first_call) then !### .or. associated(CS%ctrl_forcing_CSp)) then
call alloc_if_needed(CS%T_Restore, isd, ied, jsd, jed)
call alloc_if_needed(CS%S_Restore, isd, ied, jsd, jed)
call alloc_if_needed(CS%Heat, isd, ied, jsd, jed)
call alloc_if_needed(CS%PmE, isd, ied, jsd, jed)
call alloc_if_needed(CS%Solar, isd, ied, jsd, jed)
call safe_alloc_ptr(CS%T_Restore, isd, ied, jsd, jed)
call safe_alloc_ptr(CS%S_Restore, isd, ied, jsd, jed)
call safe_alloc_ptr(CS%Heat, isd, ied, jsd, jed)
call safe_alloc_ptr(CS%PmE, isd, ied, jsd, jed)
call safe_alloc_ptr(CS%Solar, isd, ied, jsd, jed)

call MOM_read_data(trim(CS%inputdir)//trim(CS%SSTrestore_file), "SST", &
CS%T_Restore(:,:), G%Domain)
Expand Down Expand Up @@ -281,7 +286,7 @@ subroutine MESO_buoyancy_forcing(sfc_state, fluxes, day, dt, G, CS)

if (CS%restorebuoy) then
if (CS%use_temperature) then
call alloc_if_needed(fluxes%heat_added, isd, ied, jsd, jed)
call safe_alloc_ptr(fluxes%heat_added, isd, ied, jsd, jed)
! When modifying the code, comment out this error message. It is here
! so that the original (unmodified) version is not accidentally used.
! call MOM_error(FATAL, "MESO_buoyancy_surface_forcing: " // &
Expand Down Expand Up @@ -323,24 +328,16 @@ subroutine MESO_buoyancy_forcing(sfc_state, fluxes, day, dt, G, CS)

end subroutine MESO_buoyancy_forcing

subroutine alloc_if_needed(ptr, isd, ied, jsd, jed)
! If ptr is not associated, this routine allocates it with the given size
! and zeros out its contents. This is equivalent to safe_alloc_ptr in
! MOM_diag_mediator, but is here so as to be completely transparent.
real, pointer :: ptr(:,:)
integer :: isd, ied, jsd, jed
if (.not.associated(ptr)) then
allocate(ptr(isd:ied,jsd:jed))
ptr(:,:) = 0.0
endif
end subroutine alloc_if_needed

!> Initialize the MESO surface forcing module
subroutine MESO_surface_forcing_init(Time, G, param_file, diag, CS)
type(time_type), intent(in) :: Time
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(diag_ctrl), target, intent(in) :: diag
type(MESO_surface_forcing_CS), pointer :: CS

type(time_type), intent(in) :: Time !< The current model time
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(diag_ctrl), target, intent(inout) :: diag !< structure used to regulate diagnostic output
type(MESO_surface_forcing_CS), pointer :: CS !< A pointer that is set to point to the
!! control structure for this module

! Arguments: Time - The current model time.
! (in) G - The ocean's grid structure.
! (in) param_file - A structure indicating the open file to parse for
Expand Down

0 comments on commit 01b434e

Please sign in to comment.