Skip to content

Commit

Permalink
Update doxygen for orog_mask_tools.fd. (#421)
Browse files Browse the repository at this point in the history
Clear all doxygen warnings. Fill in missing subroutine and function
descriptions. Define all 'params'. Remove unused routine 'machine.f90'
from orog.fd program.

Part of #191
Fixes #344
Fixes #408
Fixes #413
  • Loading branch information
GeorgeGayno-NOAA authored Mar 24, 2021
1 parent b75447f commit 3c4fa73
Show file tree
Hide file tree
Showing 6 changed files with 658 additions and 251 deletions.
31 changes: 22 additions & 9 deletions sorc/orog_mask_tools.fd/lake.fd/find_limit.F90
Original file line number Diff line number Diff line change
@@ -1,4 +1,16 @@
!> @file
!! @brief Geo-reference utilities for a cubed-sphere grid.
!! @author Ning Wang

!> Given two points on a cubed-sphere grid, compute the
!! maximum and minimum latitudinal extent of the
!! resulting great circle.
!!
!! @param[in] p1_in Latitude and longitude of point 1.
!! @param[in] p2_in Latitude and longitude of point 2.
!! @param[out] latmin Minimum latitudinal extent.
!! @param[out] latmax Maximum latitudinal extent.
!! @author Ning Wang
!#define DIAG
SUBROUTINE find_limit (p1_in, p2_in, latmin, latmax)
REAL*8, INTENT(IN) :: p1_in(2), p2_in(2)
Expand Down Expand Up @@ -37,13 +49,12 @@ SUBROUTINE find_limit (p1_in, p2_in, latmin, latmax)

END SUBROUTINE find_limit

!>
!! This subroutine computes the latitude and longitude
!! of the middle point between two given ponits.
!> Compute the latitude and longitude of the middle
!! point between two given points.
!!
!! There are two formulae available to compute it.
!! There are two formulae available to compute it.
!!
!! One derived from a more general m-sect formula:
!! One derived from a more general m-sect formula:
!! <pre>
!! xyz = sin((1-f)*theta) / sin(theta) * xyz1 +
!! sin(f*theta) /sin(theta) * xyz2 ;
Expand All @@ -54,15 +65,17 @@ END SUBROUTINE find_limit
!! xyz = 0.5 / sqrt[(1+dot(xyz1,xyz2))/2] * (xyz1+xyz2)
!! </pre>
!!
!! and the other one is the normalized middle point of
!! the two end points:
!! and the other one is the normalized middle point of
!! the two end points:
!!
!! <pre>
!! xyz = 0.5 * (xyz1+xyz2), xyz = xyz / sqrt(dot(xyz,xyz))
!! </pre>
!!
!! @author Ning Wang @date March, 2006
!!
!! @param[in] p1 Latitude/longitude of first end point.
!! @param[in] p2 Latitude/longitude of second end point
!! @param[out] p Latitude/longitude of the mid-point.
!! @author Ning Wang @date March, 2006
SUBROUTINE middle(p1,p2,p)
IMPLICIT NONE

Expand Down
67 changes: 64 additions & 3 deletions sorc/orog_mask_tools.fd/lake.fd/lakefrac.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
!> @file
!! This program computes lake fraction and depth numbers for FV3 cubed sphere
!! @brief Compute lake fraction and depth.
!! @author Ning Wang

!> This program computes lake fraction and depth numbers for FV3 cubed sphere
!! grid cells, from a high resolution lat/lon data set.
!!
!! @author Ning Wang @date July 2018
Expand All @@ -12,6 +15,7 @@
!! - Ning Wang, Apr. 2019: Extended the program to process the same lake data
!! for FV3 stand-alone regional (SAR) model.
!!
!! @return 0 for successful completion and for error.
!#define DIAG_N_VERBOSE
#define ADD_ATT_FOR_NEW_VAR
PROGRAM lake_frac
Expand Down Expand Up @@ -129,6 +133,14 @@ PROGRAM lake_frac
STOP
CONTAINS

!> Calculate lake fraction and depth on the model grid from
!! high-resolution data.
!!
!! @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(:)
INTEGER*2, INTENT(IN) :: lakedpth(:)
Expand Down Expand Up @@ -358,7 +370,15 @@ SUBROUTINE cal_lake_frac_depth(lakestat,cs_lakestat,lakedpth,cs_lakedpth)

END SUBROUTINE cal_lake_frac_depth


!> 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 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
REAL, INTENT(OUT) :: grid(:,:)
Expand Down Expand Up @@ -411,6 +431,15 @@ SUBROUTINE read_cubed_sphere_grid(res, grid)

END SUBROUTINE read_cubed_sphere_grid

!> Read the latitude and longitude for a regional grid
!! from the 'grid' file.
!!
!! @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
INTEGER, INTENT(OUT) :: res_x, res_y
Expand Down Expand Up @@ -471,6 +500,16 @@ SUBROUTINE read_cubed_sphere_reg_grid(res, grid, halo_depth, res_x, res_y)

END SUBROUTINE read_cubed_sphere_reg_grid

!> 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 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 @@ -495,7 +534,14 @@ SUBROUTINE read_lakedata(lakedata_path,lake_stat,lake_dpth,nlat,nlon)

END SUBROUTINE read_lakedata


!> 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 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
INTEGER, INTENT(IN) :: cs_res
Expand Down Expand Up @@ -685,6 +731,16 @@ SUBROUTINE write_lakedata_to_orodata(cs_res, cs_lakestat, cs_lakedpth)

END SUBROUTINE write_lakedata_to_orodata

!> 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 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
INTEGER, INTENT(IN) :: cs_res, tile_x_dim, tile_y_dim
Expand Down Expand Up @@ -887,6 +943,11 @@ SUBROUTINE write_reg_lakedata_to_orodata(cs_res, tile_x_dim, tile_y_dim, cs_lake

END SUBROUTINE write_reg_lakedata_to_orodata

!> Check NetCDF error code
!!
!! @param[in] stat Error code.
!! @param[in] opname NetCDF operation that failed.
!! @author Ning Wang
SUBROUTINE nc_opchk(stat,opname)
USE netcdf
IMPLICIT NONE
Expand Down
1 change: 0 additions & 1 deletion sorc/orog_mask_tools.fd/orog.fd/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
set(fortran_src
machine.f90
mtnlm7_oclsm.f
netcdf_io.F90)

Expand Down
14 changes: 0 additions & 14 deletions sorc/orog_mask_tools.fd/orog.fd/machine.f90

This file was deleted.

Loading

0 comments on commit 3c4fa73

Please sign in to comment.