source: trunk/LMDZ.GENERIC/libf/phystd/largescale2.F @ 146

Last change on this file since 146 was 135, checked in by aslmd, 14 years ago

CHANGEMENT ARBORESCENCE ETAPE 2 -- NON COMPLET

File size: 3.3 KB
RevLine 
[135]1      SUBROUTINE largescale2(dtime, paprs, pplay, t, q,
2     s                   d_t, d_q, d_ql, rneb)
3
4      use watercommon_h, only : RLVTT
5
6      IMPLICIT none
7
8!==================================================================
9!     
10!     Purpose
11!     -------
12!     Calculates large-scale (stratiform) H2O condensation.
13!     
14!     Authors
15!     -------
16!     Adapted from the LMDTERRE code by R. Wordsworth (2009)
17!     Original author Z. X. Li (1993)
18!     
19!==================================================================
20
21#include "dimensions.h"
22#include "dimphys.h"
23#include "comcstfi.h"
24
25#include "fisice.h"
26#include "callkeys.h"
27#include "tracer.h"
28
29
30!     Arguments
31      REAL dtime ! intervalle du temps (s)
32      REAL paprs(ngridmx,nlayermx+1) ! pression a inter-couche
33      REAL pplay(ngridmx,nlayermx) ! pression au milieu de couche
34      REAL t(ngridmx,nlayermx) ! temperature (K)
35      REAL q(ngridmx,nlayermx) ! humidite specifique (kg/kg)
36      REAL d_t(ngridmx,nlayermx) ! incrementation de la temperature (K)
37      REAL d_q(ngridmx,nlayermx) ! incrementation de la vapeur d'eau
38      REAL d_ql(ngridmx,nlayermx) ! incrementation de l'eau liquide
39      REAL rneb(ngridmx,nlayermx) ! fraction nuageuse
40
41!     Options du programme
42      REAL ratqs   ! determine largeur de la distribution de vapeur
43      PARAMETER (ratqs=0.2)
44
45!     Variables locales
46      REAL CBRT
47      EXTERNAL CBRT
48      INTEGER i, k
49      REAL zt(ngridmx), zq(ngridmx)
50      REAL zcond(ngridmx)
51      REAL zdelq(ngridmx)
52      REAL zqs(ngridmx), zdqs(ngridmx)
53
54      REAL zcor(ngridmx), zdelta(ngridmx), zcvm5(ngridmx)
55      REAL zx_q(ngridmx)
56
57!     Initialisation des sorties
58      DO k = 1, nlayermx
59      DO i = 1, ngridmx
60         d_t(i,k)=0.
61         d_q(i,k)=0.
62         d_ql(i,k)=0.
63         rneb(i,k) = 0.0
64      ENDDO
65      ENDDO
66
67!     Boucle verticale (du haut vers le bas)
68      DO 9999 k = nlayermx, 1, -1
69
70      DO i = 1, ngridmx
71         zt(i)=t(i,k)
72         zq(i)=q(i,k)
73      ENDDO
74
75!     Calculer la vapeur d'eau saturante et
76!     determiner la condensation partielle
77      DO i = 1, ngridmx
78
79         call watersat_2(zt(i),pplay(i,k),zqs(i))
80         call watersat_grad(zt(i),zqs(i),zdqs(i))
81
82         !IF (zt(i).LT.t_coup) THEN
83         !   zqs(i) = qsats(zt(i))/pplay(i,k)
84         !   zdqs(i) = dqsats(zt(i),zqs(i))
85         !ELSE
86         !   zqs(i) = qsatl(zt(i))/pplay(i,k)
87         !   zdqs(i) = dqsatl(zt(i),zqs(i))
88         !ENDIF
89
90         zdelq(i) = ratqs * zq(i)
91         rneb(i,k) = (zq(i)+zdelq(i)-zqs(i)) / (2.0*zdelq(i))
92         zcond(i) = 0.0
93         zx_q(i) = (zq(i)+zdelq(i)+zqs(i))/2.0
94         if (rneb(i,k) .LE. 0.0) zx_q(i) = 0.0
95         if (rneb(i,k) .GE. 1.0) zx_q(i) = zq(i)
96         rneb(i,k) = MAX(0.0,MIN(1.0,rneb(i,k)))
97         zcond(i) = MAX(0.0,zx_q(i)-zqs(i))*rneb(i,k)/(1.+zdqs(i))
98         zcond(i) = zcond(i)/dtime ! added by RDW
99
100!     for varying particle size in rad tran and (possibly) sedimentation
101!     to be dealt with in next version...
102
103!         rice(i,k) = CBRT( 3*zcond(i)/( 4*Nmix_h2o*pi*rho_ice))
104!         rice(i,k) = max(rice(i,k),1.e-16)
105
106      ENDDO
107
108!     Tendances de t et q
109      DO i = 1, ngridmx
110         d_q(i,k) = - zcond(i)
111         d_ql(i,k) = zcond(i)
112         d_t(i,k) = zcond(i)*RLVTT/cpp
113      ENDDO
114
115 9999 CONTINUE
116
117      !print*,'rice=',rice
118      !print*,'rneb=',rneb
119
120      RETURN
121      END
Note: See TracBrowser for help on using the repository browser.