Skip to content

Commit

Permalink
Doxygen updates to ./lake.fd/lakefrac.F90 and
Browse files Browse the repository at this point in the history
./orog.fd/mtnlm7_oclsm.f.

Part of ufs-community#191
Fixes ufs-community#344
Fixes ufs-community#408
  • Loading branch information
GeorgeGayno-NOAA committed Mar 17, 2021
1 parent 20e85f0 commit 5378c73
Show file tree
Hide file tree
Showing 2 changed files with 97 additions and 59 deletions.
73 changes: 43 additions & 30 deletions sorc/orog_mask_tools.fd/lake.fd/lakefrac.F90
Original file line number Diff line number Diff line change
Expand Up @@ -133,12 +133,13 @@ PROGRAM lake_frac
STOP
CONTAINS

!> Calculate lake fraction depth
!> Calculate lake fraction and depth on the model grid from
!! high-resolution data.
!!
!! @param[in] lakestat ???
!! @param[in] lakedpth ???
!! @param[out] cs_lakestat ???
!! @param[out] cs_lakedpth ???
!! @param[in] lakestat High-resolution lake status code.
!! @param[in] lakedpth High-resolution lake depth.
!! @param[out] cs_lakestat Lake fraction on the model grid.
!! @param[out] cs_lakedpth Lake depth on the model grid.
!! @author Ning Wang
SUBROUTINE cal_lake_frac_depth(lakestat,cs_lakestat,lakedpth,cs_lakedpth)
INTEGER*1, INTENT(IN) :: lakestat(:)
Expand Down Expand Up @@ -369,10 +370,14 @@ SUBROUTINE cal_lake_frac_depth(lakestat,cs_lakestat,lakedpth,cs_lakedpth)

END SUBROUTINE cal_lake_frac_depth

!> Read cubed sphere grid
!> Read the latitude and longitude for a cubed-sphere
!! grid from the 'grid' files. For global grids, all
!! six sides are returned.
!!
!! @param[in] res ???
!! @param[out] grid ???
!! @param[in] res The resolution. Example: '96' for C96.
!! @param[out] grid Array containing the latitude and
!! longitude on the 'supergrid'. Multiple tiles
!! are concatenated.
!! @author Ning Wang
SUBROUTINE read_cubed_sphere_grid(res, grid)
INTEGER, INTENT(IN) :: res
Expand Down Expand Up @@ -426,13 +431,14 @@ SUBROUTINE read_cubed_sphere_grid(res, grid)

END SUBROUTINE read_cubed_sphere_grid

!> Read cubed sphere reg grid
!> Read the latitude and longitude for a regional grid
!! from the 'grid' file.
!!
!! @param[in] res ???
!! @param[out] grid ???
!! @param[in] halo_depth ???
!! @param[out] res_x ???
!! @param[out] res_y ???
!! @param[in] res Resolution of grid. Example: '96' for C96.
!! @param[out] grid Latitude and longitude on the supergrid.
!! @param[in] halo_depth Lateral halo. Not used.
!! @param[out] res_x Number of grid points in the 'x' direction.
!! @param[out] res_y Number of grid points in the 'y' direction.
!! @author Ning Wang
SUBROUTINE read_cubed_sphere_reg_grid(res, grid, halo_depth, res_x, res_y)
INTEGER, INTENT(IN) :: res, halo_depth
Expand Down Expand Up @@ -494,13 +500,16 @@ SUBROUTINE read_cubed_sphere_reg_grid(res, grid, halo_depth, res_x, res_y)

END SUBROUTINE read_cubed_sphere_reg_grid

!> Read lake data
!> Read a high-resolution lake depth dataset, and a corresponding
!! lake status dataset which provides a status code on the
!! reliability of each lake depth point.
!!
!! @param[in] lakedata_path ???
!! @param[out] lake_stat ???
!! @param[out] lake_dpth ???
!! @param[in] nlat ???
!! @param[in] nlon ???
!! @param[in] lakedata_path Path to the lake depth and lake status
!! dataset.
!! @param[out] lake_stat Status code.
!! @param[out] lake_dpth Lake depth.
!! @param[in] nlat 'j' dimension of both datasets.
!! @param[in] nlon 'i' dimension of both datasets.
SUBROUTINE read_lakedata(lakedata_path,lake_stat,lake_dpth,nlat,nlon)
CHARACTER(len=256), INTENT(IN) :: lakedata_path
INTEGER*1, INTENT(OUT) :: lake_stat(:)
Expand All @@ -525,11 +534,13 @@ SUBROUTINE read_lakedata(lakedata_path,lake_stat,lake_dpth,nlat,nlon)

END SUBROUTINE read_lakedata

!> Write lake data to oro data.
!> Write lake depth and fraction to an existing model orography file.
!! Also, perform some quality control checks on the lake data.
!! This routine is used for non-regional grids.
!!
!! @param[in] cs_res ???
!! @param[in] cs_lakestat ???
!! @param[in] cs_lakedpth ???
!! @param[in] cs_res Resolution. Example: '96' for C96.
!! @param[in] cs_lakestat Lake fraction.
!! @param[in] cs_lakedpth Lake depth.
!! @author Ning Wang
SUBROUTINE write_lakedata_to_orodata(cs_res, cs_lakestat, cs_lakedpth)
USE netcdf
Expand Down Expand Up @@ -720,13 +731,15 @@ SUBROUTINE write_lakedata_to_orodata(cs_res, cs_lakestat, cs_lakedpth)

END SUBROUTINE write_lakedata_to_orodata

!> write reg lake data to oro data.
!> Write lake depth and fraction to an existing model orography file.
!! Also, perform some quality control checks on the lake data.
!! This routine is used for regional grids.
!!
!! @param[in] cs_res ???
!! @param[in] tile_x_dim ???
!! @param[in] tile_y_dim ???
!! @param[in] cs_lakestat ???
!! @param[in] cs_lakedpth ???
!! @param[in] cs_res Resolution. Example: '96' for C96.
!! @param[in] cs_lakestat Lake fraction.
!! @param[in] cs_lakedpth Lake depth.
!! @param[in] tile_x_dim 'x' dimension of the model grid.
!! @param[in] tile_y_dim 'y' dimension of the model grid.
!! @author Ning Wang
SUBROUTINE write_reg_lakedata_to_orodata(cs_res, tile_x_dim, tile_y_dim, cs_lakestat, cs_lakedpth)
USE netcdf
Expand Down
83 changes: 54 additions & 29 deletions sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.f
Original file line number Diff line number Diff line change
Expand Up @@ -172,7 +172,7 @@
!! @param[in] NR Rhomboidal flag.
!! @param[in] NF0 First order spectral filter parameters.
!! @param[in] NF1 Second order spectral filter parameters.
!! @param[in] NW ???
!! @param[in] NW Number of waves.
!! @param[in] EFAC Factor to adjust orography by its variance.
!! @param[in] BLAT When less than zero, reverse latitude/
!! longitude for output.
Expand Down Expand Up @@ -4562,22 +4562,34 @@ function get_xnsum(lon1,lat1,lon2,lat2,IMN,JMN,

end function get_xnsum

!> Get xnnum2
!> Count the number of high-resolution orography points that
!! are higher than a critical value inside a model grid box
!! (or a portion of a model grid box). The critical value is a
!! function of the standard deviation of orography.
!!
!! @param[in] lon1 ???
!! @param[in] lat1 ???
!! @param[in] lon2 ???
!! @param[in] lat2 ???
!! @param[in] imn ???
!! @param[in] jmn ???
!! @param[in] glat ???
!! @param[in] zavg ???
!! @param[in] zslm ???
!! @param[in] delxn ???
!! @param[in] xnsum1 ???
!! @param[in] xnsum2 ???
!! @param[in] lon1 Longitude of corner point 1 of the model
!! grid box.
!! @param[in] lat1 Latitude of corner point 1 of the model
!! grid box.
!! @param[in] lon2 Longitude of corner point 2 of the model
!! grid box.
!! @param[in] lat2 Latitude of corner point 2 of the model
!! grid box.
!! @param[in] imn 'i' dimension of the high-resolution orography
!! data.
!! @param[in] jmn 'j' dimension of the high-resolution orography
!! data.
!! @param[in] glat Latitude of each row of the high-resolution
!! orography data.
!! @param[in] zavg The high-resolution orography.
!! @param[in] zslm The high-resolution land mask.
!! @param[in] delxn Resolution of the high-res orography data.
!! @param[out] xnsum1 The number of high-resolution orography
!! above the critical value inside a model grid box.
!! @param[out] xnsum2 The number of high-resolution orography
!! points inside a model grid box.
!! @param[out] hc Critical height.
!! @author Jordan Alpert NOAA/EMC
!! @author GFDL Programmer
subroutine get_xnsum2(lon1,lat1,lon2,lat2,IMN,JMN,
& glat,zavg,zslm,delxn,xnsum1,xnsum2,HC)
implicit none
Expand Down Expand Up @@ -4645,22 +4657,35 @@ subroutine get_xnsum2(lon1,lat1,lon2,lat2,IMN,JMN,

end subroutine get_xnsum2

!> Get xnnum3
!> Count the number of high-resolution orography points that
!! are higher than a critical value inside a model grid box
!! (or a portion of a model grid box). Unlike routine
!! get_xnsum2(), this routine does not compute the critical
!! value. Rather, it is passed in.
!!
!! @param[in] lon1 ???
!! @param[in] lat1 ???
!! @param[in] lon2 ???
!! @param[in] lat2 ???
!! @param[in] imn ???
!! @param[in] jmn ???
!! @param[in] glat ???
!! @param[in] zavg ???
!! @param[in] zslm ???
!! @param[in] delxn ???
!! @param[in] xnsum1 ???
!! @param[in] xnsum2 ???
!! @param[in] lon1 Longitude of corner point 1 of the model
!! grid box.
!! @param[in] lat1 Latitude of corner point 1 of the model
!! grid box.
!! @param[in] lon2 Longitude of corner point 2 of the model
!! grid box.
!! @param[in] lat2 Latitude of corner point 2 of the model
!! grid box.
!! @param[in] imn 'i' dimension of the high-resolution orography
!! data.
!! @param[in] jmn 'j' dimension of the high-resolution orography
!! data.
!! @param[in] glat Latitude of each row of the high-resolution
!! orography data.
!! @param[in] zavg The high-resolution orography.
!! @param[in] zslm The high-resolution land mask.
!! @param[in] delxn Resolution of the high-res orography data.
!! @param[out] xnsum1 The number of high-resolution orography
!! above the critical value inside a model grid box.
!! @param[out] xnsum2 The number of high-resolution orography
!! points inside a model grid box.
!! @param[in] hc Critical height.
!! @author Jordan Alpert NOAA/EMC
!! @author GFDL Programmer
subroutine get_xnsum3(lon1,lat1,lon2,lat2,IMN,JMN,
& glat,zavg,zslm,delxn,xnsum1,xnsum2,HC)
implicit none
Expand Down

0 comments on commit 5378c73

Please sign in to comment.