Skip to content

Commit

Permalink
dOxyGenized arguments in MOM_opacity.F90
Browse files Browse the repository at this point in the history
  Added dOxyGen comments for several recently added arguments in MOM_opacity.F90
where they had been omitted.  Also shortened some openMP directives.  All
answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 3, 2018
1 parent 86818dd commit a4fe3ae
Showing 1 changed file with 31 additions and 36 deletions.
67 changes: 31 additions & 36 deletions src/parameterizations/vertical/MOM_opacity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -100,14 +100,15 @@ module MOM_opacity
contains

subroutine set_opacity(optics, fluxes, G, GV, CS)
type(optics_type), intent(inout) :: optics
type(forcing), intent(in) :: fluxes !< A structure containing pointers to any
!! possible forcing fields. Unused fields
!! have NULL ptrs.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
type(opacity_CS), pointer :: CS !< The control structure earlier set up by
!! opacity_init.
type(optics_type), intent(inout) :: optics !< An optics structure that has values
!! set based on the opacities.
type(forcing), intent(in) :: fluxes !< A structure containing pointers to any
!! possible forcing fields. Unused fields
!! have NULL ptrs.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
type(opacity_CS), pointer :: CS !< The control structure earlier set up by
!! opacity_init.

! Arguments: (inout) opacity - The inverse of the vertical absorption decay
! scale for penetrating shortwave radiation, in m-1.
Expand Down Expand Up @@ -147,21 +148,20 @@ subroutine set_opacity(optics, fluxes, G, GV, CS)
! Make sure there is no division by 0.
inv_sw_pen_scale = 1.0 / max(CS%pen_sw_scale, 0.1*GV%Angstrom_z, &
GV%H_to_m*GV%H_subroundoff)
!$OMP parallel default(none) shared(is,ie,js,je,nz,optics,inv_sw_pen_scale,fluxes,CS,Inv_nbands,GV)
if ( CS%Opacity_scheme == DOUBLE_EXP ) then
!$OMP do
!$OMP parallel do default(shared)
do k=1,nz ; do j=js,je ; do i=is,ie
optics%opacity_band(1,i,j,k) = inv_sw_pen_scale
optics%opacity_band(2,i,j,k) = 1.0 / max(CS%pen_sw_scale_2nd, &
0.1*GV%Angstrom_z,GV%H_to_m*GV%H_subroundoff)
enddo ; enddo ; enddo
if (.not.associated(fluxes%sw) .or. (CS%pen_SW_scale <= 0.0)) then
!$OMP do
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie ; do n=1,optics%nbands
optics%sw_pen_band(n,i,j) = 0.0
enddo ; enddo ; enddo
else
!$OMP do
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie ;
optics%sw_pen_band(1,i,j) = (CS%SW_1st_EXP_RATIO) * fluxes%sw(i,j)
optics%sw_pen_band(2,i,j) = (1.-CS%SW_1st_EXP_RATIO) * fluxes%sw(i,j)
Expand All @@ -172,22 +172,21 @@ subroutine set_opacity(optics, fluxes, G, GV, CS)
optics%opacity_band(n,i,j,k) = inv_sw_pen_scale
enddo ; enddo ; enddo ; enddo
if (.not.associated(fluxes%sw) .or. (CS%pen_SW_scale <= 0.0)) then
!$OMP do
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie ; do n=1,optics%nbands
optics%sw_pen_band(n,i,j) = 0.0
enddo ; enddo ; enddo
else
!$OMP do
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie ; do n=1,optics%nbands
optics%sw_pen_band(n,i,j) = CS%pen_SW_frac * Inv_nbands * fluxes%sw(i,j)
enddo ; enddo ; enddo
endif
endif
!$OMP end parallel
endif
if (query_averaging_enabled(CS%diag)) then
if (CS%id_sw_pen > 0) then
!$OMP parallel do default(none) shared(is,ie,js,je,Pen_SW_tot,optics)
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie
Pen_SW_tot(i,j) = 0.0
do n=1,optics%nbands
Expand All @@ -198,15 +197,15 @@ subroutine set_opacity(optics, fluxes, G, GV, CS)
endif
if (CS%id_sw_vis_pen > 0) then
if (CS%opacity_scheme == MANIZZA_05) then
!$OMP parallel do default(none) shared(is,ie,js,je,Pen_SW_tot,optics)
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie
Pen_SW_tot(i,j) = 0.0
do n=1,min(optics%nbands,2)
Pen_SW_tot(i,j) = Pen_SW_tot(i,j) + optics%sw_pen_band(n,i,j)
enddo
enddo ; enddo
else
!$OMP parallel do default(none) shared(is,ie,js,je,Pen_SW_tot,optics)
!$OMP parallel do default(shared)
do j=js,je ; do i=is,ie
Pen_SW_tot(i,j) = 0.0
do n=1,optics%nbands
Expand All @@ -217,7 +216,7 @@ subroutine set_opacity(optics, fluxes, G, GV, CS)
call post_data(CS%id_sw_vis_pen, Pen_SW_tot, CS%diag)
endif
do n=1,optics%nbands ; if (CS%id_opacity(n) > 0) then
!$OMP parallel do default(none) shared(nz,is,ie,js,je,tmp,optics,n)
!$OMP parallel do default(shared)
do k=1,nz ; do j=js,je ; do i=is,ie
tmp(i,j,k) = optics%opacity_band(n,i,j,k)
enddo ; enddo ; enddo
Expand All @@ -229,21 +228,16 @@ end subroutine set_opacity


subroutine opacity_from_chl(optics, fluxes, G, CS, chl_in)
type(optics_type), intent(inout) :: optics
type(forcing), intent(in) :: fluxes !< A structure containing pointers to any
!! possible forcing fields. Unused fields
!! have NULL ptrs.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(opacity_CS), pointer :: CS !< The control structure.
type(optics_type), intent(inout) :: optics !< An optics structure that has values
!! set based on the opacities.
type(forcing), intent(in) :: fluxes !< A structure containing pointers to any
!! possible forcing fields. Unused fields
!! have NULL ptrs.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(opacity_CS), pointer :: CS !< The control structure.
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in), optional :: chl_in !< A 3-d field of chlorophyll A,
!! in mg m-3.
! Arguments: fluxes - A structure containing pointers to any possible
! forcing fields. Unused fields have NULL ptrs.
! (out) opacity - The inverse of the vertical absorption decay
! scale for penetrating shortwave radiation, in m-1.
! (in) G - The ocean's grid structure.
! (in) chl_in - A 3-d field of chlorophyll A, in mg m-3.
optional, intent(in) :: chl_in !< A 3-d field of chlorophyll A,
!! in mg m-3.

real :: chl_data(SZI_(G),SZJ_(G)) ! The chlorophyll A concentrations in
! a layer, in mg/m^3.
Expand Down Expand Up @@ -476,7 +470,8 @@ subroutine opacity_init(Time, G, param_file, diag, tracer_flow, CS, optics)
target, intent(in) :: tracer_flow
type(opacity_CS), pointer :: CS !< A pointer that is set to point to the control
!! structure for this module.
type(optics_type), pointer :: optics
type(optics_type), pointer :: optics !< An optics structure that has parameters
!! set and arrays allocated here.
! 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 Expand Up @@ -674,8 +669,8 @@ end subroutine opacity_init


subroutine opacity_end(CS, optics)
type(opacity_CS), pointer :: CS
type(optics_type), pointer, optional :: optics
type(opacity_CS), pointer :: CS !< An opacity control structure that should be deallocated.
type(optics_type), optional, pointer :: optics !< An optics type structure that should be deallocated.

if (associated(CS%id_opacity)) deallocate(CS%id_opacity)
if (associated(CS)) deallocate(CS)
Expand Down

0 comments on commit a4fe3ae

Please sign in to comment.