PUBLIC INTERFACE / ROUTINES / NAMELIST / CHANGES / ERRORS / REFERENCES / NOTES


module diag_cloud_mod

     Contact:   Bill Stern, Tony Gordon
     Reviewers:

     Tags/Status

OVERVIEW

     DIAG_CLOUD - DIAGNOSTIC CLOUD PREDICTION - Gordon (1992)
 
Calculates cloud fractions diagnostically using relative humidity, omega and stability.

This cloud parameterization scheme closely resembles the empirically based RH threshold scheme of Slingo (1987). Fractional cloud amount is predicted quasi-empirically.  It is possible to determine cloud amounts for 7 different cloud types, as follows:

Type 1 - Relative humidity (RH) cloud, where cloud amounts > 0 will occur above some specified critical RH value increasing either linearly or quadratically up to 100%.
Type 2 - A modified (reduced) RH low cloud amount may result in some regions of descending motion if this option is activated.
Type 3 - Marine stratus type low clouds are determined using linear regression via a combination approaches by Slingo and Tim Li. (not yet implemented as of August 2000)
Type 4 - Shallow convective low clouds may be computed above a locally determined LCL up to the top of the low cloud region.
Type 5 - Deep convective clouds are determined based on the occurance of convection as determined by the convective parameterization.  The actual cloud fractions will then be calculated based on a linear regression between cloud amount and convective precip. (In practice this cloud type is not being used.)
Types 6 & 7 - High clouds that occur in regions of convection may be determined to be anvil or super anvil cirrus.  With regard to cloud amount they are treated the same as other high clouds, however, they will have different cloud optical properties.

Clouds are vertically grouped as either high, middle or low based on a seasonally varying climatological normalized pressure level limits.
 
 


OTHER MODULES USED

     constants_mod
          utilities_mod
          time_manager_mod
          cloud_zonal_mod
          diag_cloud_rad_mod
          sat_vapor_pres_mod
          shallow_conv_mod
 
 


PUBLIC INTERFACE

use diag_cloud_mod [,only:  diag_cloud_driver, diag_cloud_init, diag_cloud_end, diag_cloud_sum, diag_cloud_avg, do_diag_cloud   ]

diag_cloud_init  - Called once to initialize diag_cloud -  Allocates storage for global cloud quantities,
read in a cloud restart file and also reads namelist. Must be called before diag_cloud.

diag_cloud_driver       - Driver for diagnostic cloud prediction module

diag_cloud_end  - Writes out cloud restart file..

diag_cloud_sum -  Accumulates diagnostic cloud predictors for time averaging.

diag_cloud_avg - Calculates time averaged predictors to be used in diag_cloud to compute clouds

do_diag_cloud -  returns logical value for whether diag_cloud has been initialized

Notes:
 * A namelist interface ( &diag_cloud_nml ) controls runtime options.
 
 


PUBLIC ROUTINES

call diag_cloud_init (ix,iy,kx, ierr)
!---------------------------------------------------------------------
! Input Arguments
!  parmameter mxband = max number of radiative bands to be considered for some
!              cloud properties (defined at top of module)
!
!      IX, IY, KX   Dimensions for global storage arrays (2- horiz, vert)
!---------------------------------------------------------------------
 integer, intent(in) :: ix, iy, kx
!---------------------------------------------------------------------
! Output Argument
!      IERR     Error flag
!---------------------------------------------------------------------
 integer, intent(out) :: ierr
!---------------------------------------------------------------------
 
 

  call diag_cloud_driver (is,js, &
                    temp,qmix,rhum,omega,lgscldelq,cnvcntq,convprc, &
                    pfull,phalf,psfc,coszen,lat,time, &
                    nclds,cldtop,cldbas,cldamt,r_uv,r_nir,ab_uv,ab_nir, &
                    em_lw,kbot)
!---------------------------------------------------------------------
! Input Arguments
!      IS,JS    starting i,j indices from the full horizontal grid
!      IX, IY   Horizontal dimensions for global storage arrays
!      TEMP     Temperature (Deg K) at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      QMIX     Mixing Ratio at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      RHUM     Relative humidity fraction at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      OMEGA   Pressure vertical velocity at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      LGSCLDELQ  Averaged rate of change in mix ratio due to lg scale precip
!               at full model levels
!               (dimensioned IDIM x JDIM x kx)
!      CNVCNTQ  Accumulated count of change in mix ratio due to conv precip
!               at full model levels
!               (dimensioned IDIM x JDIM x kx)
!      convprc Accumulated conv precip rate summed over all
!               full model levels (mm/day )
!               (dimensioned IDIM x JDIM)
!      PFULL    Pressure at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      PHALF    Pressure at half model levels
!                   (dimensioned IDIM x JDIM x kx+1)
!      PSFC     Surface pressure field
!                   (dimensioned IDIM x JDIM)
!      COSZEN     cosine of the zenith angle
!                   (dimensioned IDIM x JDIM)
!      TIME       time of year (time_type)
!      LAT        latitudes in radians, dimensioned by (1xJDIM)
!      KBOT      OPTIONAL; lowest model level index array
!                   (dimensioned IDIM x JDIM)
 !---------------------------------------------------------------------
integer, intent(in)   ::  is,js
 type(time_type), intent(in)  :: time
 real, intent(in)  :: lat(:,:)
 real, intent(in), dimension (:,:,:) ::  temp,qmix,rhum,omega
 real, intent(in), dimension (:,:,:) ::  lgscldelq,cnvcntq,pfull, phalf
 real, intent(in), dimension (:,:)   ::  convprc,psfc, coszen

 integer, intent(in), OPTIONAL, dimension(:,:) :: kbot

!---------------------------------------------------------------------
! Output Arguments

!      OUTPUT
!      ------

!       NCLDS   number of (random overlapping) clouds in column and also
!                     the current # for clouds to be operating on
!                   (dimensioned IDIM x JDIM )
!      CLDTOP   index of cloud tops (at cloud levels)
!                   (dimensioned IDIM x JDIM x kx)
!      CLDBAS   index of cloud bottoms (at cloud levels)
!                   (dimensioned IDIM x JDIM x kx)
!      CLDAMT   cloud amount (fraction) (at cloud levels)
!                   (dimensioned IDIM x JDIM x kx)
!      R_UV     fractional amount of ultraviolet radiation
!                     reflected by the clouds (at cloud levels)
!      R_NIR fractional amount of near inrared radiation
!                     reflected by the clouds (at cloud levels)
!      AB_UV fractional amount of ultraviolet radiation
!                     absorbed by the clouds (at cloud levels)
!      AB_NIR fractional amount of near inrared radiation
!                     absorbed by the clouds (at cloud levels)
!      EM_LW emissivity for the clouds (at cloud levels)
!---------------------------------------------------------------------
integer, intent(out), dimension(:,:,:) :: cldtop,cldbas
integer, intent(out), dimension(:,:)  ::  nclds

 real, intent(out), dimension(:,:,:) :: r_uv,r_nir,ab_uv,ab_nir,em_lw
 real, intent(out), dimension(:,:,:) :: cldamt
 

call diag_cloud_sum(is,js, &
                    temp,qmix,rhum,omega,lgscldelq,cnvcntq,convprc,kbot)
!---------------------------------------------------------------------
! Input Arguments
!      IS,JS    starting i,j indices from the full horizontal grid
!      TEMP     Temperature (Deg K) at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      QMIX     Mixing Ratio at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      RHUM     Relative humidity fraction at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      OMEGA   Pressure vertical velocity at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      LGSCLDELQ  Averaged rate of change in mix ratio due to lg scale precip
!               at full model levels
!               (dimensioned IDIM x JDIM x kx)
!      CNVCNTQ  Accumulated count of change in mix ratio due to conv precip
!               at full model levels
!               (dimensioned IDIM x JDIM x kx)
!      CONVPRC Accumulated conv precip rate summed over all
!               full model levels (mm/day )
!               (dimensioned IDIM x JDIM)
!      KBOT      OPTIONAL; lowest model level index array
!                   (dimensioned IDIM x JDIM)
! ******* kbot will be used to select only those qmix values that are really
! ******* needed (typically this will be the bottom level except for
! ******* step mountains
!-----------------------------------------------------------------------
 integer, intent(in)                 :: is,js
 real, intent(in), dimension (:,:,:) ::  temp,qmix,rhum,omega
 real, intent(in), dimension (:,:,:) ::  lgscldelq,cnvcntq
 real, intent(in), dimension (:,:)   ::  convprc

 integer, intent(in), OPTIONAL, dimension(:,:) :: kbot
 

 call diag_cloud_avg (is, js, temp,qmix,rhum,omega, &
                           lgscldelq,cnvcntq,convprc,ierr)
!-----------------------------------------------------------------------
! Input Arguments
!      IS,JS    starting i,j indices from the full horizontal grid
!-----------------------------------------------------------------------
 integer, intent(in)                    :: is, js
!!-----------------------------------------------------------------------
! Input/Output Arguments
!      TEMP     Temperature (Deg K) at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      QMIX     Mixing Ratio at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      RHUM     Relative humidity fraction at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      OMEGA   Pressure vertical velocity at full model levels
!                   (dimensioned IDIM x JDIM x kx)
!      LGSCLDELQ  Averaged rate of change in mix ratio due to lg scale precip
!               at full model levels
!               (dimensioned IDIM x JDIM x kx)
!      CNVCNTQ  Accumulated count of change in mix ratio due to conv precip
!               at full model levels
!               (dimensioned IDIM x JDIM x kx)
!      CONVPRC Accumulated conv precip rate summed over all
!               full model levels (mm/day )
!               (dimensioned IDIM x JDIM)
-----------------------------------------------------------------------
      real, intent(inout), dimension(:,:,:) :: temp,qmix,rhum,omega
      real, intent(inout), dimension(:,:,:) :: lgscldelq,cnvcntq
      real, intent(inout), dimension(:,:)   :: convprc
!-----------------------------------------------------------------------
! Output Argument
!      IERR     Error flag
!-----------------------------------------------------------------------
   integer, intent(out)                   :: ierr
 
 

call diag_cloud_end ()
there are no arguments to this routine


NAMELIST

&diag_cloud_nml
!     RHC -    critical humidity value (ras = 0.8 - 0.84, mca =0.7)
!              (note:  in vers >= 0.9.3 a function of 3 levels
!                i.e.,"high" , "mid", "low" - but here is more general)
!     PBOUNDS - sets pressure bounds for RHC (dimension = size(rhc) - 1
!     DO_AVERAGE - logical flag for time averaging cloud predictor variables
!     LQUADRA - logical switch for turning on quadratic relation
!             for calculating rhum clouds from rhum,
!             i.e., true for quadratice scheme, false for linear scheme
!     LRHCNV - logical switch for using rhum fields as follows:
!              if true - use rel humidities modified for presence of 
!              convective clouds (rhumcnv), otherwise use original 
!              rel humidities (rhum)
!     LOMEGA - logical switch for turning on omega correction to rhum 
!              clouds - true for omega correction, otherwise false 
!     LCNVCLD - logical switch for turning on calculation of deep convective 
!              clouds - true for deep convective clouds, otherwise false 
!     L_THEQV - logical switch for turning on calculation of shallow convective 
!              clouds - true for shallow convective clouds, otherwise false 
!     LINVERS - logical switch for turning on calculation of marine stratus 
!              clouds - true for marine stratus, otherwise false 
!     LSLINGO - logical variable = true apply Slingo marine stratus 
!                scheme, otherwise = false. 
!     LREGRSC - logical variable = true apply Tim Li marine stratus 
!                scheme, otherwise = false. Slingo & Li schemes may be
!                used in combination, but atleast one scheme must be used. 
!     LTHICK_HIGH - logical variable = true -> allow possibility of raising
!               high cloud tops one sigma level to increase their thickness
!               from 1 to nmax levels; otherwise they remain thin 
!               (1 level)
!     LTHICK_MID - logical variable = true -> allow possibility of raising
!               mid cloud tops one sigma level to increase their thickness
!               from 1 to nmax levels; otherwise they remain thin 
!               (1 level)
!     LTHICK_LOW - logical variable = true -> allow possibility of raising
!               low cloud tops one sigma level to increase their thickness
!               from 1 to nmax levels; otherwise they remain thin 
!               (1 level)
!     HIGH_LEV_CLOUD_INDEX - level above which no clouds are allowed to form 
!              (model level index)
!     NOFOG - logical switch for not allowing rhum clouds (or fog)
!             to occur beneath a certain level (low_lev_cloud_index) -> 
!              nofog = true
!             to allow clouds at the lowest model level -> nofog = false
!     LOW_LEV_CLOUD_INDEX - level below which no clouds are allowed to occur 
!               when nofog = true (model level index)
!     NBAND - max number of radiative bands to be considered for some
!              cloud properties
!     PSHALLOW - top of shallow convective layer (pressure level - n/m**2 )
!     WCUT0 - omega cutoff value for omega cloud depletion factor = 0
!     WCUT1 - omega cutoff value for omega cloud depletion factor = 1

CHANGE HISTORY

Revision history

changes (07/13/2000)

     MPP version created. Minor changes for open_file, error_mesg,
     and Fortran write statements.

ERROR MESSAGES

Warning in diag_cloud_init:

    No cloud restart file found; ierr = 1
Error flag set = 1 in diag_cloud_avg:

    indicates potential divide by zero in cloud predictor averaging process

REFERENCE

Gordon, C.T., 1992. Comparison of 30-day integrations with and without cloud-radiation
                         interaction. Mon. Wea. Rev., 120, 1244-1277.
 
 
 
 


KNOWN BUGS

     There are no known bugs.


NOTES


   Code developed by Tony Gordon & Bill Stern
   Original code ~ 1992.
   First Fortran 90 version created by Bill Stern in September 1999.
   
   cloud radiative properties are calculated via a call to cloud_tau_driver which is the driver routine for
   module diag_cloud_rad_mod.  the calling interface is: 
      call cloud_tau_driver (pfull,phalf,qmix_kx,nclds,icld,cldamt, &
                 cldtop, cldbas,delp_true,tempcld, &
                 lhight,lhighb, lmidt, lmidb, llowt,lk, &
                 r_uv,r_nir,ab_uv,ab_nir,em_lw,tau, coszen, psfc )





FUTURE PLANS

     Complete marine stratus code