source: trunk/LMDZ.GENERIC/libf/phystd/thermcell_dq.F90 @ 2127

Last change on this file since 2127 was 2127, checked in by aboissinot, 6 years ago

Fix in convadj.F
New version of the thermal plume model (new entrainment and detrainment formulae, alimentation is removed)

File size: 5.7 KB
Line 
1!
2!
3!
4SUBROUTINE thermcell_dq(ngrid,nlay,ptimestep,fm,entr,detr,masse,              &
5                        q,dq,qa,lmin)
6     
7     
8!===============================================================================
9!  Purpose: Calcul du transport verticale dans la couche limite en presence de
10!           "thermiques" explicitement representes
11!           Calcul du dq/dt une fois qu'on connait les ascendances
12
13!  Modif 2013/01/04 (FH hourdin@lmd.jussieu.fr)
14!  Introduction of an implicit computation of vertical advection in the environ-
15!     ment of thermal plumes in thermcell_dq
16
17!  Modif 2019/04 (AB alexandre.boissinot@lmd.jussieu.fr)
18!     dqimpl = 1 : implicit scheme
19!     dqimpl = 0 : explicit scheme
20
21!===============================================================================
22     
23      USE print_control_mod, ONLY: prt_level
24      USe thermcell_mod, ONLY: dqimpl
25     
26      IMPLICIT NONE
27     
28     
29!===============================================================================
30! Declaration
31!===============================================================================
32     
33!     Inputs:
34!     -------
35     
36      INTEGER ngrid, nlay
37      INTEGER lmin(ngrid)
38     
39      REAL ptimestep
40      REAL masse(ngrid,nlay)
41      REAL fm(ngrid,nlay+1)
42      REAL entr(ngrid,nlay)
43      REAL detr(ngrid,nlay)
44      REAL q(ngrid,nlay)
45     
46!     Outputs:
47!     --------
48     
49      REAL dq(ngrid,nlay)
50      REAL qa(ngrid,nlay)
51     
52!     Local:
53!     ------
54     
55      INTEGER ig, l
56      INTEGER niter, iter
57     
58      REAL cfl
59      REAL qold(ngrid,nlay)
60      REAL fqa(ngrid,nlay+1)
61      REAL wqd(ngrid,nlay+1)
62      REAL zzm
63     
64!===============================================================================
65! Initialization
66!===============================================================================
67     
68      qold(:,:) = q(:,:)
69     
70!===============================================================================
71! Tracer variation computation
72!===============================================================================
73     
74!-------------------------------------------------------------------------------
75! CFL criterion computation for advection in downdraft
76!-------------------------------------------------------------------------------
77     
78      cfl = 0.
79     
80      DO l=1,nlay
81         DO ig=1,ngrid
82            zzm = masse(ig,l) / ptimestep
83            cfl = max(cfl, fm(ig,l) / zzm)
84           
85            IF (entr(ig,l).gt.zzm) THEN
86               print *, 'ERROR: entrainment is greater than the layer mass!'
87               print *, 'ig,l,entr', ig, l, entr(ig,l)
88               print *, '-------------------------------'
89               print *, 'entr*dt,mass', entr(ig,l)*ptimestep, masse(ig,l)
90               print *, '-------------------------------'
91               print *, 'fm+', fm(ig,l+1)
92               print *, 'entr,detr', entr(ig,l), detr(ig,l)
93               print *, 'fm ', fm(ig,l)
94               print *, 'entr,detr', entr(ig,l-1), detr(ig,l-1)
95               print *, 'fm-', fm(ig,l-1)
96               CALL abort
97            ENDIF
98         ENDDO
99      ENDDO
100     
101!-------------------------------------------------------------------------------
102! Computation of tracer concentrations in the ascending plume
103!-------------------------------------------------------------------------------
104     
105      DO ig=1,ngrid
106         DO l=1,lmin(ig)
107            qa(ig,l) = q(ig,l)
108         ENDDO
109      ENDDO
110     
111      DO ig=1,ngrid
112         DO l=lmin(ig)+1,nlay
113            IF ((fm(ig,l+1)+detr(ig,l))*ptimestep.gt.1.e-6*masse(ig,l)) THEN
114               qa(ig,l) = (fm(ig,l) * qa(ig,l-1) + entr(ig,l) * q(ig,l))      &
115               &        / (fm(ig,l+1) + detr(ig,l))
116            ELSE
117               qa(ig,l) = q(ig,l)
118            ENDIF
119           
120!            IF (qa(ig,l).lt.0.) THEN
121!               print *, 'WARNING: qa is negative!'
122!               print *, 'qa', qa(ig,l)
123!            ENDIF
124           
125!            IF (q(ig,l).lt.0.) THEN
126!               print *, 'WARNING: q is negative!'
127!               print *, 'q', q(ig,l)
128!            ENDIF
129         ENDDO
130      ENDDO
131     
132!-------------------------------------------------------------------------------
133! Plume vertical flux of tracer
134!-------------------------------------------------------------------------------
135     
136      DO l=2,nlay-1
137         fqa(:,l) = fm(:,l) * qa(:,l-1)
138      ENDDO
139     
140      fqa(:,1) = 0.
141      fqa(:,nlay) = 0.
142     
143!-------------------------------------------------------------------------------
144! Trace species evolution
145!-------------------------------------------------------------------------------
146     
147      IF (dqimpl==0) THEN
148         DO l=1,nlay-1
149            q(:,l) = q(:,l) + (fqa(:,l) - fqa(:,l+1) - fm(:,l) * q(:,l)       &
150            &      + fm(:,l+1) * q(:,l+1)) * ptimestep / masse(:,l)
151         ENDDO
152      ELSEIF (dqimpl==1) THEN
153         DO l=nlay-1,1,-1
154            q(:,l) = ( q(:,l) + ptimestep / masse(:,l)                        &
155            &      * ( fqa(:,l) - fqa(:,l+1) + fm(:,l+1) * q(:,l+1) ) )       &
156            &      / ( 1. + fm(:,l) * ptimestep / masse(:,l) )
157         ENDDO
158      ELSE
159         print *, 'ERROR: No corresponding scheme for mixing computations!'
160         print *, '       dqimpl must be equal to 1, 0 or -1 but'
161         print *, 'dqimpl =', dqimpl
162         call abort
163      ENDIF
164     
165!===============================================================================
166! Tendencies
167!===============================================================================
168     
169      DO l=1,nlay
170         DO ig=1,ngrid
171            dq(ig,l) = (q(ig,l) - qold(ig,l)) / ptimestep
172            q(ig,l) = qold(ig,l)
173         ENDDO
174      ENDDO
175     
176     
177RETURN
178END
Note: See TracBrowser for help on using the repository browser.