source: LMDZ6/trunk/libf/phylmd/lmdz_wake_ini.f90 @ 5765

Last change on this file since 5765 was 5761, checked in by jyg, 3 weeks ago

Modifications of lmdz_wake.f90:
1/ reorganization of the computations relative to the vertical
differential advection, to the differential convective heating
and to the entrainment in the two columns (w) and (x).
2/ new implicit upstream scheme for the vertical differential
advection. The use of this scheme is controlled by the flag

flag_dadv_implicit.

True ==> use implicit upstream scheme
Default = False.

File size: 9.8 KB
Line 
1MODULE lmdz_wake_ini
2IMPLICIT NONE
3
4  ! ============================================================================
5
6
7  ! But : Decrire le comportement des poches froides apparaissant dans les
8  ! grands systemes convectifs, et fournir l'energie disponible pour
9  ! le declenchement de nouvelles colonnes convectives.
10
11  ! State variables :
12  ! deltatw    : temperature difference between wake and off-wake regions
13  ! deltaqw    : specific humidity difference between wake and off-wake regions
14  ! sigmaw     : fractional area covered by wakes.
15  ! wdens      : number of wakes per unit area
16
17  ! -------------------------------------------------------------------------
18  ! Declaration de variables
19  ! -------------------------------------------------------------------------
20
21  ! Variables a fixer
22!jyg<
23!!  REAL, SAVE                                            :: stark, wdens_ref, coefgw, alpk
24  INTEGER, SAVE, PROTECTED                                    :: prt_level
25  REAL, SAVE, PROTECTED, DIMENSION(2)                         :: wdens_ref
26  REAL, SAVE, PROTECTED                                       :: stark, coefgw, alpk, wk_pupper
27!>jyg
28  REAL, SAVE, PROTECTED                                       :: crep_upper, crep_sol 
29  !$OMP THREADPRIVATE(prt_level,stark, wdens_ref, coefgw, alpk, wk_pupper, crep_upper, crep_sol)
30
31  REAL, SAVE, PROTECTED                                       :: tau_cv
32  !$OMP THREADPRIVATE(tau_cv)
33
34   REAL, SAVE, PROTECTED                                       :: wk_delta_t_min
35  !$OMP THREADPRIVATE(wk_delta_t_min)
36
37   REAL, SAVE, PROTECTED                                       :: wk_frac_int_delta_t
38  !$OMP THREADPRIVATE(wk_frac_int_delta_t)
39
40  REAL, SAVE, PROTECTED                                       :: rzero, aa0 ! minimal wake radius and area
41  !$OMP THREADPRIVATE(rzero, aa0)
42
43  LOGICAL, SAVE, PROTECTED                                    :: ok_bug_gfl
44  !$OMP THREADPRIVATE(ok_bug_gfl)
45  LOGICAL, SAVE, PROTECTED                                    :: flag_wk_check_trgl
46  !$OMP THREADPRIVATE(flag_wk_check_trgl)
47  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_act
48  !$OMP THREADPRIVATE(iflag_wk_act)
49
50  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_check_trgl
51  !$OMP THREADPRIVATE(iflag_wk_check_trgl)
52  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_pop_dyn
53  !$OMP THREADPRIVATE(iflag_wk_pop_dyn)
54
55  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_profile
56  !$OMP THREADPRIVATE(iflag_wk_profile)
57
58  LOGICAL, SAVE, PROTECTED                                    :: flag_dadv_implicit
59  !$OMP THREADPRIVATE(flag_dadv_implicit)
60
61  INTEGER, SAVE, PROTECTED                                    :: wk_nsub
62  !$OMP THREADPRIVATE(wk_nsub)
63
64  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_new_ptop
65  !$OMP THREADPRIVATE(iflag_wk_new_ptop)
66
67  REAL, SAVE, PROTECTED                                       :: wdensinit ! Minimum wake density used to restart wakes from a wake-free state
68  !$OMP THREADPRIVATE(wdensinit)
69  REAL, SAVE, PROTECTED                                       :: wdensthreshold ! Threshold wake density below which wakes are killed
70  !$OMP THREADPRIVATE(wdensthreshold)
71  REAL, SAVE, PROTECTED                                       :: sigmad, hwmin, wapecut, cstart
72  !$OMP THREADPRIVATE(sigmad, hwmin, wapecut, cstart)
73  REAL, SAVE, PROTECTED                                       :: sigmaw_max
74  !$OMP THREADPRIVATE(sigmaw_max) 
75  REAL, SAVE, PROTECTED                                       :: dens_rate
76  !$OMP THREADPRIVATE(dens_rate)
77  REAL, SAVE, PROTECTED                                       :: epsilon_loc
78  !$OMP THREADPRIVATE(epsilon_loc)
79  REAL, SAVE, PROTECTED                                       :: epsim1,RG,RD
80  !$OMP THREADPRIVATE(epsim1,RG,RD)
81  REAL, SAVE, PROTECTED                                        ::smallestreal
82  !$OMP THREADPRIVATE(smallestreal)
83  REAL, SAVE, PROTECTED                                        :: wk_int_delta_t_min
84  !$OMP THREADPRIVATE(wk_int_delta_t_min)
85
86! CPP key used only in this module for debugging purposes. jyg 09/24
87  LOGICAL, SAVE, PROTECTED :: CPPKEY_IOPHYS_WK = .FALSE.
88  !$OMP THREADPRIVATE(CPPKEY_IOPHYS_WK)
89
90
91
92CONTAINS
93
94  ! =========================================================================
95  SUBROUTINE wake_ini(rg_in,rd_in,rv_in,prt_lev)
96  ! =========================================================================
97
98  ! **************************************************************
99  ! *
100  ! WAKE                                                        *
101  ! retour a un Pupper fixe                                *
102  ! *
103  ! written by   :  GRANDPEIX Jean-Yves   09/03/2000            *
104  ! modified by :   ROEHRIG Romain        01/29/2007            *
105  ! **************************************************************
106
107  ! -------------------------------------------------------------------------
108  ! Initialisations
109  ! -------------------------------------------------------------------------
110
111  USE ioipsl_getin_p_mod, ONLY : getin_p
112  real eps
113  integer, intent(in) :: prt_lev
114  real, intent(in) :: rg_in,rd_in,rv_in
115
116  smallestreal=tiny(smallestreal)
117!
118  prt_level=prt_lev
119  epsilon_loc=1.E-15
120  wapecut=1. ! previously 5.
121!
122  rzero = 5000.
123  CALL getin_p('rzero_wk', rzero)
124  aa0 = 3.14*rzero*rzero
125!
126  ! Essais d'initialisation avec sigmaw = 0.02 et hw = 10.
127!!  sigmad=0.005
128  sigmad=0.02
129  CALL getin_p('sigmad', sigmad)
130  hwmin=10.
131!
132!!wdensthreshold=1.e-12
133  wdensthreshold=1.e-14
134  wdensthreshold=2.e-14
135  CALL getin_p('wdensthreshold', wdensthreshold)
136!
137  IF (sigmad < 0.) THEN
138    sigmad = abs(sigmad)
139!!    wdensmin=sigmad/(3.14*rzero**2)
140    wdensinit=sigmad/(3.14*rzero**2)
141  ELSE
142    wdensinit = wdensthreshold/2.
143  ENDIF
144!
145!
146  ! cc nrlmd
147  sigmaw_max=0.4
148  dens_rate=0.1
149
150  eps = rd_in/rv_in
151  epsim1 = 1.0/eps - 1.0
152  RG=rg_in
153  RD=rd_in
154
155
156  ! cc
157  ! Longueur de maille (en m)
158  ! -------------------------------------------------------------------------
159
160  ! ALON = 3.e5
161  ! alon = 1.E6
162
163  ! Configuration de coefgw,stark,wdens (22/02/06 by YU Jingmei)
164
165  ! coefgw : Coefficient pour les ondes de gravite
166  ! stark : Coefficient k dans Cstar=k*sqrt(2*WAPE)
167  ! wdens : Densite surfacique de poche froide
168  ! -------------------------------------------------------------------------
169
170  ! cc nrlmd      coefgw=10
171  ! coefgw=1
172  ! wdens0 = 1.0/(alon**2)
173  ! cc nrlmd      wdens = 1.0/(alon**2)
174  ! cc nrlmd      stark = 0.50
175  ! CRtest
176  ! cc nrlmd      alpk=0.1
177  ! alpk = 1.0
178  ! alpk = 0.5
179  ! alpk = 0.05
180
181
182
183  crep_upper = 0.9
184  crep_sol = 1.0
185
186  ! Flag concerning the bug in gfl computation
187  ok_bug_gfl = .True.
188  call getin_p('ok_bug_gfl', ok_bug_gfl)
189
190  ! Get wapecut from parameter file
191  wapecut = 1.
192
193print*,'wapecut',wapecut
194  CALL getin_p('wapecut', wapecut)
195print*,'wapecut',wapecut
196
197  ! cc nrlmd Lecture du fichier wake_param.data
198
199
200  ! cc nrlmd Lecture du fichier wake_param.data
201  stark=0.33
202  CALL getin_p('stark',stark)
203  cstart = stark*sqrt(2.*wapecut)
204
205  alpk=0.25
206  CALL getin_p('alpk',alpk)
207 
208  wk_pupper=0.6
209  CALL getin_p('wk_pupper',wk_pupper)
210
211
212!jyg<
213!!  wdens_ref=8.E-12
214!!  CALL getin_p('wdens_ref',wdens_ref)
215  wdens_ref(1)=8.E-12
216  wdens_ref(2)=8.E-12
217  CALL getin_p('wdens_ref_o',wdens_ref(1))    !wake number per unit area ; ocean
218  CALL getin_p('wdens_ref_l',wdens_ref(2))    !wake number per unit area ; land
219!>jyg
220!
221!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
222!!!!!!!!!  Population dynamics parameters    !!!!!!!!!!!!!!!!!!!!!!!!!!!!
223!------------------------------------------------------------------------
224
225  iflag_wk_pop_dyn = 0
226  CALL getin_p('iflag_wk_pop_dyn',iflag_wk_pop_dyn) ! switch between wdens prescribed
227                                                    ! and wdens prognostic
228  iflag_wk_act = 0
229  CALL getin_p('iflag_wk_act',iflag_wk_act) ! 0: act(:)=0.
230                                            ! 1: act(:)=1.
231                                            ! 2: act(:)=f(Wape)
232
233  iflag_wk_profile = 0
234  CALL getin_p('iflag_wk_profile',iflag_wk_profile) ! switch between wdens prescribed
235                                                    ! and wdens prognostic
236 ! iflag_wk_profile = 0
237  iflag_wk_new_ptop = 0
238  CALL getin_p('iflag_wk_new_ptop',iflag_wk_new_ptop)
239
240  wk_nsub = 10
241  CALL getin_p('wk_nsub',wk_nsub)
242
243  tau_cv = 4000.
244  CALL getin_p('tau_cv', tau_cv)
245 
246  wk_delta_t_min = 0.
247  CALL getin_p('wk_delta_t_min', wk_delta_t_min)
248 
249  wk_int_delta_t_min = 10.
250  CALL getin_p('wk_int_delta_t_min', wk_int_delta_t_min)
251 
252  wk_frac_int_delta_t = 0.9
253  CALL getin_p('wk_frac_int_delta_t', wk_frac_int_delta_t)
254
255  flag_dadv_implicit = .FALSE.
256  CALL getin_p('flag_dadv_implicit', flag_dadv_implicit)
257
258  CALL getin_p('CPPKEY_IOPHYS_WK', CPPKEY_IOPHYS_WK)
259
260
261!------------------------------------------------------------------------
262
263  coefgw=4.
264  CALL getin_p('coefgw',coefgw)
265
266  WRITE(*,*) 'stark=', stark
267  WRITE(*,*) 'alpk=', alpk
268  WRITE(*,*) 'wk_pupper=', wk_pupper
269!jyg<
270!!  WRITE(*,*) 'wdens_ref=', wdens_ref
271  WRITE(*,*) 'wdens_ref_o=', wdens_ref(1)
272  WRITE(*,*) 'wdens_ref_l=', wdens_ref(2)
273!>jyg
274  WRITE(*,*) 'iflag_wk_pop_dyn=',iflag_wk_pop_dyn
275  WRITE(*,*) 'iflag_wk_act',iflag_wk_act
276  WRITE(*,*) 'coefgw=', coefgw
277
278  flag_wk_check_trgl=.false.
279  CALL getin_p('flag_wk_check_trgl ', flag_wk_check_trgl)
280  WRITE(*,*) 'flag_wk_check_trgl=', flag_wk_check_trgl
281  WRITE(*,*) 'flag_wk_check_trgl OBSOLETE. Utilisr iflag_wk_check_trgl plutot'
282  iflag_wk_check_trgl=0 ; IF (flag_wk_check_trgl) iflag_wk_check_trgl=1
283  CALL getin_p('iflag_wk_check_trgl ', iflag_wk_check_trgl)
284  WRITE(*,*) 'iflag_wk_check_trgl=', iflag_wk_check_trgl
285 
286  WRITE(*,*) 'wk_delta_t_min=', wk_delta_t_min
287  WRITE(*,*) 'wk_int_delta_t_min=', wk_int_delta_t_min
288  WRITE(*,*) 'wk_frac_int_delta_t=', wk_frac_int_delta_t
289  WRITE(*,*) 'iflag_wk_new_ptop=', iflag_wk_new_ptop
290  WRITE(*,*) 'wk_nsub=', wk_nsub
291
292 RETURN
293
294END SUBROUTINE wake_ini
295
296
297
298END MODULE lmdz_wake_ini
Note: See TracBrowser for help on using the repository browser.