1 !MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
3 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !MNH_LIC for details. version 1.
5 !-----------------------------------------------------------------
6 !--------------- special set of characters for RCS information
7 !-----------------------------------------------------------------
9 ! MASDEV4_7 microph 2006/06/06 18:25:10
10 !-----------------------------------------------------------------
11 ! #######################
12 MODULE MODI_C3R5_ADJUST
13 ! #######################
17 SUBROUTINE C3R5_ADJUST( KRR, KMI, HFMFILE, HLUOUT, HRAD, &
18 HTURBDIM, OCLOSE_OUT, OSUBG_COND, PTSTEP, &
19 PRHODREF, PRHODJ, PEXNREF, PSIGS, PPABST, &
20 PRVT, PRCT, PRRT, PRIT, PRST, PRGT, PRHT, &
21 PRVS, PRCS, PRRS, PRIS, PRSS, PRGS, PRHS, &
22 PCCT, PCIT, PCNUCS, PCCS, PINUCS, PCIS, &
25 INTEGER, INTENT(IN) :: KRR ! Number of moist variables
26 INTEGER, INTENT(IN) :: KMI ! Model index
27 CHARACTER(LEN=*), INTENT(IN) :: HFMFILE ! Name of the output FM-file
28 CHARACTER(LEN=*), INTENT(IN) :: HLUOUT ! Output-listing name for
30 CHARACTER*4, INTENT(IN) :: HTURBDIM ! Dimensionality of the
32 CHARACTER*4, INTENT(IN) :: HRAD ! Radiation scheme name
33 LOGICAL, INTENT(IN) :: OCLOSE_OUT ! Conditional closure of
35 LOGICAL, INTENT(IN) :: OSUBG_COND ! Switch for Subgrid
37 REAL, INTENT(IN) :: PTSTEP ! Time step
39 REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODREF! Dry density of the
41 REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODJ ! Dry density * Jacobian
42 REAL, DIMENSION(:,:,:), INTENT(IN) :: PEXNREF ! Reference Exner function
43 REAL, DIMENSION(:,:,:), INTENT(IN) :: PSIGS ! Sigma_s at time t
44 REAL, DIMENSION(:,:,:), INTENT(IN) :: PPABST ! Absolute Pressure at t
46 REAL, DIMENSION(:,:,:), INTENT(IN) :: PRVT ! Water vapor m.r. at t
47 REAL, DIMENSION(:,:,:), INTENT(IN) :: PRCT ! Cloud water m.r. at t
48 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRRT ! Rain water m.r. at t
49 REAL, DIMENSION(:,:,:), INTENT(IN) :: PRIT ! Cloud ice m.r. at t
50 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRST ! Aggregate m.r. at t
51 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRGT ! Graupel m.r. at t
52 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRHT ! Hail m.r. at t
54 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PRVS ! Water vapor m.r. source
55 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PRCS ! Cloud water m.r. source
56 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRRS ! Rain water m.r. at t+1
57 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PRIS ! Cloud ice m.r. at t+1
58 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRSS ! Aggregate m.r. at t+1
59 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRGS ! Graupel m.r. at t+1
60 REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(IN) :: PRHS ! Hail m.r. at t+1
62 REAL, DIMENSION(:,:,:), INTENT(IN) :: PCCT ! Cloud water conc. at t
63 REAL, DIMENSION(:,:,:), INTENT(IN) :: PCIT ! Cloud ice conc. at t
64 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCNUCS ! Nucl. aero. conc. source
65 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCCS ! Cloud water conc. source
66 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINUCS ! Ice Nucl. conc. source
67 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCIS ! Cloud ice conc. source
69 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PTHS ! Theta source
70 REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSRCS ! Second-order flux
71 ! s'rc'/2Sigma_s2 at time t+1
72 ! multiplied by Lambda_3
73 REAL, DIMENSION(:,:,:), INTENT(OUT) :: PCLDFR ! Cloud fraction
75 END SUBROUTINE C3R5_ADJUST
79 END MODULE MODI_C3R5_ADJUST
81 ! ##########################################################################
82 SUBROUTINE C3R5_ADJUST( KRR, KMI, HFMFILE, HLUOUT, HRAD, &
83 HTURBDIM, OCLOSE_OUT, OSUBG_COND, PTSTEP, &
84 PRHODREF, PRHODJ, PEXNREF, PSIGS, PPABST, &
85 PRVT, PRCT, PRRT, PRIT, PRST, PRGT, PRHT, &
86 PRVS, PRCS, PRRS, PRIS, PRSS, PRGS, PRHS, &
87 PCCT, PCIT, PCNUCS, PCCS, PINUCS, PCIS, &
89 ! ##########################################################################
91 !!**** *C3R5_ADJUST* - compute the fast microphysical sources
95 !! The purpose of this routine is to compute the fast microphysical sources
96 !! through an explict scheme and a saturation ajustement procedure.
101 !! Reisin et al., 1996 for the explicit scheme when ice is present
102 !! Langlois, Tellus, 1973 for the implict adjustment for the cloud water
103 !! (refer also to book 1 of the documentation).
110 !! IMPLICIT ARGUMENTS
111 !! ------------------
113 !! XP00 ! Reference pressure
114 !! XMD,XMV ! Molar mass of dry air and molar mass of vapor
115 !! XRD,XRV ! Gaz constant for dry air, gaz constant for vapor
116 !! XCPD,XCPV ! Cpd (dry air), Cpv (vapor)
118 !! XTT ! Triple point temperature
119 !! XLVTT ! Vaporization heat constant
120 !! XALPW,XBETAW,XGAMW ! Constants for saturation vapor
121 !! ! pressure function
124 !! Module MODD_BUDGET:
131 !! Module MODD_LES : NCTR_LES,LTURB_LES,NMODNBR_LES
132 !! XNA declaration (cloud fraction as global var)
137 !! Book 1 and Book2 of documentation ( routine FAST_TERMS )
138 !! Langlois, Tellus, 1973
141 !! E. Richard * Laboratoire d'Aerologie*
147 !! Modifications: March 1, 1995 (J.M. Carriere)
148 !! Introduction of cloud water with order 1
150 !! Modifications: June 8, 1995 ( J.Stein )
152 !! Modifications: August 30, 1995 ( J.Stein )
153 !! add Lambda3 for the subgrid condensation
155 !! October 16, 1995 (J. Stein) change the budget calls
156 !! March 16, 1996 (J. Stein) store the cloud fraction
157 !! April 03, 1996 (J. Stein) displace the nebulosity
158 !! computation in the all and nothing case
159 !! April 15, 1996 (J. Stein) displace the lambda 3
160 !! multiplication and change the nebulosity threshold
161 !! September 16, 1996 (J. Stein) bug in the SG cond for
163 !! October 10, 1996 (J. Stein) reformulate the Subgrid
164 !! condensation scheme
165 !! October 8, 1996 (Cuxart,Sanchez) Cloud frac. LES diag (XNA)
166 !! December 6, 1996 (J.-P. Pinty) correction of Delta_2
167 !! November 5, 1996 (J. Stein) remove Rnp<0 values
168 !! November 13 1996 (V. Masson) add prints in test above
169 !! March 11, 1997 (J.-M. Cohard) C2R2 option
170 !! April 6, 2001 (J.-P. Pinty) C3R5 option
172 !-------------------------------------------------------------------------------
174 PRINT *,'C3R5_ADJUST IS NOT YET DEVELOPPED'
179 END SUBROUTINE C3R5_ADJUST