source: LMDZ6/branches/Amaury_dev/libf/phylmd/alpale_th.F90 @ 5111

Last change on this file since 5111 was 5111, checked in by abarral, 4 months ago

Put abort_physic into a module
Remove -g option from makelmdz_fcm, since that option is linked to a header file that isn't included anywhere.
(lint) light lint on traversed files

  • Property svn:keywords set to Id
File size: 13.1 KB
Line 
1
2! $Id: alpale_th.F90 5111 2024-07-24 10:17:33Z abarral $
3
4SUBROUTINE alpale_th( dtime, lmax_th, t_seri, cell_area,  &
5                       cin, s2, n2, strig,  &
6                       ale_bl_trig, ale_bl_stat, ale_bl,  &
7                       alp_bl, alp_bl_stat, &
8                       proba_notrig, random_notrig, birth_rate)
9
10! **************************************************************
11! *
12! ALPALE_TH                                                    *
13! *
14! *
15! written by   : Jean-Yves Grandpeix, 11/05/2016              *
16! modified by :                                               *
17! **************************************************************
18
19  USE dimphy
20  USE ioipsl_getin_p_mod, ONLY: getin_p
21  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
22  USE lmdz_abort_physic, ONLY: abort_physic
23
24  IMPLICIT NONE
25
26!================================================================
27! Auteur(s)   : Jean-Yves Grandpeix, 11/05/2016
28! Objet : Contribution of the thermal scheme to Ale and Alp
29!================================================================
30
31! Input arguments
32!----------------
33  REAL, INTENT(IN)                                           :: dtime
34  REAL, DIMENSION(klon), INTENT(IN)                          :: cell_area
35  INTEGER, DIMENSION(klon), INTENT(IN)                       :: lmax_th
36  REAL, DIMENSION(klon,klev), INTENT(IN)                     :: t_seri
37  REAL, DIMENSION(klon), INTENT(IN)                          :: ale_bl_stat
38  REAL, DIMENSION(klon), INTENT(IN)                          :: cin
39  REAL, DIMENSION(klon), INTENT(IN)                          :: s2, n2, strig
40                                                               
41  REAL, DIMENSION(klon), INTENT(INOUT)                       :: ale_bl_trig, ale_bl
42  REAL, DIMENSION(klon), INTENT(INOUT)                       :: alp_bl
43  REAL, DIMENSION(klon), INTENT(INOUT)                       :: alp_bl_stat
44  REAL, DIMENSION(klon), INTENT(INOUT)                       :: proba_notrig
45
46  REAL, DIMENSION(klon), INTENT(OUT)                         :: random_notrig
47
48  REAL, DIMENSION(klon), INTENT(OUT)                         :: birth_rate
49
50  include "alpale.h"
51
52! Local variables
53!----------------
54  INTEGER                                                    :: i
55  LOGICAL, SAVE                                              :: first = .TRUE.
56  LOGICAL, SAVE                                              :: multiply_proba_notrig = .FALSE.
57  REAL, SAVE                                                 :: random_notrig_max=1.
58  REAL, SAVE                                                 :: cv_feed_area
59  REAL                                                       :: birth_number
60  REAL, DIMENSION(klon)                                      :: ale_bl_ref
61  REAL, DIMENSION(klon)                                      :: tau_trig
62
63    !$OMP THREADPRIVATE(multiply_proba_notrig)
64    !$OMP THREADPRIVATE(random_notrig_max)
65    !$OMP THREADPRIVATE(cv_feed_area)
66    !$OMP THREADPRIVATE(first)
67
68 REAL umexp  ! expression of (1.-exp(-x))/x valid for all x, especially when x->0
69 REAL x
70
71     CHARACTER (LEN=20) :: modname='alpale_th'
72     CHARACTER (LEN=80) :: abort_message
73     
74 umexp(x) = max(sign(1.,x-1.e-3),0.)*(1.-exp(-x))/max(x,1.e-3) + &
75            (1.-max(sign(1.,x-1.e-3),0.))*(1.-0.5*x*(1.-x/3.*(1.-0.25*x)))  !!! correct formula            (jyg)
76!!!            (1.-max(sign(1.,x-1.e-3),0.))*(-0.5*x*(1.-x/3.*(1.-0.25*x))) !!! bug introduced by mistake  (jyg)
77!!!            (1.-max(sign(1.,x-1.e-3),0.))*(1.-0.5*x*(1.-x/3.*(1.-0.25*x)))  !!! initial correct formula (jyg)
78
79!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
80!  JYG, 20160513 : Introduction of the Effective Lifting Power (ELP), which
81! takes into account the area (cv_feed_area) covered by thermals contributing
82! to each cumulonimbus.
83!   The use of ELP prevents singularities when the trigger probability tends to
84! zero. It is activated by iflag_clos_bl = 3.
85!   The ELP values are stored in the ALP_bl variable.
86
87!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
88
89    IF (first) THEN
90      CALL getin_p('multiply_proba_notrig',multiply_proba_notrig)
91      IF (iflag_clos_bl < 3) THEN
92         random_notrig_max=1.
93         CALL getin_p('random_notrig_max',random_notrig_max)
94      ELSEIF (iflag_clos_bl == 3) THEN  ! (iflag_clos_bl .LT. 3)
95         cv_feed_area = 1.e10   ! m2
96         CALL getin_p('cv_feed_area', cv_feed_area)
97      ENDIF  !! (iflag_clos_bl .LT. 3)
98      first=.FALSE.
99    ENDIF
100
101!!
102!!   Control of the multiplication of no-trigger probabilities between calls
103!! to the convection scheme. If multiply_proba_notrig is .FALSE., then
104!! proba_notrig is set to 1 at each CALL to alpale_th, so that only the last CALL
105!! plays a role in the triggering of convection. If it is .TRUE., then propa_notrig
106!! is saved between calls to convection and is reset to 1 only after calling the
107!! convection scheme.
108!!    For instance, if the probability of no_trigger is 0.9 at each call, and if
109!! there are 3 calls to alpale_th between calls to the convection scheme, then the
110!! probability of triggering convection will be 0.1 (= 1.-0.9) if
111!! multiply_proba_notrig is .FALSE. and 0.271 (= 1.-0.9^3) if multiply_proba_notrig
112!! is .TRUE.
113!!
114    IF (.NOT.multiply_proba_notrig) THEN
115             DO i=1,klon
116                proba_notrig(i)=1.
117             ENDDO
118    ENDIF  !! (.NOT.multiply_proba_notrig)
119!!
120!!
121!---------------------------------------
122  IF (iflag_clos_bl < 3) THEN
123!---------------------------------------
124
125!      Original code (Nicolas Rochetin)
126!     --------------------------------
127          !cc nrlmd le 10/04/2012
128          !-----------Stochastic triggering-----------
129          if (iflag_trig_bl>=1) then
130
131             IF (prt_level >= 10) THEN
132                WRITE(lunout,*)'cin, ale_bl_stat, alp_bl, alp_bl_stat ', &
133                     cin, ale_bl_stat, alp_bl, alp_bl_stat
134             ENDIF
135
136
137             !----Initialisations
138             do i=1,klon
139!!jyg                proba_notrig(i)=1.
140                random_notrig(i)=1e6*ale_bl_stat(i)-int(1e6*ale_bl_stat(i))
141                if ( random_notrig(i) > random_notrig_max ) random_notrig(i)=0.
142                if ( ale_bl_trig(i) < abs(cin(i))+1.e-10 ) then
143                   tau_trig(i)=tau_trig_shallow
144                else
145                   tau_trig(i)=tau_trig_deep
146                endif
147             enddo
148
149             IF (prt_level >= 10) THEN
150                WRITE(lunout,*)'random_notrig, tau_trig ', &
151                     random_notrig, tau_trig
152                WRITE(lunout,*)'s_trig,s2,n2 ', &
153                     s_trig,s2,n2
154             ENDIF
155
156             !Option pour re-activer l'ancien calcul de Ale_bl (iflag_trig_bl=2)
157             IF (iflag_trig_bl==1) then
158
159                !----Tirage al\'eatoire et calcul de ale_bl_trig
160                do i=1,klon
161                   if ( (ale_bl_stat(i) > abs(cin(i))+1.e-10) )  then
162                      proba_notrig(i)=proba_notrig(i)* &
163                         (1.-exp(-strig(i)/s2(i)))**(n2(i)*dtime/tau_trig(i))
164                      !        print *, 'proba_notrig(i) ',proba_notrig(i)
165                      if (random_notrig(i) >= proba_notrig(i)) then
166                         ale_bl_trig(i)=ale_bl_stat(i)
167                      else
168                         ale_bl_trig(i)=0.
169                      endif
170                      birth_rate(i) = n2(i)*exp(-strig(i)/s2(i))/(tau_trig(i)*cell_area(i))
171!!!                      birth_rate(i) = max(birth_rate(i),1.e-18)
172                   else
173!!jyg                      proba_notrig(i)=1.
174                      birth_rate(i) = 0.
175                      random_notrig(i)=0.
176                      ale_bl_trig(i)=0.
177                   endif
178                enddo
179
180             ELSE IF (iflag_trig_bl>=2) then
181
182                do i=1,klon
183                   if ( (Ale_bl(i) > abs(cin(i))+1.e-10) )  then
184                      proba_notrig(i)=proba_notrig(i)* &
185                         (1.-exp(-strig(i)/s2(i)))**(n2(i)*dtime/tau_trig(i))
186                      !        print *, 'proba_notrig(i) ',proba_notrig(i)
187                      if (random_notrig(i) >= proba_notrig(i)) then
188                         ale_bl_trig(i)=Ale_bl(i)
189                      else
190                         ale_bl_trig(i)=0.
191                      endif
192                      birth_rate(i) = n2(i)*exp(-strig(i)/s2(i))/(tau_trig(i)*cell_area(i))
193!!!                      birth_rate(i) = max(birth_rate(i),1.e-18)
194                   else
195!!jyg                      proba_notrig(i)=1.
196                      birth_rate(i) = 0.
197                      random_notrig(i)=0.
198                      ale_bl_trig(i)=0.
199                   endif
200                enddo
201
202             ENDIF
203
204             IF (prt_level >= 10) THEN
205                WRITE(lunout,*)'proba_notrig, ale_bl_trig ', &
206                     proba_notrig, ale_bl_trig
207             ENDIF
208
209          endif !(iflag_trig_bl)
210
211          !-----------Statistical closure-----------
212          if (iflag_clos_bl==1) then
213
214             do i=1,klon
215                !CR: alp probabiliste
216                if (ale_bl_trig(i)>0.) then
217                   alp_bl(i)=alp_bl(i)/(1.-min(proba_notrig(i),0.999))
218                endif
219             enddo
220
221          else if (iflag_clos_bl==2) then
222
223             !CR: alp calculee dans thermcell_main
224             do i=1,klon
225                alp_bl(i)=alp_bl_stat(i)
226             enddo
227
228          else
229
230             alp_bl_stat(:)=0.
231
232          endif !(iflag_clos_bl)
233
234!---------------------------------------
235  ELSEIF (iflag_clos_bl == 3) THEN  ! (iflag_clos_bl .LT. 3)
236!---------------------------------------
237
238!      New code with Effective Lifting Power
239!     -------------------------------------
240
241          !-----------Stochastic triggering-----------
242     if (iflag_trig_bl>=1) then
243
244        IF (prt_level >= 10) THEN
245           WRITE(lunout,*)'cin, ale_bl_stat, alp_bl_stat ', &
246                cin, ale_bl_stat, alp_bl_stat
247        ENDIF
248
249        ! Use ale_bl_stat (Rochetin's code) or ale_bl (old code) according to
250        ! iflag_trig_bl value.
251        IF (iflag_trig_bl==1) then         ! use ale_bl_stat (Rochetin computation)
252         do i=1,klon
253              ale_bl_ref(i)=ale_bl_stat(i)
254         enddo
255        ELSE IF (iflag_trig_bl>=2) then    ! use ale_bl (old computation)
256         do i=1,klon
257              ale_bl_ref(i)=Ale_bl(i)
258         enddo
259        ENDIF ! (iflag_trig_bl.eq.1)
260
261
262        !----Initializations and random number generation
263        do i=1,klon
264!!jyg           proba_notrig(i)=1.
265           random_notrig(i)=1e6*ale_bl_stat(i)-int(1e6*ale_bl_stat(i))
266           if ( ale_bl_trig(i) < abs(cin(i))+1.e-10 ) then
267              tau_trig(i)=tau_trig_shallow
268           else
269              tau_trig(i)=tau_trig_deep
270           endif
271        enddo
272
273        IF (prt_level >= 10) THEN
274           WRITE(lunout,*)'random_notrig, tau_trig ', &
275                random_notrig, tau_trig
276           WRITE(lunout,*)'s_trig,s2,n2 ', &
277                s_trig,s2,n2
278        ENDIF
279
280        !----alp_bl computation
281        do i=1,klon
282           if ( (ale_bl_ref(i) > abs(cin(i))+1.e-10) )  then
283              birth_number = n2(i)*exp(-strig(i)/s2(i))
284              birth_rate(i) = birth_number/(tau_trig(i)*cell_area(i))
285!!!              birth_rate(i) = max(birth_rate(i),1.e-18)
286              proba_notrig(i)=proba_notrig(i)*exp(-birth_number*dtime/tau_trig(i))
287              Alp_bl(i) = Alp_bl(i)* &
288                          umexp(-birth_number*cv_feed_area/cell_area(i))/ &
289                          umexp(-birth_number*dtime/tau_trig(i))*  &
290                          tau_trig(i)*cv_feed_area/(dtime*cell_area(i))
291          else
292!!jyg              proba_notrig(i)=1.
293              birth_rate(i)=0.
294              random_notrig(i)=0.
295              alp_bl(i)=0.
296           endif
297        enddo
298
299        !----ale_bl_trig computation
300         do i=1,klon
301           if (random_notrig(i) >= proba_notrig(i)) then
302              ale_bl_trig(i)=ale_bl_ref(i)
303           else
304              ale_bl_trig(i)=0.
305           endif
306         enddo
307
308        IF (prt_level >= 10) THEN
309           WRITE(lunout,*)'proba_notrig, ale_bl_trig ', &
310                proba_notrig, ale_bl_trig
311        ENDIF
312
313     endif !(iflag_trig_bl .ge. 1)
314
315!---------------------------------------
316  ENDIF ! (iflag_clos_bl .LT. 3)
317!---------------------------------------
318
319          IF (prt_level >= 10) THEN
320             WRITE(lunout,*)'alpale_th: ale_bl_trig, alp_bl_stat, birth_rate ', &
321                      ale_bl_trig(1), alp_bl_stat(1), birth_rate(1)
322          ENDIF
323
324          !cc fin nrlmd le 10/04/2012
325
326          !IM/FH: 2011/02/23
327          ! Couplage Thermiques/Emanuel seulement si T<0
328          if (iflag_coupl==2) then
329             IF (prt_level >= 10) THEN
330                WRITE(lunout,*)'Couplage Thermiques/Emanuel seulement si T<0'
331             ENDIF
332             do i=1,klon
333                if (t_seri(i,lmax_th(i))>273.) then
334                   Ale_bl(i)=0.
335                endif
336             enddo
337!    print *,'In order to run with iflag_coupl=2, you have to comment out the following stop '
338!             STOP
339             abort_message='In order to run with iflag_coupl=2, you have to comment out the following abort'
340             CALL abort_physic(modname,abort_message,1)
341          endif
342   RETURN
343   END
344
Note: See TracBrowser for help on using the repository browser.