Skip to content

Commit

Permalink
Added Doxygen comments to subroutines
Browse files Browse the repository at this point in the history
Added doxygen comments to all of the subroutines in MOM_TFreeze.F90, MOM_hor_visc.F90, MOM_internal_tides.F90, MOM_tracer_flow_control.F90. All the
answers are bitwise identical.
  • Loading branch information
CarolineCardinale committed Jun 23, 2017
1 parent d2e6771 commit 40a7aed
Show file tree
Hide file tree
Showing 4 changed files with 454 additions and 206 deletions.
64 changes: 49 additions & 15 deletions src/equation_of_state/MOM_TFreeze.F90
Original file line number Diff line number Diff line change
Expand Up @@ -66,12 +66,22 @@ subroutine calculate_TFreeze_linear_scalar(S, pres, T_Fr, TFr_S0_P0, &

end subroutine calculate_TFreeze_linear_scalar

!> This subroutine computes the freezing point potential temparature
!! (in deg C) from salinity (in psu), and pressure (in Pa) using a simple
!! linear expression, with coefficients passed in as arguments.
subroutine calculate_TFreeze_linear_array(S, pres, T_Fr, start, npts, &
TFr_S0_P0, dTFr_dS, dTFr_dp)
real, dimension(:), intent(in) :: S, pres
real, dimension(:), intent(out) :: T_Fr
integer, intent(in) :: start, npts
real, intent(in) :: TFr_S0_P0, dTFr_dS, dTFr_dp
real, dimension(:), intent(in) :: S !< salinity in PSU.
real, dimension(:), intent(in) :: pres !< pressure in Pa.
real, dimension(:), intent(out) :: T_Fr !< Freezing point potential temperature in deg C.
integer, intent(in) :: start !< the starting point in the arrays.
integer, intent(in) :: npts !< the number of values to calculate.
real, intent(in) :: TFr_S0_P0 !< The freezing point at S=0, p=0, in deg C.
real, intent(in) :: dTFr_dS !< The derivative of freezing point with salinity,
!! in deg C PSU-1.
real, intent(in) :: dTFr_dp !< The derivative of freezing point with pressure,
!! in deg C Pa-1.

! This subroutine computes the freezing point potential temparature
! (in deg C) from salinity (in psu), and pressure (in Pa) using a simple
! linear expression, with coefficients passed in as arguments.
Expand All @@ -94,9 +104,17 @@ subroutine calculate_TFreeze_linear_array(S, pres, T_Fr, start, npts, &

end subroutine calculate_TFreeze_linear_array

!> This subroutine computes the freezing point potential temparature
!! (in deg C) from salinity (in psu), and pressure (in Pa) using the expression
!! from Millero (1978) (and in appendix A of Gill 1982), but with the of the
!! pressure dependence changed from 7.53e-8 to 7.75e-8 to make this an
!! expression for potential temperature (not in situ temperature), using a
!! value that is correct at the freezing point at 35 PSU and 5e6 Pa (500 dbar).
subroutine calculate_TFreeze_Millero_scalar(S, pres, T_Fr)
real, intent(in) :: S, pres
real, intent(out) :: T_Fr
real, intent(in) :: S !< Salinity in PSU.
real, intent(in) :: pres !< Pressure in Pa.
real, intent(out) :: T_Fr !< Freezing point potential temperature in deg C.

! This subroutine computes the freezing point potential temparature
! (in deg C) from salinity (in psu), and pressure (in Pa) using the expression
! from Millero (1978) (and in appendix A of Gill 1982), but with the of the
Expand All @@ -114,11 +132,18 @@ subroutine calculate_TFreeze_Millero_scalar(S, pres, T_Fr)

end subroutine calculate_TFreeze_Millero_scalar


!> This subroutine computes the freezing point potential temparature
!! (in deg C) from salinity (in psu), and pressure (in Pa) using the expression
!! from Millero (1978) (and in appendix A of Gill 1982), but with the of the
!! pressure dependence changed from 7.53e-8 to 7.75e-8 to make this an
!! expression for potential temperature (not in situ temperature), using a
!! value that is correct at the freezing point at 35 PSU and 5e6 Pa (500 dbar).
subroutine calculate_TFreeze_Millero_array(S, pres, T_Fr, start, npts)
real, dimension(:), intent(in) :: S, pres
real, dimension(:), intent(out) :: T_Fr
integer, intent(in) :: start, npts
real, dimension(:), intent(in) :: S !< Salinity in PSU.
real, dimension(:), intent(in) :: pres !< Pressure in Pa.
real, dimension(:), intent(out) :: T_Fr !< Freezing point potential temperature in deg C.
integer, intent(in) :: start !< The starting point in the arrays.
integer, intent(in) :: npts !< The number of values to calculate.
! This subroutine computes the freezing point potential temparature
! (in deg C) from salinity (in psu), and pressure (in Pa) using the expression
! from Millero (1978) (and in appendix A of Gill 1982), but with the of the
Expand All @@ -142,9 +167,13 @@ subroutine calculate_TFreeze_Millero_array(S, pres, T_Fr, start, npts)

end subroutine calculate_TFreeze_Millero_array

!> This subroutine computes the freezing point conservative temparature
!! (in deg C) from absolute salinity (in g/kg), and pressure (in Pa) using the
!! TEOS10 package.
subroutine calculate_TFreeze_teos10_scalar(S, pres, T_Fr)
real, intent(in) :: S, pres
real, intent(out) :: T_Fr
real, intent(in) :: S !< Absolute salinity in g/kg.
real, intent(in) :: pres !< Pressure in Pa.
real, intent(out) :: T_Fr !< Freezing point conservative temperature in deg C.
! This subroutine computes the freezing point conservative temparature
! (in deg C) from absolute salinity (in g/kg), and pressure (in Pa) using the
! TEOS10 package.
Expand All @@ -163,10 +192,15 @@ subroutine calculate_TFreeze_teos10_scalar(S, pres, T_Fr)

end subroutine calculate_TFreeze_teos10_scalar

!> This subroutine computes the freezing point conservative temparature
!! (in deg C) from absolute salinity (in g/kg), and pressure (in Pa) using the
!! TEOS10 package.
subroutine calculate_TFreeze_teos10_array(S, pres, T_Fr, start, npts)
real, dimension(:), intent(in) :: S, pres
real, dimension(:), intent(out) :: T_Fr
integer, intent(in) :: start, npts
real, dimension(:), intent(in) :: S !< absolute salinity in g/kg.
real, dimension(:), intent(in) :: pres !< pressure in Pa.
real, dimension(:), intent(out) :: T_Fr !< Freezing point conservative temperature in deg C.
integer, intent(in) :: start !< the starting point in the arrays.
integer, intent(in) :: npts !< the number of values to calculate.
! This subroutine computes the freezing point conservative temparature
! (in deg C) from absolute salinity (in g/kg), and pressure (in Pa) using the
! TEOS10 package.
Expand Down
60 changes: 43 additions & 17 deletions src/parameterizations/lateral/MOM_hor_visc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -216,18 +216,39 @@ module MOM_hor_visc

contains

!> This subroutine determines the acceleration due to the
!! horizontal viscosity. A combination of biharmonic and Laplacian
!! forms can be used. The coefficient may either be a constant or
!! a shear-dependent form. The biharmonic is determined by twice
!! taking the divergence of an appropriately defined stress tensor.
!! The Laplacian is determined by doing so once.
!! To work, the following fields must be set outside of the usual
!! is to ie range before this subroutine is called:
!! v[is-2,is-1,ie+1,ie+2], u[is-2,is-1,ie+1,ie+2], and h[is-1,ie+1],
!! with a similarly sized halo in the y-direction.
subroutine horizontal_viscosity(u, v, h, diffu, diffv, MEKE, VarMix, G, GV, CS, OBC)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in) :: u !< The zonal velocity, in m s-1
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: v !< The meridional velocity, in m s-1
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(out) :: diffu
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(out) :: diffv
type(MEKE_type), pointer :: MEKE
type(VarMix_CS), pointer :: VarMix
type(hor_visc_CS), pointer :: CS
type(ocean_OBC_type), pointer, optional :: OBC
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
intent(in) :: u !< The zonal velocity, in m s-1.
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
intent(in) :: v !< The meridional velocity, in m s-1.
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: h !< Layer thicknesses, in H
!! (usually m or kg m-2).
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
intent(out) :: diffu !< Zonal acceleration due to convergence of
!! along-coordinate stress tensor (m/s2)
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
intent(out) :: diffv !< Meridional acceleration due to convergence
!! of along-coordinate stress tensor (m/s2).
type(MEKE_type), pointer :: MEKE !< Pointer to a structure containing fields
!! related to Mesoscale Eddy Kinetic Energy.
type(VarMix_CS), pointer :: VarMix !< Pointer to a structure with fields that
!! specify the spatially variable viscosities
type(hor_visc_CS), pointer :: CS !< Pontrol structure returned by a previous
!! call to hor_visc_init.
type(ocean_OBC_type), pointer, optional :: OBC !< Pointer to an open boundary condition type

! Arguments:
! (in) u - zonal velocity (m/s)
Expand Down Expand Up @@ -929,13 +950,18 @@ subroutine horizontal_viscosity(u, v, h, diffu, diffv, MEKE, VarMix, G, GV, CS,

end subroutine horizontal_viscosity


!> This subroutine allocates space for and calculates static variables
!! used by this module. The metrics may be 0, 1, or 2-D arrays,
!! while fields like the background viscosities are 2-D arrays.
!! ALLOC is a macro defined in MOM_memory.h to either allocate
!! for dynamic memory, or do nothing when using static memory.
subroutine hor_visc_init(Time, G, param_file, diag, CS)
type(time_type), intent(in) :: Time
type(ocean_grid_type), intent(inout) :: 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
type(hor_visc_CS), pointer :: CS
type(time_type), intent(in) :: Time !< current model time.
type(ocean_grid_type), intent(inout) :: 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 to regulate diagnostic output.
type(hor_visc_CS), pointer :: CS !< pointer to the control structure for this module

! This subroutine allocates space for and calculates static variables
! used by this module. The metrics may be 0, 1, or 2-D arrays,
Expand Down
Loading

0 comments on commit 40a7aed

Please sign in to comment.