Skip to content

Commit

Permalink
Documented 212 length and velocity variable units
Browse files Browse the repository at this point in the history
  Changed comments to use the square bracket notation to document the units of
about 212 variables, including numerous lengths, velocities and areas.  Only
comments have been changed and all answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Feb 1, 2019
1 parent 6298e8f commit cc1e58b
Show file tree
Hide file tree
Showing 16 changed files with 213 additions and 213 deletions.
22 changes: 11 additions & 11 deletions src/SIS_continuity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -67,9 +67,9 @@ subroutine ice_continuity(u, v, hin, h, uh, vh, dt, G, IG, CS)
type(SIS_hor_grid_type), intent(inout) :: G !< The horizontal grid type
type(ice_grid_type), intent(inout) :: IG !< The sea-ice specific grid type
real, dimension(SZIB_(G),SZJ_(G)), &
intent(in) :: u !< Zonal ice velocity, in m s-1.
intent(in) :: u !< Zonal ice velocity [m s-1].
real, dimension(SZI_(G),SZJB_(G)), &
intent(in) :: v !< Meridional ice velocity, in m s-1.
intent(in) :: v !< Meridional ice velocity [m s-1].
real, dimension(SZI_(G),SZJ_(G),SZCAT_(IG)), &
intent(in) :: hin !< Initial ice or snow thickness by category [H ~> kg m-2].
real, dimension(SZI_(G),SZJ_(G),SZCAT_(IG)), &
Expand Down Expand Up @@ -211,8 +211,8 @@ end subroutine ice_continuity
subroutine summed_continuity(u, v, h_in, h, uh, vh, dt, G, IG, CS, h_ice)
type(SIS_hor_grid_type), intent(inout) :: G !< The horizontal grid type
type(ice_grid_type), intent(inout) :: IG !< The sea-ice specific grid type
real, dimension(SZIB_(G),SZJ_(G)), intent(in) :: u !< Zonal ice velocity, in m s-1.
real, dimension(SZI_(G),SZJB_(G)), intent(in) :: v !< Meridional ice velocity, in m s-1.
real, dimension(SZIB_(G),SZJ_(G)), intent(in) :: u !< Zonal ice velocity [m s-1].
real, dimension(SZI_(G),SZJB_(G)), intent(in) :: v !< Meridional ice velocity [m s-1].
real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Initial total ice and snow mass per
!! unit cell area [H ~> kg m-2].
real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: h !< Total ice and snow mass per unit cell
Expand All @@ -232,7 +232,7 @@ subroutine summed_continuity(u, v, h_in, h, uh, vh, dt, G, IG, CS, h_ice)
type(loop_bounds_type) :: LB ! A structure with the active loop bounds.
real, dimension(SZIB_(G),SZJ_(G)) :: uh_ice ! Ice mass flux through zonal faces = u*h*dy
! [H m2 s-1 ~> kg s-1].
real, dimension(SZI_(G),SZJB_(G)) :: vh_ice ! Ice mass flux through meridional faces = v*h*dx
real, dimension(SZI_(G),SZJB_(G)) :: vh_ice ! Ice mass flux through meridional faces = v*h*dx
! [H m2 s-1 ~> kg s-1].
real :: h_up
integer :: is, ie, js, je, stensil
Expand Down Expand Up @@ -723,7 +723,7 @@ subroutine zonal_mass_flux(u, dt, G, IG, CS, LB, h_in, uh, htot_in, uh_tot)
type(SIS_hor_grid_type), intent(inout) :: G !< The horizontal grid type
type(ice_grid_type), intent(inout) :: IG !< The sea-ice specific grid type
real, dimension(SZIB_(G),SZJ_(G)), &
intent(in) :: u !< Zonal ice velocity, in m s-1.
intent(in) :: u !< Zonal ice velocity [m s-1].
real, intent(in) :: dt !< Time increment [s]
type(SIS_continuity_CS), pointer :: CS !< The control structure returned by a
!! previous call to SIS_continuity_init.
Expand Down Expand Up @@ -755,7 +755,7 @@ subroutine zonal_mass_flux(u, dt, G, IG, CS, LB, h_in, uh, htot_in, uh_tot)
real :: curv_3 ! A measure of the thickness curvature over a grid length,
! with the same units as h_in.
! real :: h_marg ! The marginal thickness of a flux [H ~> kg m-2].
real :: dx_E, dx_W ! Effective x-grid spacings to the east and west, in m.
real :: dx_E, dx_W ! Effective x-grid spacings to the east and west [m].
integer :: i, j, k, ish, ieh, jsh, jeh, nz

ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = IG%CatIce
Expand Down Expand Up @@ -845,7 +845,7 @@ subroutine meridional_mass_flux(v, dt, G, IG, CS, LB, h_in, vh, htot_in, vh_tot)
type(SIS_hor_grid_type), intent(inout) :: G !< The horizontal grid type
type(ice_grid_type), intent(inout) :: IG !< The sea-ice specific grid type
real, dimension(SZI_(G),SZJB_(G)), &
intent(in) :: v !< Meridional ice velocity, in m s-1.
intent(in) :: v !< Meridional ice velocity [m s-1].
real, intent(in) :: dt !< Time increment [s]
type(SIS_continuity_CS), pointer :: CS !< The control structure returned by a
!! previous call to SIS_continuity_init.
Expand All @@ -870,14 +870,14 @@ subroutine meridional_mass_flux(v, dt, G, IG, CS, LB, h_in, vh, htot_in, vh_tot)
real, dimension(SZI_(G),SZJ_(G)) :: &
htot, & ! The total thickness summed across categories [H ~> kg m-2].
I_htot, & ! The inverse of htot or 0 [H-1 ~> m2 kg-1].
hl, hr ! Left and right face thicknesses, in m.
hl, hr ! Left and right face thicknesses [m].
real, dimension(SZI_(G)) :: &
vhtot ! The total transports [H m2 s-1 ~> kg s-1].
real :: CFL ! The CFL number based on the local velocity and grid spacing, ND.
real :: curv_3 ! A measure of the thickness curvature over a grid length,
! with the same units as h_in.
real :: h_marg ! The marginal thickness of a flux, in m.
real :: dy_N, dy_S ! Effective y-grid spacings to the north and south, in m.
real :: h_marg ! The marginal thickness of a flux [m].
real :: dy_N, dy_S ! Effective y-grid spacings to the north and south [m].
integer :: i, j, k, ish, ieh, jsh, jeh, nz

ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = IG%CatIce
Expand Down
2 changes: 1 addition & 1 deletion src/SIS_ctrl_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -187,7 +187,7 @@ subroutine ice_diagnostics_init(IOF, OSS, FIA, G, IG, diag, Time, Cgrid)
!! sea ice velocities. The default is true.

real, dimension(G%isc:G%iec,G%jsc:G%jec) :: tmp_diag ! A temporary diagnostic array
real :: I_area_Earth ! The inverse of the area of the sphere, in m-2.
real :: I_area_Earth ! The inverse of the area of the sphere [m-2].
real, parameter :: missing = -1e34 ! The fill value for missing data.
integer :: id_geo_lon, id_geo_lat, id_sin_rot, id_cos_rot, id_cell_area
logical :: Cgrid_dyn
Expand Down
10 changes: 5 additions & 5 deletions src/SIS_dyn_bgrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -252,15 +252,15 @@ subroutine SIS_B_dynamics(ci, misp, mice, ui, vi, uo, vo, &
real, dimension(SZI_(G),SZJ_(G)), intent(in ) :: misp !< Mass per unit ocean area of sea ice,
!! snow and melt pond water [kg m-2]
real, dimension(SZI_(G),SZJ_(G)), intent(in ) :: mice !< Mass per unit ocean area of sea ice [kg m-2]
real, dimension(SZIB_(G),SZJB_(G)), intent(inout) :: ui !< Zonal ice velocity in m s-1
real, dimension(SZIB_(G),SZJB_(G)), intent(inout) :: vi !< Meridional ice velocity in m s-1
real, dimension(SZIB_(G),SZJB_(G)), intent(in ) :: uo !< Zonal ocean velocity in m s-1
real, dimension(SZIB_(G),SZJB_(G)), intent(in ) :: vo !< Meridional ocean velocity in m s-1
real, dimension(SZIB_(G),SZJB_(G)), intent(inout) :: ui !< Zonal ice velocity [m s-1]
real, dimension(SZIB_(G),SZJB_(G)), intent(inout) :: vi !< Meridional ice velocity [m s-1]
real, dimension(SZIB_(G),SZJB_(G)), intent(in ) :: uo !< Zonal ocean velocity [m s-1]
real, dimension(SZIB_(G),SZJB_(G)), intent(in ) :: vo !< Meridional ocean velocity [m s-1]
real, dimension(SZIB_(G),SZJB_(G)), intent(in ) :: fxat !< Zonal air stress on ice [Pa]
real, dimension(SZIB_(G),SZJB_(G)), intent(in ) :: fyat !< Meridional air stress on ice [Pa]
real, dimension(SZI_(G),SZJ_(G)), intent(in ) :: sea_lev !< The height of the sea level, including
!! contributions from non-levitating ice from
!! an earlier time step, in m.
!! an earlier time step [m].
real, dimension(SZIB_(G),SZJB_(G)), intent( out) :: fxoc !< Zonal ice stress on ocean [Pa]
real, dimension(SZIB_(G),SZJB_(G)), intent( out) :: fyoc !< Meridional ice stress on ocean [Pa]
logical, intent(in ) :: do_ridging !< If true, the ice can ridge
Expand Down
Loading

0 comments on commit cc1e58b

Please sign in to comment.