Skip to content

Commit

Permalink
Document remapping function variable units
Browse files Browse the repository at this point in the history
  Added or amended comments to document the mostly arbitrary units of about 108
variables in 5 low-level remapping modules.  Only comments are changed and
all answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Feb 14, 2024
1 parent 0fb905f commit 00d88d2
Show file tree
Hide file tree
Showing 5 changed files with 128 additions and 112 deletions.
10 changes: 5 additions & 5 deletions src/ALE/P1M_functions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ subroutine P1M_interpolation( N, h, u, edge_values, ppoly_coef, h_neglect, answe

! Local variables
integer :: k ! loop index
real :: u0_l, u0_r ! edge values (left and right)
real :: u0_l, u0_r ! edge values (left and right) [A]

! Bound edge values (routine found in 'edge_values.F90')
call bound_edge_values( N, h, u, edge_values, h_neglect, answer_date=answer_date )
Expand Down Expand Up @@ -74,10 +74,10 @@ subroutine P1M_boundary_extrapolation( N, h, u, edge_values, ppoly_coef )
real, dimension(:,:), intent(inout) :: ppoly_coef !< coefficients of piecewise polynomials, mainly [A]

! Local variables
real :: u0, u1 ! cell averages
real :: h0, h1 ! corresponding cell widths
real :: slope ! retained PLM slope
real :: u0_l, u0_r ! edge values
real :: u0, u1 ! cell averages [A]
real :: h0, h1 ! corresponding cell widths [H]
real :: slope ! retained PLM slope [A]
real :: u0_l, u0_r ! edge values [A]

! -----------------------------------------
! Left edge value in the left boundary cell
Expand Down
6 changes: 3 additions & 3 deletions src/ALE/PCM_functions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -17,11 +17,11 @@ module PCM_functions
!! defining 'grid' and 'ppoly'. No consistency check is performed.
subroutine PCM_reconstruction( N, u, edge_values, ppoly_coef )
integer, intent(in) :: N !< Number of cells
real, dimension(:), intent(in) :: u !< cell averages
real, dimension(:), intent(in) :: u !< cell averages in arbitrary units [A]
real, dimension(:,:), intent(inout) :: edge_values !< Edge value of polynomial,
!! with the same units as u.
!! with the same units as u [A].
real, dimension(:,:), intent(inout) :: ppoly_coef !< Coefficients of polynomial,
!! with the same units as u.
!! with the same units as u [A].

! Local variables
integer :: k
Expand Down
122 changes: 64 additions & 58 deletions src/ALE/PLM_functions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,20 +16,21 @@ module PLM_functions

contains

!> Returns a limited PLM slope following White and Adcroft, 2008. [units of u]
!> Returns a limited PLM slope following White and Adcroft, 2008, in the same arbitrary
!! units [A] as the input values.
!! Note that this is not the same as the Colella and Woodward method.
real elemental pure function PLM_slope_wa(h_l, h_c, h_r, h_neglect, u_l, u_c, u_r)
real, intent(in) :: h_l !< Thickness of left cell [units of grid thickness]
real, intent(in) :: h_c !< Thickness of center cell [units of grid thickness]
real, intent(in) :: h_r !< Thickness of right cell [units of grid thickness]
real, intent(in) :: h_neglect !< A negligible thickness [units of grid thickness]
real, intent(in) :: u_l !< Value of left cell [units of u]
real, intent(in) :: u_c !< Value of center cell [units of u]
real, intent(in) :: u_r !< Value of right cell [units of u]
real, intent(in) :: h_l !< Thickness of left cell in arbitrary grid thickness units [H]
real, intent(in) :: h_c !< Thickness of center cell in arbitrary grid thickness units [H]
real, intent(in) :: h_r !< Thickness of right cell in arbitrary grid thickness units [H]
real, intent(in) :: h_neglect !< A negligible thickness [H]
real, intent(in) :: u_l !< Value of left cell in arbitrary units [A]
real, intent(in) :: u_c !< Value of center cell in arbitrary units [A]
real, intent(in) :: u_r !< Value of right cell in arbitrary units [A]
! Local variables
real :: sigma_l, sigma_c, sigma_r ! Left, central and right slope estimates as
! differences across the cell [units of u]
real :: u_min, u_max ! Minimum and maximum value across cell [units of u]
! differences across the cell [A]
real :: u_min, u_max ! Minimum and maximum value across cell [A]

! Side differences
sigma_r = u_r - u_c
Expand Down Expand Up @@ -63,20 +64,21 @@ real elemental pure function PLM_slope_wa(h_l, h_c, h_r, h_neglect, u_l, u_c, u_

end function PLM_slope_wa

!> Returns a limited PLM slope following Colella and Woodward 1984.
!> Returns a limited PLM slope following Colella and Woodward 1984, in the same
!! arbitrary units as the input values [A].
real elemental pure function PLM_slope_cw(h_l, h_c, h_r, h_neglect, u_l, u_c, u_r)
real, intent(in) :: h_l !< Thickness of left cell [units of grid thickness]
real, intent(in) :: h_c !< Thickness of center cell [units of grid thickness]
real, intent(in) :: h_r !< Thickness of right cell [units of grid thickness]
real, intent(in) :: h_neglect !< A negligible thickness [units of grid thickness]
real, intent(in) :: u_l !< Value of left cell [units of u]
real, intent(in) :: u_c !< Value of center cell [units of u]
real, intent(in) :: u_r !< Value of right cell [units of u]
real, intent(in) :: h_l !< Thickness of left cell in arbitrary grid thickness units [H]
real, intent(in) :: h_c !< Thickness of center cell in arbitrary grid thickness units [H]
real, intent(in) :: h_r !< Thickness of right cell in arbitrary grid thickness units [H]
real, intent(in) :: h_neglect !< A negligible thickness [H]
real, intent(in) :: u_l !< Value of left cell in arbitrary units [A]
real, intent(in) :: u_c !< Value of center cell in arbitrary units [A]
real, intent(in) :: u_r !< Value of right cell in arbitrary units [A]
! Local variables
real :: sigma_l, sigma_c, sigma_r ! Left, central and right slope estimates as
! differences across the cell [units of u]
real :: u_min, u_max ! Minimum and maximum value across cell [units of u]
real :: h_cn ! Thickness of center cell [units of grid thickness]
! differences across the cell [A]
real :: u_min, u_max ! Minimum and maximum value across cell [A]
real :: h_cn ! Thickness of center cell [H]

h_cn = h_c + h_neglect

Expand Down Expand Up @@ -117,18 +119,19 @@ real elemental pure function PLM_slope_cw(h_l, h_c, h_r, h_neglect, u_l, u_c, u_

end function PLM_slope_cw

!> Returns a limited PLM slope following Colella and Woodward 1984.
!> Returns a limited PLM slope following Colella and Woodward 1984, in the same
!! arbitrary units as the input values [A].
real elemental pure function PLM_monotonized_slope(u_l, u_c, u_r, s_l, s_c, s_r)
real, intent(in) :: u_l !< Value of left cell [units of u]
real, intent(in) :: u_c !< Value of center cell [units of u]
real, intent(in) :: u_r !< Value of right cell [units of u]
real, intent(in) :: s_l !< PLM slope of left cell [units of u]
real, intent(in) :: s_c !< PLM slope of center cell [units of u]
real, intent(in) :: s_r !< PLM slope of right cell [units of u]
real, intent(in) :: u_l !< Value of left cell in arbitrary units [A]
real, intent(in) :: u_c !< Value of center cell in arbitrary units [A]
real, intent(in) :: u_r !< Value of right cell in arbitrary units [A]
real, intent(in) :: s_l !< PLM slope of left cell [A]
real, intent(in) :: s_c !< PLM slope of center cell [A]
real, intent(in) :: s_r !< PLM slope of right cell [A]
! Local variables
real :: e_r, e_l, edge ! Right, left and temporary edge values [units of u]
real :: almost_two ! The number 2, almost.
real :: slp ! Magnitude of PLM central slope [units of u]
real :: e_r, e_l, edge ! Right, left and temporary edge values [A]
real :: almost_two ! The number 2, almost [nondim]
real :: slp ! Magnitude of PLM central slope [A]

almost_two = 2. * ( 1. - epsilon(s_c) )

Expand All @@ -155,17 +158,18 @@ real elemental pure function PLM_monotonized_slope(u_l, u_c, u_r, s_l, s_c, s_r)

end function PLM_monotonized_slope

!> Returns a PLM slope using h2 extrapolation from a cell to the left.
!> Returns a PLM slope using h2 extrapolation from a cell to the left, in the same
!! arbitrary units as the input values [A].
!! Use the negative to extrapolate from the cell to the right.
real elemental pure function PLM_extrapolate_slope(h_l, h_c, h_neglect, u_l, u_c)
real, intent(in) :: h_l !< Thickness of left cell [units of grid thickness]
real, intent(in) :: h_c !< Thickness of center cell [units of grid thickness]
real, intent(in) :: h_neglect !< A negligible thickness [units of grid thickness]
real, intent(in) :: u_l !< Value of left cell [units of u]
real, intent(in) :: u_c !< Value of center cell [units of u]
real, intent(in) :: h_l !< Thickness of left cell in arbitrary grid thickness units [H]
real, intent(in) :: h_c !< Thickness of center cell in arbitrary grid thickness units [H]
real, intent(in) :: h_neglect !< A negligible thickness [H]
real, intent(in) :: u_l !< Value of left cell in arbitrary units [A]
real, intent(in) :: u_c !< Value of center cell in arbitrary units [A]
! Local variables
real :: left_edge ! Left edge value [units of u]
real :: hl, hc ! Left and central cell thicknesses [units of grid thickness]
real :: left_edge ! Left edge value [A]
real :: hl, hc ! Left and central cell thicknesses [H]

! Avoid division by zero for vanished cells
hl = h_l + h_neglect
Expand All @@ -185,24 +189,26 @@ end function PLM_extrapolate_slope
!! defining 'grid' and 'ppoly'. No consistency check is performed here.
subroutine PLM_reconstruction( N, h, u, edge_values, ppoly_coef, h_neglect )
integer, intent(in) :: N !< Number of cells
real, dimension(:), intent(in) :: h !< cell widths (size N)
real, dimension(:), intent(in) :: u !< cell averages (size N)
real, dimension(:), intent(in) :: h !< cell widths (size N) [H]
real, dimension(:), intent(in) :: u !< cell averages (size N) in arbitrary units [A]
real, dimension(:,:), intent(inout) :: edge_values !< edge values of piecewise polynomials,
!! with the same units as u.
!! with the same units as u [A].
real, dimension(:,:), intent(inout) :: ppoly_coef !< coefficients of piecewise polynomials, mainly
!! with the same units as u.
!! with the same units as u [A].
real, optional, intent(in) :: h_neglect !< A negligibly small width for
!! the purpose of cell reconstructions
!! in the same units as h
!! in the same units as h [H]

! Local variables
integer :: k ! loop index
real :: u_l, u_r ! left and right cell averages
real :: slope ! retained PLM slope
real :: e_r, edge
real :: almost_one
real, dimension(N) :: slp, mslp
real :: hNeglect
integer :: k ! loop index
real :: u_l, u_r ! left and right cell averages [A]
real :: slope ! retained PLM slope for a normalized cell width [A]
real :: e_r ! The edge value in the neighboring cell [A]
real :: edge ! The projected edge value in the cell [A]
real :: almost_one ! A value that is slightly smaller than 1 [nondim]
real, dimension(N) :: slp ! The first guess at the normalized tracer slopes [A]
real, dimension(N) :: mslp ! The monotonized normalized tracer slopes [A]
real :: hNeglect ! A negligibly small width used in cell reconstructions [H]

hNeglect = hNeglect_dflt ; if (present(h_neglect)) hNeglect = h_neglect

Expand Down Expand Up @@ -265,18 +271,18 @@ end subroutine PLM_reconstruction
!! defining 'grid' and 'ppoly'. No consistency check is performed here.
subroutine PLM_boundary_extrapolation( N, h, u, edge_values, ppoly_coef, h_neglect )
integer, intent(in) :: N !< Number of cells
real, dimension(:), intent(in) :: h !< cell widths (size N)
real, dimension(:), intent(in) :: u !< cell averages (size N)
real, dimension(:), intent(in) :: h !< cell widths (size N) [H]
real, dimension(:), intent(in) :: u !< cell averages (size N) in arbitrary units [A]
real, dimension(:,:), intent(inout) :: edge_values !< edge values of piecewise polynomials,
!! with the same units as u.
!! with the same units as u [A].
real, dimension(:,:), intent(inout) :: ppoly_coef !< coefficients of piecewise polynomials, mainly
!! with the same units as u.
!! with the same units as u [A].
real, optional, intent(in) :: h_neglect !< A negligibly small width for
!! the purpose of cell reconstructions
!! in the same units as h
!! in the same units as h [H]
! Local variables
real :: slope ! retained PLM slope
real :: hNeglect
real :: slope ! retained PLM slope for a normalized cell width [A]
real :: hNeglect ! A negligibly small width used in cell reconstructions [H]

hNeglect = hNeglect_dflt ; if (present(h_neglect)) hNeglect = h_neglect

Expand Down
32 changes: 17 additions & 15 deletions src/ALE/PPM_functions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,15 +28,15 @@ module PPM_functions
subroutine PPM_reconstruction( N, h, u, edge_values, ppoly_coef, h_neglect, answer_date)
integer, intent(in) :: N !< Number of cells
real, dimension(N), intent(in) :: h !< Cell widths [H]
real, dimension(N), intent(in) :: u !< Cell averages [A]
real, dimension(N), intent(in) :: u !< Cell averages in arbitrary coordinates [A]
real, dimension(N,2), intent(inout) :: edge_values !< Edge values [A]
real, dimension(N,3), intent(inout) :: ppoly_coef !< Polynomial coefficients, mainly [A]
real, optional, intent(in) :: h_neglect !< A negligibly small width [H]
integer, optional, intent(in) :: answer_date !< The vintage of the expressions to use

! Local variables
integer :: k ! Loop index
real :: edge_l, edge_r ! Edge values (left and right)
real :: edge_l, edge_r ! Edge values (left and right) [A]

! PPM limiter
call PPM_limiter_standard( N, h, u, edge_values, h_neglect, answer_date=answer_date )
Expand Down Expand Up @@ -69,9 +69,9 @@ subroutine PPM_limiter_standard( N, h, u, edge_values, h_neglect, answer_date )

! Local variables
integer :: k ! Loop index
real :: u_l, u_c, u_r ! Cell averages (left, center and right)
real :: edge_l, edge_r ! Edge values (left and right)
real :: expr1, expr2
real :: u_l, u_c, u_r ! Cell averages (left, center and right) [A]
real :: edge_l, edge_r ! Edge values (left and right) [A]
real :: expr1, expr2 ! Temporary expressions [A2]

! Bound edge values
call bound_edge_values( N, h, u, edge_values, h_neglect, answer_date=answer_date )
Expand Down Expand Up @@ -135,8 +135,8 @@ subroutine PPM_monotonicity( N, u, edge_values )
real, dimension(:,:), intent(inout) :: edge_values !< Potentially modified edge values [A]

! Local variables
integer :: k ! Loop index
real :: a6,da ! scalar temporaries
integer :: k ! Loop index
real :: a6, da ! Normalized scalar curvature and slope [A]

! Loop on interior cells to impose monotonicity
! Eq. 1.10 of (Colella & Woodward, JCP 84)
Expand Down Expand Up @@ -195,14 +195,16 @@ subroutine PPM_boundary_extrapolation( N, h, u, edge_values, ppoly_coef, h_negle

! Local variables
integer :: i0, i1
real :: u0, u1
real :: h0, h1
real :: a, b, c
real :: u0_l, u0_r
real :: u1_l, u1_r
real :: slope
real :: exp1, exp2
real :: hNeglect
real :: u0, u1 ! Average concentrations in the two neighboring cells [A]
real :: h0, h1 ! Thicknesses of the two neighboring cells [H]
real :: a, b, c ! An edge value, normalized slope and normalized curvature
! of a reconstructed distribution [A]
real :: u0_l, u0_r ! Edge values of a neighboring cell [A]
real :: u1_l, u1_r ! Neighboring cell slopes renormalized by the thickness of
! the cell being worked on [A]
real :: slope ! The normalized slope [A]
real :: exp1, exp2 ! Temporary expressions [A2]
real :: hNeglect ! A negligibly small width used in cell reconstructions [H]

hNeglect = hNeglect_dflt ; if (present(h_neglect)) hNeglect = h_neglect

Expand Down
Loading

0 comments on commit 00d88d2

Please sign in to comment.