Skip to content

Commit

Permalink
Added dOxyGen comments in coord_ code
Browse files Browse the repository at this point in the history
  Added dOxyGen comments for all of the subroutines and their arguments in the
coord_... modules in ALE.  Also shortened the name of several variables.  All
answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 6, 2018
1 parent a9605fb commit 380574a
Show file tree
Hide file tree
Showing 7 changed files with 118 additions and 91 deletions.
12 changes: 6 additions & 6 deletions src/ALE/MOM_regridding.F90
Original file line number Diff line number Diff line change
Expand Up @@ -694,7 +694,7 @@ subroutine check_grid_def(filename, varname, expected_units, msg, ierr)
integer :: i

ierr = .false.
status = NF90_OPEN(trim(filename), NF90_NOWRITE, ncid);
status = NF90_OPEN(trim(filename), NF90_NOWRITE, ncid)
if (status /= NF90_NOERR) then
ierr = .true.
msg = 'File not found: '//trim(filename)
Expand Down Expand Up @@ -2149,19 +2149,19 @@ subroutine set_regrid_params( CS, boundary_extrapolation, min_thickness, old_gri
adaptTimeRatio, adaptZoom, adaptZoomCoeff, adaptBuoyCoeff, adaptAlpha, adaptDoMin)
type(regridding_CS), intent(inout) :: CS !< Regridding control structure
logical, optional, intent(in) :: boundary_extrapolation !< Extrapolate in boundary cells
real, optional, intent(in) :: min_thickness !< Minimum thickness allowed when building the new grid (m)
real, optional, intent(in) :: old_grid_weight !< Weight given to old coordinate when time-filtering grid
real, optional, intent(in) :: min_thickness !< Minimum thickness allowed when building the new grid (m)
real, optional, intent(in) :: old_grid_weight !< Weight given to old coordinate when time-filtering grid
character(len=*), optional, intent(in) :: interp_scheme !< Interpolation method for state-dependent coordinates
real, optional, intent(in) :: depth_of_time_filter_shallow !< Depth to start cubic (H units)
real, optional, intent(in) :: depth_of_time_filter_deep !< Depth to end cubic (H units)
real, optional, intent(in) :: compress_fraction !< Fraction of compressibility to add to potential density
real, optional, intent(in) :: dz_min_surface !< The fixed resolution in the topmost SLight_nkml_min layers (m)
integer, optional, intent(in) :: nz_fixed_surface !< The number of fixed-thickess layers at the top of the model
real, optional, intent(in) :: dz_min_surface !< The fixed resolution in the topmost SLight_nkml_min layers (m)
integer, optional, intent(in) :: nz_fixed_surface !< The number of fixed-thickness layers at the top of the model
real, optional, intent(in) :: Rho_ml_avg_depth !< Averaging depth over which to determine mixed layer potential
!! density (m)
real, optional, intent(in) :: nlay_ML_to_interior !< Number of layers to offset the mixed layer density to find
!! resolved stratification (nondim)
logical, optional, intent(in) :: fix_haloclines !< Detect regions with much weaker stratification in the coordinate
logical, optional, intent(in) :: fix_haloclines !< Detect regions with much weaker stratification in the coordinate
real, optional, intent(in) :: halocline_filt_len !< Length scale over which to filter T & S when looking for
!! spuriously unstable water mass profiles (m)
real, optional, intent(in) :: halocline_strat_tol !< Value of the stratification ratio that defines a problematic
Expand Down
24 changes: 16 additions & 8 deletions src/ALE/coord_adapt.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,7 @@ module coord_adapt

#include <MOM_memory.h>

type, public :: adapt_CS
private
type, public :: adapt_CS ; private

!> Number of layers/levels
integer :: nk
Expand Down Expand Up @@ -51,8 +50,8 @@ module coord_adapt
!> Initialise an adapt_CS with parameters
subroutine init_coord_adapt(CS, nk, coordinateResolution)
type(adapt_CS), pointer :: CS !< Unassociated pointer to hold the control structure
integer, intent(in) :: nk
real, dimension(:), intent(in) :: coordinateResolution
integer, intent(in) :: nk !< Number of layers in the grid
real, dimension(:), intent(in) :: coordinateResolution !< Nominal near-surface resolution (m)

if (associated(CS)) call MOM_error(FATAL, "init_coord_adapt: CS already associated")
allocate(CS)
Expand All @@ -72,12 +71,21 @@ subroutine end_coord_adapt(CS)
deallocate(CS)
end subroutine end_coord_adapt

!> This subtroutine can be used to set the parameters for coord_adapt module
subroutine set_adapt_params(CS, adaptTimeRatio, adaptAlpha, adaptZoom, adaptZoomCoeff, &
adaptBuoyCoeff, adaptDrho0, adaptDoMin)
adaptBuoyCoeff, adaptDrho0, adaptDoMin)
type(adapt_CS), pointer :: CS !< The control structure for this module
real, optional, intent(in) :: adaptTimeRatio, adaptAlpha, adaptZoom, adaptZoomCoeff
real, optional, intent(in) :: adaptBuoyCoeff, adaptDrho0
logical, optional, intent(in) :: adaptDoMin
real, optional, intent(in) :: adaptTimeRatio !< Ratio of optimisation and diffusion timescales
real, optional, intent(in) :: adaptAlpha !< Nondimensional coefficient determining
!! how much optimisation to apply
real, optional, intent(in) :: adaptZoom !< Near-surface zooming depth, in m
real, optional, intent(in) :: adaptZoomCoeff !< Near-surface zooming coefficient
real, optional, intent(in) :: adaptBuoyCoeff !< Stratification-dependent diffusion coefficient
real, optional, intent(in) :: adaptDrho0 !< Reference density difference for
!! stratification-dependent diffusion
logical, optional, intent(in) :: adaptDoMin !< If true, form a HYCOM1-like mixed layer by
!! preventing interfaces from becoming shallower than
!! the depths set by coordinateResolution

if (.not. associated(CS)) call MOM_error(FATAL, "set_adapt_params: CS not associated")

Expand Down
17 changes: 9 additions & 8 deletions src/ALE/coord_hycom.F90
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,7 @@ module coord_hycom
implicit none ; private

!> Control structure containing required parameters for the HyCOM coordinate
type, public :: hycom_CS
private
type, public :: hycom_CS ; private

!> Number of layers/levels in generated grid
integer :: nk
Expand Down Expand Up @@ -40,7 +39,7 @@ module coord_hycom
subroutine init_coord_hycom(CS, nk, coordinateResolution, target_density, interp_CS)
type(hycom_CS), pointer :: CS !< Unassociated pointer to hold the control structure
integer, intent(in) :: nk !< Number of layers in generated grid
real, dimension(nk), intent(in) :: coordinateResolution !< Z-space thicknesses (m)
real, dimension(nk), intent(in) :: coordinateResolution !< Nominal near-surface resolution (m)
real, dimension(nk+1),intent(in) :: target_density !< Interface target densities (kg/m3)
type(interp_CS_type), intent(in) :: interp_CS !< Controls for interpolation

Expand All @@ -55,8 +54,9 @@ subroutine init_coord_hycom(CS, nk, coordinateResolution, target_density, interp
CS%interp_CS = interp_CS
end subroutine init_coord_hycom

!> This subroutine deallocates memory in the control structure for the coord_hycom module
subroutine end_coord_hycom(CS)
type(hycom_CS), pointer :: CS
type(hycom_CS), pointer :: CS !< Coordinate control structure

! nothing to do
if (.not. associated(CS)) return
Expand All @@ -67,11 +67,12 @@ subroutine end_coord_hycom(CS)
deallocate(CS)
end subroutine end_coord_hycom

!> This subroutine can be used to set the parameters for the coord_hycom module
subroutine set_hycom_params(CS, max_interface_depths, max_layer_thickness, interp_CS)
type(hycom_CS), pointer :: CS
real, optional, dimension(:), intent(in) :: max_interface_depths
real, optional, dimension(:), intent(in) :: max_layer_thickness
type(interp_CS_type), optional, intent(in) :: interp_CS
type(hycom_CS), pointer :: CS !< Coordinate control structure
real, dimension(:), optional, intent(in) :: max_interface_depths !< Maximum depths of interfaces in m
real, dimension(:), optional, intent(in) :: max_layer_thickness !< Maximum thicknesses of layers in m
type(interp_CS_type), optional, intent(in) :: interp_CS !< Controls for interpolation

if (.not. associated(CS)) call MOM_error(FATAL, "set_hycom_params: CS not associated")

Expand Down
61 changes: 32 additions & 29 deletions src/ALE/coord_rho.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,23 +11,22 @@ module coord_rho
implicit none ; private

!> Control structure containing required parameters for the rho coordinate
type, public :: rho_CS
private
type, public :: rho_CS ; private

!> Number of layers
integer :: nk

!> Minimum thickness allowed for layers
!> Minimum thickness allowed for layers, in m
real :: min_thickness = 0.

!> Reference pressure for density calculations
!> Reference pressure for density calculations, in Pa
real :: ref_pressure

!> If true, integrate for interface positions from the top downward.
!! If false, integrate from the bottom upward, as does the rest of the model.
logical :: integrate_downward_for_e = .false.

!> Nominal density of interfaces
!> Nominal density of interfaces, in kg m-3
real, allocatable, dimension(:) :: target_density

!> Interpolation control structure
Expand All @@ -46,10 +45,10 @@ module coord_rho
!> Initialise a rho_CS with pointers to parameters
subroutine init_coord_rho(CS, nk, ref_pressure, target_density, interp_CS)
type(rho_CS), pointer :: CS !< Unassociated pointer to hold the control structure
integer, intent(in) :: nk
real, intent(in) :: ref_pressure
real, dimension(:), intent(in) :: target_density
type(interp_CS_type), intent(in) :: interp_CS
integer, intent(in) :: nk !< Number of layers in the grid
real, intent(in) :: ref_pressure !< Nominal density of interfaces in Pa
real, dimension(:), intent(in) :: target_density !< Nominal density of interfaces in kg m-3
type(interp_CS_type), intent(in) :: interp_CS !< Controls for interpolation

if (associated(CS)) call MOM_error(FATAL, "init_coord_rho: CS already associated!")
allocate(CS)
Expand All @@ -61,20 +60,25 @@ subroutine init_coord_rho(CS, nk, ref_pressure, target_density, interp_CS)
CS%interp_CS = interp_CS
end subroutine init_coord_rho

!> This subroutine deallocates memory in the control structure for the coord_rho module
subroutine end_coord_rho(CS)
type(rho_CS), pointer :: CS
type(rho_CS), pointer :: CS !< Coordinate control structure

! nothing to do
if (.not. associated(CS)) return
deallocate(CS%target_density)
deallocate(CS)
end subroutine end_coord_rho

!> This subroutine can be used to set the parameters for the coord_rho module
subroutine set_rho_params(CS, min_thickness, integrate_downward_for_e, interp_CS)
type(rho_CS), pointer :: CS
real, optional, intent(in) :: min_thickness
logical, optional, intent(in) :: integrate_downward_for_e
type(interp_CS_type), optional, intent(in) :: interp_CS
type(rho_CS), pointer :: CS !< Coordinate control structure
real, optional, intent(in) :: min_thickness !< Minimum allowed thickness, in m
logical, optional, intent(in) :: integrate_downward_for_e !< If true, integrate for interface
!! positions from the top downward. If false, integrate
!! from the bottom upward, as does the rest of the model.

type(interp_CS_type), optional, intent(in) :: interp_CS !< Controls for interpolation

if (.not. associated(CS)) call MOM_error(FATAL, "set_rho_params: CS not associated")

Expand Down Expand Up @@ -342,14 +346,13 @@ subroutine copy_finite_thicknesses(nk, h_in, threshold, nout, h_out, mapping)
end subroutine copy_finite_thicknesses

!------------------------------------------------------------------------------
! Inflate vanished layers to finite (nonzero) width
!------------------------------------------------------------------------------
subroutine old_inflate_layers_1d( minThickness, N, h )
!> Inflate vanished layers to finite (nonzero) width
subroutine old_inflate_layers_1d( min_thickness, nk, h )

! Argument
real, intent(in) :: minThickness
integer, intent(in) :: N
real, intent(inout) :: h(:)
real, intent(in) :: min_thickness !< Minimum allowed thickness, in m
integer, intent(in) :: nk !< Number of layers in the grid
real, dimension(:), intent(inout) :: h !< Layer thicknesses, in m

! Local variable
integer :: k
Expand All @@ -361,28 +364,28 @@ subroutine old_inflate_layers_1d( minThickness, N, h )

! Count number of nonzero layers
count_nonzero_layers = 0
do k = 1,N
if ( h(k) > minThickness ) then
do k = 1,nk
if ( h(k) > min_thickness ) then
count_nonzero_layers = count_nonzero_layers + 1
end if
end do

! If all layer thicknesses are greater than the threshold, exit routine
if ( count_nonzero_layers == N ) return
if ( count_nonzero_layers == nk ) return

! If all thicknesses are zero, inflate them all and exit
if ( count_nonzero_layers == 0 ) then
do k = 1,N
h(k) = minThickness
do k = 1,nk
h(k) = min_thickness
end do
return
end if

! Inflate zero layers
correction = 0.0
do k = 1,N
if ( h(k) <= minThickness ) then
delta = minThickness - h(k)
do k = 1,nk
if ( h(k) <= min_thickness ) then
delta = min_thickness - h(k)
correction = correction + delta
h(k) = h(k) + delta
end if
Expand All @@ -391,7 +394,7 @@ subroutine old_inflate_layers_1d( minThickness, N, h )
! Modify thicknesses of nonzero layers to ensure volume conservation
maxThickness = h(1)
k_found = 1
do k = 1,N
do k = 1,nk
if ( h(k) > maxThickness ) then
maxThickness = h(k)
k_found = k
Expand Down
17 changes: 9 additions & 8 deletions src/ALE/coord_sigma.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,7 @@ module coord_sigma
implicit none ; private

!> Control structure containing required parameters for the sigma coordinate
type, public :: sigma_CS
private
type, public :: sigma_CS ; private

!> Number of levels
integer :: nk
Expand All @@ -28,8 +27,8 @@ module coord_sigma
!> Initialise a sigma_CS with pointers to parameters
subroutine init_coord_sigma(CS, nk, coordinateResolution)
type(sigma_CS), pointer :: CS !< Unassociated pointer to hold the control structure
integer, intent(in) :: nk
real, dimension(:), intent(in) :: coordinateResolution
integer, intent(in) :: nk !< Number of layers in the grid
real, dimension(:), intent(in) :: coordinateResolution !< Nominal coordinate resolution (nondim)

if (associated(CS)) call MOM_error(FATAL, "init_coord_sigma: CS already associated!")
allocate(CS)
Expand All @@ -39,18 +38,20 @@ subroutine init_coord_sigma(CS, nk, coordinateResolution)
CS%coordinateResolution = coordinateResolution
end subroutine init_coord_sigma

!> This subroutine deallocates memory in the control structure for the coord_sigma module
subroutine end_coord_sigma(CS)
type(sigma_CS), pointer :: CS
type(sigma_CS), pointer :: CS !< Coordinate control structure

! nothing to do
if (.not. associated(CS)) return
deallocate(CS%coordinateResolution)
deallocate(CS)
end subroutine end_coord_sigma

!> This subroutine can be used to set the parameters for the coord_sigma module
subroutine set_sigma_params(CS, min_thickness)
type(sigma_CS), pointer :: CS
real, optional, intent(in) :: min_thickness
type(sigma_CS), pointer :: CS !< Coordinate control structure
real, optional, intent(in) :: min_thickness !< Minimum allowed thickness, in m

if (.not. associated(CS)) call MOM_error(FATAL, "set_sigma_params: CS not associated")

Expand All @@ -63,7 +64,7 @@ subroutine build_sigma_column(CS, depth, totalThickness, zInterface)
type(sigma_CS), intent(in) :: CS !< Coordinate control structure
real, intent(in) :: depth !< Depth of ocean bottom (positive in m)
real, intent(in) :: totalThickness !< Column thickness (positive in m)
real, dimension(CS%nk+1), intent(inout) :: zInterface !< Absolute positions of interfaces
real, dimension(CS%nk+1), intent(inout) :: zInterface !< Absolute positions of interfaces in m

! Local variables
integer :: k
Expand Down
Loading

0 comments on commit 380574a

Please sign in to comment.