Skip to content

Commit

Permalink
This is part of Issue #392 (#465)
Browse files Browse the repository at this point in the history
Fixes the doxygen warnings in CALLCL.f CALMCVG.f CALMICT.f
  • Loading branch information
kayeekayee committed Apr 1, 2022
1 parent af62bd2 commit 6ffdd3d
Show file tree
Hide file tree
Showing 3 changed files with 125 additions and 209 deletions.
74 changes: 28 additions & 46 deletions sorc/ncep_post.fd/CALLCL.f
Original file line number Diff line number Diff line change
@@ -1,50 +1,32 @@
!> @file
!
!> SUBPROGRAM: CALLCL COMPUTES LCL HEIGHTS AND PRESSURE
!! PRGRMMR: TREADON ORG: W/NP2 DATE: 93-03-15
!!
!! ABSTRACT:
!! THIS ROUTINE COMPUTES THE LIFTING CONDENSATION LEVEL
!! PRESSURE AND HEIGHT IN EACH COLUMN AT MASS POINTS.
!! THE HEIGHT IS ABOVE GROUND LEVEL. THE EQUATION USED
!! TO FIND THE LCL PRESSURE IS FROM BOLTAN (1980,MWR)
!! AND IS THE SAME AS THAT USED IN SUBROUTINE CALCAPE.
!!
!! THIS ROUTINE IS A TEST VERSION. STILL TO BE RESOLVED
!! IS THE "BEST" PARCEL TO LIFT.
!!
!! PROGRAM HISTORY LOG:
!! 93-03-15 RUSS TREADON
!! 98-06-16 T BLACK - CONVERSION FROM 1-D TO 2-D
!! 00-01-04 JIM TUCCILLO - MPI VERSION
!! 02-04-24 MIKE BALDWIN - WRF VERSION
!! 19-10-30 Bo CUI - REMOVE "GOTO" STATEMENT
!! 21-07-28 W Meng - Restriction compuatation from undefined grids
!!
!! USAGE: CALL CALLCL(P1D,T1D,Q1D,PLCL,ZLCL)
!! INPUT ARGUMENT LIST:
!! P1D - ARRAY OF PARCEL PRESSURES (PA)
!! T1D - ARRAY OF PARCEL TEMPERATURES (K)
!! Q1D - ARRAY OF PARCEL SPECIFIC HUMIDITIES (KG/KG)
!!
!! OUTPUT ARGUMENT LIST:
!! PLCL - PARCEL PRESSURE AT LCL (PA)
!! ZLCL - PARCEL AGL HEIGHT AT LCL (M)
!!
!! OUTPUT FILES:
!! NONE
!!
!! SUBPROGRAMS CALLED:
!! UTILITIES:
!! NONE
!! LIBRARY:
!! COMMON - LOOPS
!! OPTIONS
!!
!! ATTRIBUTES:
!! LANGUAGE: FORTRAN 90
!! MACHINE : CRAY C-90
!!
!> @brief Subroutine that computes LCL heights and pressure.
!>
!> This routine computes the lifting condensation level
!> pressure and height in each column at mass points.
!> The height is above ground level. The equation used
!> to find the LCL pressure is from Boltan (1980, MWR)
!> and is the same as that used in subroutine CALCAPE.
!>
!> This is a test version. Still to be resolved
!> is the "best" parcel to lift.
!>
!> @param[in] P1D Array of parcel pressures (Pa).
!> @param[in] T1D Array of parcel temperatures (K).
!> @param[in] Q1D Array of parcel specific humidities (kg/kg).
!> @param[out] PLCL Parcel Pressure at LCL (Pa).
!> @param[out] ZLCL Parcel AGL height at LCL (m).
!>
!> ### Program history log:
!> Date | Programmer | Comments
!> -----|------------|---------
!> 1993-03-15 | Russ Treadon | Initial
!> 1998-06-16 | T Black | Convesion from 1-D to 2-D
!> 2000-01-04 | Jim Tuccillo | MPI Version
!> 2002-04-24 | Mike Baldwin | WRF Version
!> 2019-10-30 | Bo Cui | Remove "GOTO" Statement
!> 2021-07-28 | W Meng | Restriction compuatation from undefined grids
!>
!> @author Russ Treadon W/NP2 @date 1993-03-15
SUBROUTINE CALLCL(P1D,T1D,Q1D,PLCL,ZLCL)

!
Expand Down
80 changes: 31 additions & 49 deletions sorc/ncep_post.fd/CALMCVG.f
Original file line number Diff line number Diff line change
@@ -1,53 +1,35 @@
!> @file
!
!> SUBPROGRAM: CALMCVG COMPUTES MOISTURE CONVERGENCE
!! PRGRMMR: TREADON ORG: W/NP2 DATE: 93-01-22
!!
!! ABSTRACT:
!! GIVEN SPECIFIC HUMIDITY, Q, AND THE U-V WIND COMPONENTS
!! THIS ROUTINE EVALUATES THE VECTOR OPERATION,
!! DEL DOT (Q*VEC)
!! WHERE,
!! DEL IS THE VECTOR GRADIENT OPERATOR,
!! DOT IS THE STANDARD DOT PRODUCT OPERATOR, AND
!! VEC IS THE VECTOR WIND.
!! MINUS ONE TIMES THE RESULTING SCALAR FIELD IS THE
!! MOISTURE CONVERGENCE WHICH IS RETURNED BY THIS ROUTINE.
!!
!! PROGRAM HISTORY LOG:
!! 93-01-22 RUSS TREADON
!! 98-06-08 T BLACK - CONVERSION FROM 1-D TO 2-D
!! 00-01-04 JIM TUCCILLO - MPI VERSION
!! 02-04-23 MIKE BALDWIN - WRF C-GRID VERSION
!! 05-07-07 BINBIN ZHOU - ADD RSM A GRID
!! 06-04-25 H CHUANG - BUG FIXES TO CORECTLY COMPUTE MC AT BOUNDARIES
!! 21-04-01 J MENG - COMPUTATION ON DEFINED POINTS ONLY
!!
!! USAGE: CALL CALMCVG(Q1D,U1D,V1D,QCNVG)
!! INPUT ARGUMENT LIST:
!! Q1D - SPECIFIC HUMIDITY AT P-POINTS (KG/KG)
!! U1D - U WIND COMPONENT (M/S) AT P-POINTS
!! V1D - V WIND COMPONENT (M/S) AT P-POINTS
!!
!! OUTPUT ARGUMENT LIST:
!! QCNVG - MOISTURE CONVERGENCE (1/S) AT P-POINTS
!!
!! OUTPUT FILES:
!! NONE
!!
!! SUBPROGRAMS CALLED:
!! UTILITIES:
!! NONE
!! LIBRARY:
!! COMMON - MASKS
!! DYNAM
!! OPTIONS
!! INDX
!!
!! ATTRIBUTES:
!! LANGUAGE: FORTRAN 90
!! MACHINE : CRAY C-90
!!
!> @brief Subroutine that computes moisture convergence.
!>
!><pre>
!> Given specific humidity, Q, and the U-V wind components
!> This routine evaluates the vector operation,
!> DEL DOT (Q*VEC)
!> where,
!> DEL is the vector gradient operator,
!> DOT is the standard dot product operator, and
!> VEC is the vector wind.
!> Minus one times the resulting scalar field is the
!> moisture convergence which is returned by this routine.
!></pre>
!>
!> @param[in] Q1D - Specific humidity at P-points (kg/kg).
!> @param[in] U1D - U wind component (m/s) at P-points.
!> @param[in] V1D - V wind component (m/s) at P-points.
!> @param[out] QCNVG - Moisture convergence (1/s) at P-points.
!>
!> ### Program history log:
!> Date | Programmer | Comments
!> -----|------------|---------
!> 1993-01-22 | Russ Treadon | Initial
!> 1998-06-08 | T Black | Conversion From 1-D To 2-D
!> 2000-01-04 | Jim Tuccillo | MPI Version
!> 2002-04-23 | Mike Baldwin | WRF C-Grid Version
!> 2005-07-07 | Binbin Zhou | Add RSM A Grid
!> 2006-04-25 | H Chuang | Bug fixes to correctly compute MC at boundaries
!> 2021-04-01 | J Meng | Computation on defined points only
!>
!> @author Russ Treadon W/NP2 @date 1993-01-22
SUBROUTINE CALMCVG(Q1D,U1D,V1D,QCNVG)

!
Expand Down
180 changes: 66 additions & 114 deletions sorc/ncep_post.fd/CALMICT.f
Original file line number Diff line number Diff line change
@@ -1,58 +1,37 @@
!> @file
! . . .
!> SUBPROGRAM: CALMIC COMPUTES HYDROMETEORS
!! PRGRMMR: JIN ORG: W/NP2 DATE: 01-08-14
!!
!! ABSTRACT:
!! THIS ROUTINE COMPUTES THE MIXING RATIOS OF CLOUD WATER,
!! CLOUD ICE, RAIN, AND SNOW. THE CODE IS BASED ON SUBROUTINES
!! GSMDRIVE & GSMCOLUMN IN THE NMM MODEL.
!!
!! PROGRAM HISTORY LOG:
!! 01-08-14 YI JIN
!! 02-02-11 Brad Ferrier - Minor changes for consistency w/ NMM model
!! 04-11-10 Brad Ferrier - Removed cloud fraction algorithm
!! 04-11-17 H CHUANG - WRF VERSION
!! 14-03-11 B Ferrier - Created new & old versions of this subroutine
!! to process new & old versions of the microphysics
!!
!! USAGE: CALL CALMICT_new(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL
!! &, QW1,QI1,QR1,QS1,DBZ1,DBZR1,DBZI1,DBZC1)
!! INPUT ARGUMENT LIST:
!! P1D - PRESSURE (PA)
!! T1D - TEMPERATURE (K)
!! Q1D - SPECIFIC HUMIDITY (KG/KG)
!! C1D - TOTAL CONDENSATE (CWM, KG/KG)
!! FI1D - F_ice (fraction of condensate in form of ice)
!! FR1D - F_rain (fraction of liquid water in form of rain)
!! FS1D - F_RimeF ("Rime Factor", ratio of total ice growth
!! to deposition growth)
!! CUREFL - Radar reflectivity contribution from convection (mm**6/m**3)
!!
!! OUTPUT ARGUMENT LIST:
!! QW1 - CLOUD WATER MIXING RATIO (KG/KG)
!! QI1 - CLOUD ICE MIXING RATIO (KG/KG)
!! QR1 - RAIN MIXING RATIO (KG/KG)
!! QS1 - "SNOW" (precipitation ice) MIXING RATIO (KG/KG)
!! DBZ1 - Equivalent radar reflectivity factor in dBZ; i.e., 10*LOG10(Z)
!! DBZR - Equivalent radar reflectivity factor from rain in dBZ
!! DBZI - Equivalent radar reflectivity factor from ice (all forms) in dBZ
!! DBZC - Equivalent radar reflectivity factor from parameterized convection in dBZ
!!
!! OUTPUT FILES:
!! NONE
!!
!! SUBPROGRAMS CALLED:
!! FUNCTIONS:
!! FPVS
!! UTILITIES:
!! LIBRARY:
!! NONE
!!
!! ATTRIBUTES:
!! LANGUAGE: FORTRAN
!! MACHINE : IBM SP
!!
!> @brief Subroutine that computes hydrometeors.
!>
!> This routin computes the mixing ratios of cloud water,
!> cloud ice, rain, and snow. The code is based on subroutines
!> GSMDRIVE and GSMCOLUMN in the NMM model.
!>
!> @param[in] P1D Pressure (Pa).
!> @param[in] T1D Temperature (K).
!> @param[in] Q1D Specific humidity (kg/kg).
!> @param[in] C1D Total condensate (CWM, kg/kg).
!> @param[in] FI1D F_ice (fraction of condensate in form of ice).
!> @param[in] FR1D F_rain (fraction of liquid water in form of rain).
!> @param[in] FS1D F_RimeF ("Rime Factor", ratio of total ice growth to deposition growth).
!> @param[in] CUREFL Radar reflectivity contribution from convection (mm**6/m**3).
!> @param[out] QW1 Cloud water mixing ratio (kg/kg).
!> @param[out] QI1 Cloud ice mixing ratio (kg/kg).
!> @param[out] QR1 Rain mixing ratio (kg/kg).
!> @param[out] QS1 "Snow" (precipitation ice) mixing ratio (kg/kg).
!> @param[out] DBZ1 Equivalent radar reflectivity factor in dBZ; i.e., 10*LOG10(Z).
!> @param[out] DBZR Equivalent radar reflectivity factor from rain in dBZ.
!> @param[out] DBZI Equivalent radar reflectivity factor from ice (all forms) in dBZ.
!> @param[out] DBZC Equivalent radar reflectivity factor from parameterized convection in dBZ.
!>
!> ### Program history log:
!> Date | Programmer | Comments
!> -----|------------|---------
!> 2001-08-14 | Yi Jin | Initial
!> 2002-02-11 | Brad Ferrier | Minor changes for consistency w/ NMM model
!> 2004-11-10 | Brad Ferrier | Removed cloud fraction algorithm
!> 2004-11-17 | H Chuang | WRF VERSION
!> 2014-03-11 | Brad Ferrier | Created new & old versions of this subroutine to process new & old versions of the microphysics
!>
!> @author Yi Jin W/NP2 @date 2001-08-14
SUBROUTINE CALMICT_new(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL, &
QW1,QI1,QR1,QS1,DBZ1,DBZR1,DBZI1,DBZC1,NLICE1,NRAIN1)

Expand Down Expand Up @@ -320,66 +299,39 @@ SUBROUTINE CALMICT_new(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL, &
!
SUBROUTINE CALMICT_old(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL, &
QW1,QI1,QR1,QS1,DBZ1,DBZR1,DBZI1,DBZC1,NLICE1,NRAIN1)
!$$$ SUBPROGRAM DOCUMENTATION BLOCK
! . . .
! SUBPROGRAM: CALMICT_old COMPUTES HYDROMETEORS FROM THE OLDER VERSION
! OF THE MICROPHYSICS
!
! PRGRMMR: JIN ORG: W/NP2 DATE: 01-08-14
!
! ABSTRACT:
! THIS ROUTINE COMPUTES THE MIXING RATIOS OF CLOUD WATER, CLOUD ICE,
! RAIN, AND SNOW. THE CODE IS BASED ON OPTION MP_PHYSICS==95 IN THE
! WRF NAMELIST AND OPTION MICRO='fer' in NMMB CONFIGURE FILES.
!
! PROGRAM HISTORY LOG:
! 01-08-14 YI JIN
! 02-02-11 Brad Ferrier - Minor changes for consistency w/ NMM model
! 04-11-10 Brad Ferrier - Removed cloud fraction algorithm
! 04-11-17 H CHUANG - WRF VERSION
! 14-03-11 B Ferrier - Created new & old versions of this subroutine
! to process new & old versions of the microphysics
!
! USAGE: CALL CALMICT_old(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL
! &, QW1,QI1,QR1,QS1,DBZ1,DBZR1,DBZI1,DBZC1)
!
! INPUT ARGUMENT LIST:
! P1D - PRESSURE (PA)
! T1D - TEMPERATURE (K)
! Q1D - SPECIFIC HUMIDITY (KG/KG)
! C1D - TOTAL CONDENSATE (CWM, KG/KG)
! FI1D - F_ice (fraction of condensate in form of ice)
! FR1D - F_rain (fraction of liquid water in form of rain)
! FS1D - F_RimeF ("Rime Factor", ratio of total ice growth
! to deposition growth)
! CUREFL - Radar reflectivity contribution from convection (mm**6/m**3)
!
! OUTPUT ARGUMENT LIST:
! QW1 - CLOUD WATER MIXING RATIO (KG/KG)
! QI1 - CLOUD ICE MIXING RATIO (KG/KG)
! QR1 - RAIN MIXING RATIO (KG/KG)
! QS1 - "SNOW" (precipitation ice) MIXING RATIO (KG/KG)
! DBZ1 - Equivalent radar reflectivity factor in dBZ; i.e., 10*LOG10(Z)
! DBZR - Equivalent radar reflectivity factor from rain in dBZ
! DBZI - Equivalent radar reflectivity factor from ice (all forms) in dBZ
! DBZC - Equivalent radar reflectivity factor from parameterized convection
! in dBZ
!
! OUTPUT FILES:
! NONE
!
! SUBPROGRAMS CALLED:
! FUNCTIONS:
! FPVS
! UTILITIES:
! LIBRARY:
! NONE
!
! ATTRIBUTES:
! LANGUAGE: FORTRAN
! MACHINE : IBM SP
!$$$
!
!> CALMICT_old computes hydrometeors from the older version of the microphysics.
!>
!> This routin computes the mixing ratios of cloud water, cloud ice,
!> rain, and snow. The code is based on option MP_PHYSICS==95 in the
!> WRF namelist and option MICRO='fer' in NMMB configure files.
!>
!> @param[in] P1D Pressure (Pa).
!> @param[in] T1D Temperature (K).
!> @param[in] Q1D Specific humidity (kg/kg).
!> @param[in] C1D Total condensate (CWM, kg/kg).
!> @param[in] FI1D F_ice (fraction of condensate in form of ice).
!> @param[in] FR1D F_rain (fraction of liquid water in form of rain).
!> @param[in] FS1D F_RimeF ("Rime Factor", ratio of total ice growth to deposition growth).
!> @param[in] CUREFL Radar reflectivity contribution from convection (mm**6/m**3).
!> @param[out] QW1 Cloud water mixing ratio (kg/kg).
!> @param[out] QI1 Cloud ice mixing ratio (kg/kg).
!> @param[out] QR1 Rain mixing ratio (kg/kg).
!> @param[out] QS1 "Snow" (precipitation ice) mixing ratio (kg/kg).
!> @param[out] DBZ1 Equivalent radar reflectivity factor in dBZ; i.e., 10*LOG10(Z).
!> @param[out] DBZR Equivalent radar reflectivity factor from rain in dBZ.
!> @param[out] DBZI Equivalent radar reflectivity factor from ice (all forms) in dBZ.
!> @param[out] DBZC Equivalent radar reflectivity factor from parameterized convection in dBZ.
!>
!> ### Program history log:
!> Date | Programmer | Comments
!> -----|------------|---------
!> 2001-08-14 | Yi Jin | Initial
!> 2002-02-11 | Brad Ferrier | Minor changes for consistency w/ NMM model
!> 2004-11-10 | Brad Ferrier | Removed cloud fraction algorithm
!> 2004-11-17 | H Chuang | WRF VERSION
!> 2014-03-11 | Brad Ferrier | Created new & old versions of this subroutine to process new & old versions of the microphysics
!>
!> @author Yi Jin W/NP2 @date 2001-08-14
use params_mod, only: dbzmin, epsq, tfrz, eps, rd, d608, oneps, nlimin
use ctlblk_mod, only: jsta, jend, jsta_2l, jend_2u, im
use rhgrd_mod, only: rhgrd
Expand Down

0 comments on commit 6ffdd3d

Please sign in to comment.