Skip to content

Commit

Permalink
Documented units of 50 grid variables
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 50 dyn_horgrid or diagnostic variables.  Only comments have been changed
and all answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Dec 22, 2018
1 parent 00b3289 commit 026f7d8
Show file tree
Hide file tree
Showing 4 changed files with 91 additions and 88 deletions.
72 changes: 36 additions & 36 deletions src/core/MOM_forcing_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -141,8 +141,8 @@ module MOM_forcing_type
! land ice-shelf related inputs
real, pointer, dimension(:,:) :: ustar_shelf => NULL() !< Friction velocity under ice-shelves [Z s-1 ~> m s-1].
!! as computed by the ocean at the previous time step.
real, pointer, dimension(:,:) :: frac_shelf_h => NULL() !< Fractional ice shelf coverage of h-cells, nondimensional
!! cells, nondimensional from 0 to 1. This is only
real, pointer, dimension(:,:) :: frac_shelf_h => NULL() !< Fractional ice shelf coverage of
!! h-cells, nondimensional from 0 to 1. This is only
!! associated if ice shelves are enabled, and are
!! exactly 0 away from shelves or on land.
real, pointer, dimension(:,:) :: iceshelf_melt => NULL() !< Ice shelf melt rate (positive)
Expand Down Expand Up @@ -773,44 +773,44 @@ subroutine extractFluxes2d(G, GV, fluxes, optics, nsw, dt, FluxRescaleDepth, &
netMassInOut, netMassOut, net_heat, Net_salt, Pen_SW_bnd, tv, &
aggregate_FW)

type(ocean_grid_type), intent(in) :: G !< ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(forcing), intent(inout) :: fluxes !< structure containing pointers to forcing.
type(optics_type), pointer :: optics !< pointer to optics
integer, intent(in) :: nsw !< number of bands of penetrating SW
real, intent(in) :: dt !< time step [s]
real, intent(in) :: FluxRescaleDepth !< min ocean depth before fluxes
!! are scaled away [H ~> m or kg m-2]
type(ocean_grid_type), intent(in) :: G !< ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(forcing), intent(inout) :: fluxes !< structure containing pointers to forcing.
type(optics_type), pointer :: optics !< pointer to optics
integer, intent(in) :: nsw !< number of bands of penetrating SW
real, intent(in) :: dt !< time step [s]
real, intent(in) :: FluxRescaleDepth !< min ocean depth before fluxes
!! are scaled away [H ~> m or kg m-2]
logical, intent(in) :: useRiverHeatContent !< logical for river heat content
logical, intent(in) :: useCalvingHeatContent !< logical for calving heat content
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: h !< layer thickness [H ~> m or kg m-2]
intent(in) :: h !< layer thickness [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: T !< layer temperatures [degC]
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: netMassInOut !< net mass flux (non-Bouss) or volume flux
!! (if Bouss) of water in/out of ocean over
!! a time step [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: netMassOut !< net mass flux (non-Bouss) or volume flux
!! (if Bouss) of water leaving ocean surface
!! over a time step [H ~> m or kg m-2].
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: net_heat !< net heat at the surface accumulated over a
!! time step associated with coupler + restore.
!! Exclude two terms from net_heat:
!! (1) downwelling (penetrative) SW,
!! (2) evaporation heat content,
!! (since do not yet know temperature of evap).
!! [degC H ~> degC m or degC kg m-2]
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: net_salt !< surface salt flux into the ocean accumulated
!! over a time step [ppt H ~> ppt m or ppt kg m-2]
real, dimension(:,:,:), intent(out) :: pen_SW_bnd !< penetrating shortwave flux, split into bands.
!! [degC H ~> degC m or degC kg m-2] array size
!! nsw x SZI_(G), where nsw=number of SW bands in
!! pen_SW_bnd. This heat flux is not in net_heat.
type(thermo_var_ptrs), intent(inout) :: tv !< structure containing pointers to available
!! thermodynamic fields. Here it is used to keep
!! track of the heat flux associated with net
!! mass fluxes into the ocean.
logical, intent(in) :: aggregate_FW !< For determining how to aggregate the forcing.
intent(in) :: T !< layer temperatures [degC]
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: netMassInOut !< net mass flux (non-Bouss) or volume flux
!! (if Bouss) of water in/out of ocean over
!! a time step [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: netMassOut !< net mass flux (non-Bouss) or volume flux
!! (if Bouss) of water leaving ocean surface
!! over a time step [H ~> m or kg m-2].
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: net_heat !< net heat at the surface accumulated over a
!! time step associated with coupler + restore.
!! Exclude two terms from net_heat:
!! (1) downwelling (penetrative) SW,
!! (2) evaporation heat content,
!! (since do not yet know temperature of evap).
!! [degC H ~> degC m or degC kg m-2]
real, dimension(SZI_(G),SZJ_(G)), intent(out) :: net_salt !< surface salt flux into the ocean accumulated
!! over a time step [ppt H ~> ppt m or ppt kg m-2]
real, dimension(:,:,:), intent(out) :: pen_SW_bnd !< penetrating shortwave flux, split into bands.
!! [degC H ~> degC m or degC kg m-2] array size
!! nsw x SZI_(G), where nsw=number of SW bands in
!! pen_SW_bnd. This heat flux is not in net_heat.
type(thermo_var_ptrs), intent(inout) :: tv !< structure containing pointers to available
!! thermodynamic fields. Here it is used to keep
!! track of the heat flux associated with net
!! mass fluxes into the ocean.
logical, intent(in) :: aggregate_FW !< For determining how to aggregate the forcing.

integer :: j
!$OMP parallel do default(none) shared(G, GV, fluxes, optics, nsw,dt,FluxRescaleDepth, &
Expand Down
17 changes: 10 additions & 7 deletions src/diagnostics/MOM_diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1331,13 +1331,16 @@ subroutine post_transport_diagnostics(G, GV, uhtr, vhtr, h, IDs, diag_pre_dyn, d
!! the transports to depth space
type(tracer_registry_type), pointer :: Reg !< Pointer to the tracer registry

real, dimension(SZIB_(G), SZJ_(G)) :: umo2d ! Diagnostics of integrated mass transport, in kg s-1
real, dimension(SZI_(G), SZJB_(G)) :: vmo2d ! Diagnostics of integrated mass transport, in kg s-1
real, dimension(SZIB_(G), SZJ_(G), SZK_(G)) :: umo ! Diagnostics of layer mass transport, in kg s-1
real, dimension(SZI_(G), SZJB_(G), SZK_(G)) :: vmo ! Diagnostics of layer mass transport, in kg s-1
real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_tend ! Change in layer thickness due to dynamics m s-1
real :: Idt
real :: H_to_kg_m2_dt ! A conversion factor from accumulated transports to fluxes, in kg m-2 H-1 s-1.
! Local variables
real, dimension(SZIB_(G), SZJ_(G)) :: umo2d ! Diagnostics of integrated mass transport [kg s-1]
real, dimension(SZI_(G), SZJB_(G)) :: vmo2d ! Diagnostics of integrated mass transport [kg s-1]
real, dimension(SZIB_(G), SZJ_(G), SZK_(G)) :: umo ! Diagnostics of layer mass transport [kg s-1]
real, dimension(SZI_(G), SZJB_(G), SZK_(G)) :: vmo ! Diagnostics of layer mass transport [kg s-1]
real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_tend ! Change in layer thickness due to dynamics
! [H s-1 ~> m s-1 or kg m-2 s-1].
real :: Idt ! The inverse of the time interval [s-1]
real :: H_to_kg_m2_dt ! A conversion factor from accumulated transports to fluxes
! [kg m-2 H-1 s-1 ~> kg m-3 s-1 or s-1].
integer :: i, j, k, is, ie, js, je, nz
is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = G%ke

Expand Down
2 changes: 1 addition & 1 deletion src/diagnostics/MOM_wave_structure.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ module MOM_wave_structure
!< Vertical profile of the magnitude of horizontal velocity,
!! (u^2+v^2)^0.5, averaged over a period [m s-1].
real, allocatable, dimension(:,:,:) :: z_depths
!< Depths of layer interfaces, in m.
!< Depths of layer interfaces [m].
real, allocatable, dimension(:,:,:) :: N2
!< Squared buoyancy frequency at each interface [s-2].
integer, allocatable, dimension(:,:):: num_intfaces
Expand Down
88 changes: 44 additions & 44 deletions src/framework/MOM_dyn_horgrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -67,56 +67,56 @@ module MOM_dyn_horgrid
!! during the course of the run via calls to set_first_direction.

real, allocatable, dimension(:,:) :: &
mask2dT, & !< 0 for land points and 1 for ocean points on the h-grid. Nd.
geoLatT, & !< The geographic latitude at q points in degrees of latitude or m.
geoLonT, & !< The geographic longitude at q points in degrees of longitude or m.
dxT, & !< dxT is delta x at h points, in m.
IdxT, & !< 1/dxT in m-1.
dyT, & !< dyT is delta y at h points, in m, and IdyT is 1/dyT in m-1.
IdyT, & !< dyT is delta y at h points, in m, and IdyT is 1/dyT in m-1.
areaT, & !< The area of an h-cell, in m2.
IareaT !< 1/areaT, in m-2.
mask2dT, & !< 0 for land points and 1 for ocean points on the h-grid [nondim].
geoLatT, & !< The geographic latitude at q points [degrees of latitude] or [m].
geoLonT, & !< The geographic longitude at q points [degrees of longitude] or [m].
dxT, & !< dxT is delta x at h points [m].
IdxT, & !< 1/dxT [m-1].
dyT, & !< dyT is delta y at h points [m].
IdyT, & !< IdyT is 1/dyT [m-1].
areaT, & !< The area of an h-cell [m2].
IareaT !< 1/areaT [m-2].
real, allocatable, dimension(:,:) :: sin_rot
!< The sine of the angular rotation between the local model grid's northward
!! and the true northward directions.
!! and the true northward directions [nondim].
real, allocatable, dimension(:,:) :: cos_rot
!< The cosine of the angular rotation between the local model grid's northward
!! and the true northward directions.
!! and the true northward directions [nondim].

real, allocatable, dimension(:,:) :: &
mask2dCu, & !< 0 for boundary points and 1 for ocean points on the u grid. Nondim.
geoLatCu, & !< The geographic latitude at u points in degrees of latitude or m.
geoLonCu, & !< The geographic longitude at u points in degrees of longitude or m.
dxCu, & !< dxCu is delta x at u points, in m.
IdxCu, & !< 1/dxCu in m-1.
dyCu, & !< dyCu is delta y at u points, in m.
IdyCu, & !< 1/dyCu in m-1.
dy_Cu, & !< The unblocked lengths of the u-faces of the h-cell in m.
IareaCu, & !< The masked inverse areas of u-grid cells in m2.
areaCu !< The areas of the u-grid cells in m2.
mask2dCu, & !< 0 for boundary points and 1 for ocean points on the u grid [nondim].
geoLatCu, & !< The geographic latitude at u points [degrees of latitude] or [m].
geoLonCu, & !< The geographic longitude at u points [degrees of longitude] or [m].
dxCu, & !< dxCu is delta x at u points [m].
IdxCu, & !< 1/dxCu [m-1].
dyCu, & !< dyCu is delta y at u points [m].
IdyCu, & !< 1/dyCu [m-1].
dy_Cu, & !< The unblocked lengths of the u-faces of the h-cell [m].
IareaCu, & !< The masked inverse areas of u-grid cells [m2].
areaCu !< The areas of the u-grid cells [m2].

real, allocatable, dimension(:,:) :: &
mask2dCv, & !< 0 for boundary points and 1 for ocean points on the v grid. Nondim.
geoLatCv, & !< The geographic latitude at v points in degrees of latitude or m.
geoLonCv, & !< The geographic longitude at v points in degrees of longitude or m.
dxCv, & !< dxCv is delta x at v points, in m.
IdxCv, & !< 1/dxCv in m-1.
dyCv, & !< dyCv is delta y at v points, in m.
IdyCv, & !< 1/dyCv in m-1.
dx_Cv, & !< The unblocked lengths of the v-faces of the h-cell in m.
IareaCv, & !< The masked inverse areas of v-grid cells in m2.
areaCv !< The areas of the v-grid cells in m2.
mask2dCv, & !< 0 for boundary points and 1 for ocean points on the v grid [nondim].
geoLatCv, & !< The geographic latitude at v points [degrees of latitude] or [m].
geoLonCv, & !< The geographic longitude at v points [degrees of longitude] or [m].
dxCv, & !< dxCv is delta x at v points [m].
IdxCv, & !< 1/dxCv [m-1].
dyCv, & !< dyCv is delta y at v points [m].
IdyCv, & !< 1/dyCv [m-1].
dx_Cv, & !< The unblocked lengths of the v-faces of the h-cell [m].
IareaCv, & !< The masked inverse areas of v-grid cells [m2].
areaCv !< The areas of the v-grid cells [m2].

real, allocatable, dimension(:,:) :: &
mask2dBu, & !< 0 for boundary points and 1 for ocean points on the q grid. Nondim.
geoLatBu, & !< The geographic latitude at q points in degrees of latitude or m.
geoLonBu, & !< The geographic longitude at q points in degrees of longitude or m.
dxBu, & !< dxBu is delta x at q points, in m.
IdxBu, & !< 1/dxBu in m-1.
dyBu, & !< dyBu is delta y at q points, in m.
IdyBu, & !< 1/dyBu in m-1.
areaBu, & !< areaBu is the area of a q-cell, in m2
IareaBu !< IareaBu = 1/areaBu in m-2.
mask2dBu, & !< 0 for boundary points and 1 for ocean points on the q grid [nondim].
geoLatBu, & !< The geographic latitude at q points [degrees of latitude] or [m].
geoLonBu, & !< The geographic longitude at q points [degrees of longitude] or [m].
dxBu, & !< dxBu is delta x at q points [m].
IdxBu, & !< 1/dxBu [m-1].
dyBu, & !< dyBu is delta y at q points [m].
IdyBu, & !< 1/dyBu [m-1].
areaBu, & !< areaBu is the area of a q-cell [m2]
IareaBu !< IareaBu = 1/areaBu [m-2].

real, pointer, dimension(:) :: gridLatT => NULL()
!< The latitude of T points for the purpose of labeling the output axes.
Expand All @@ -136,7 +136,7 @@ module MOM_dyn_horgrid
! Except on a Cartesian grid, these are usually some variant of "degrees".

real, allocatable, dimension(:,:) :: &
bathyT !< Ocean bottom depth at tracer points, in depth units.
bathyT !< Ocean bottom depth at tracer points, in depth units [Z ~> m].

logical :: bathymetry_at_vel !< If true, there are separate values for the
!! basin depths at velocity points. Otherwise the effects of
Expand All @@ -154,16 +154,16 @@ module MOM_dyn_horgrid
df_dy !< Derivative d/dy f (Coriolis parameter) at h-points [s-1 m-1].

! These variables are global sums that are useful for 1-d diagnostics
real :: areaT_global !< Global sum of h-cell area in m2
real :: IareaT_global !< Global sum of inverse h-cell area (1/areaT_global) in m2
real :: areaT_global !< Global sum of h-cell area [m2]
real :: IareaT_global !< Global sum of inverse h-cell area (1/areaT_global) [m-2]

! These parameters are run-time parameters that are used during some
! initialization routines (but not all)
real :: south_lat !< The latitude (or y-coordinate) of the first v-line
real :: west_lon !< The longitude (or x-coordinate) of the first u-line
real :: len_lat = 0. !< The latitudinal (or y-coord) extent of physical domain
real :: len_lon = 0. !< The longitudinal (or x-coord) extent of physical domain
real :: Rad_Earth = 6.378e6 !< The radius of the planet in meters.
real :: Rad_Earth = 6.378e6 !< The radius of the planet [m].
real :: max_depth !< The maximum depth of the ocean [Z ~> m].
end type dyn_horgrid_type

Expand Down

0 comments on commit 026f7d8

Please sign in to comment.