source: LMDZ6/trunk/libf/phylmd/lmdz_wake_ini.F90 @ 4771

Last change on this file since 4771 was 4744, checked in by jyg, 11 months ago

Implementation of a two radii model for wake population dynamics.
It is activated with : iflag_wk_pop_dyn=3

File size: 8.1 KB
RevLine 
[4588]1MODULE lmdz_wake_ini
[4085]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  ! -------------------------------------------------------------------------
[4230]18  ! Declaration de variables
[4085]19  ! -------------------------------------------------------------------------
20
[4230]21  ! Variables a fixer
[4085]22!jyg<
23!!  REAL, SAVE                                            :: stark, wdens_ref, coefgw, alpk
[4744]24  INTEGER, SAVE, PROTECTED                                    :: prt_level
25  REAL, SAVE, PROTECTED, DIMENSION(2)                         :: wdens_ref
26  REAL, SAVE, PROTECTED                                       :: stark, coefgw, alpk, wk_pupper
[4085]27!>jyg
[4744]28  REAL, SAVE, PROTECTED                                       :: crep_upper, crep_sol 
[4453]29  !$OMP THREADPRIVATE(stark, wdens_ref, coefgw, alpk, wk_pupper, crep_upper, crep_sol)
[4085]30
[4744]31  REAL, SAVE, PROTECTED                                       :: tau_cv
[4085]32  !$OMP THREADPRIVATE(tau_cv)
[4744]33  REAL, SAVE, PROTECTED                                       :: rzero, aa0 ! minimal wake radius and area
[4085]34  !$OMP THREADPRIVATE(rzero, aa0)
35
[4744]36  LOGICAL, SAVE, PROTECTED                                    :: ok_bug_gfl
[4695]37  !$OMP THREADPRIVATE(ok_bug_gfl)
[4744]38  LOGICAL, SAVE, PROTECTED                                    :: flag_wk_check_trgl
[4085]39  !$OMP THREADPRIVATE(flag_wk_check_trgl)
[4744]40  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_act
[4085]41  !$OMP THREADPRIVATE(iflag_wk_act)
42
[4744]43  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_check_trgl
[4085]44  !$OMP THREADPRIVATE(iflag_wk_check_trgl)
[4744]45  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_pop_dyn
[4085]46  !$OMP THREADPRIVATE(iflag_wk_pop_dyn)
47
[4744]48  INTEGER, SAVE, PROTECTED                                    :: iflag_wk_profile
[4294]49  !$OMP THREADPRIVATE(iflag_wk_profile)
50
[4744]51  REAL, SAVE, PROTECTED                                       :: wdensinit ! Minimum wake density used to restart wakes from a wake-free state
52  !$OMP THREADPRIVATE(wdensinit)
53  REAL, SAVE, PROTECTED                                       :: wdensthreshold ! Threshold wake density below which wakes are killed
54  !$OMP THREADPRIVATE(wdensthreshold)
55  REAL, SAVE, PROTECTED                                       :: sigmad, hwmin, wapecut, cstart
[4085]56  !$OMP THREADPRIVATE(sigmad, hwmin, wapecut, cstart)
[4744]57  REAL, SAVE, PROTECTED                                       :: sigmaw_max
[4085]58  !$OMP THREADPRIVATE(sigmaw_max) 
[4744]59  REAL, SAVE, PROTECTED                                       :: dens_rate
[4085]60  !$OMP THREADPRIVATE(dens_rate)
[4744]61  REAL, SAVE, PROTECTED                                       :: epsilon_loc
[4085]62  !$OMP THREADPRIVATE(epsilon_loc)
[4744]63  REAL, SAVE, PROTECTED                                       :: epsim1,RG,RD
[4085]64  !$OMP THREADPRIVATE(epsim1,RG,RD)
[4744]65  REAL, SAVE, PROTECTED                                        ::smallestreal
66  !$OMP THREADPRIVATE(smallestreal)
[4085]67
68
69
70CONTAINS
71
72  ! =========================================================================
73  SUBROUTINE wake_ini(rg_in,rd_in,rv_in,prt_lev)
74  ! =========================================================================
75
76  ! **************************************************************
77  ! *
78  ! WAKE                                                        *
79  ! retour a un Pupper fixe                                *
80  ! *
81  ! written by   :  GRANDPEIX Jean-Yves   09/03/2000            *
82  ! modified by :   ROEHRIG Romain        01/29/2007            *
83  ! **************************************************************
84
85  ! -------------------------------------------------------------------------
86  ! Initialisations
87  ! -------------------------------------------------------------------------
88
89  USE ioipsl_getin_p_mod, ONLY : getin_p
90  real eps
91  integer, intent(in) :: prt_lev
92  real, intent(in) :: rg_in,rd_in,rv_in
93
[4744]94  smallestreal=tiny(smallestreal)
95!
[4085]96  prt_level=prt_lev
97  epsilon_loc=1.E-15
98  wapecut=1. ! previously 5.
[4744]99!
100  rzero = 5000.
101  CALL getin_p('rzero_wk', rzero)
102  aa0 = 3.14*rzero*rzero
103!
[4085]104  ! Essais d'initialisation avec sigmaw = 0.02 et hw = 10.
[4744]105!!  sigmad=0.005
[4085]106  sigmad=0.02
[4744]107  CALL getin_p('sigmad', sigmad)
[4085]108  hwmin=10.
[4744]109!
110!!wdensthreshold=1.e-12
111  wdensthreshold=1.e-14
112  wdensthreshold=2.e-14
113  CALL getin_p('wdensthreshold', wdensthreshold)
114!
115  IF (sigmad < 0.) THEN
116    sigmad = abs(sigmad)
117!!    wdensmin=sigmad/(3.14*rzero**2)
118    wdensinit=sigmad/(3.14*rzero**2)
119  ELSE
120    wdensinit = wdensthreshold/2.
121  ENDIF
122!
123!
[4085]124  ! cc nrlmd
125  sigmaw_max=0.4
126  dens_rate=0.1
127
128  eps = rd_in/rv_in
129  epsim1 = 1.0/eps - 1.0
130  RG=rg_in
131  RD=rd_in
132
133
134  ! cc
135  ! Longueur de maille (en m)
136  ! -------------------------------------------------------------------------
137
138  ! ALON = 3.e5
139  ! alon = 1.E6
140
141  ! Configuration de coefgw,stark,wdens (22/02/06 by YU Jingmei)
142
[4230]143  ! coefgw : Coefficient pour les ondes de gravite
[4085]144  ! stark : Coefficient k dans Cstar=k*sqrt(2*WAPE)
[4230]145  ! wdens : Densite surfacique de poche froide
[4085]146  ! -------------------------------------------------------------------------
147
148  ! cc nrlmd      coefgw=10
149  ! coefgw=1
150  ! wdens0 = 1.0/(alon**2)
151  ! cc nrlmd      wdens = 1.0/(alon**2)
152  ! cc nrlmd      stark = 0.50
153  ! CRtest
154  ! cc nrlmd      alpk=0.1
155  ! alpk = 1.0
156  ! alpk = 0.5
157  ! alpk = 0.05
158
159
160
161  crep_upper = 0.9
162  crep_sol = 1.0
163
[4695]164  ! Flag concerning the bug in gfl computation
165  ok_bug_gfl = .True.
166  call getin_p('ok_bug_gfl', ok_bug_gfl)
167
[4085]168  ! Get wapecut from parameter file
169  wapecut = 1.
170
171print*,'wapecut',wapecut
172  CALL getin_p('wapecut', wapecut)
173print*,'wapecut',wapecut
174
175  ! cc nrlmd Lecture du fichier wake_param.data
176
177
178  ! cc nrlmd Lecture du fichier wake_param.data
179  stark=0.33
180  CALL getin_p('stark',stark)
181  cstart = stark*sqrt(2.*wapecut)
182
183  alpk=0.25
184  CALL getin_p('alpk',alpk)
[4230]185 
[4453]186  wk_pupper=0.6
187  CALL getin_p('wk_pupper',wk_pupper)
[4230]188
189
[4085]190!jyg<
191!!  wdens_ref=8.E-12
192!!  CALL getin_p('wdens_ref',wdens_ref)
193  wdens_ref(1)=8.E-12
194  wdens_ref(2)=8.E-12
195  CALL getin_p('wdens_ref_o',wdens_ref(1))    !wake number per unit area ; ocean
196  CALL getin_p('wdens_ref_l',wdens_ref(2))    !wake number per unit area ; land
197!>jyg
198!
199!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
200!!!!!!!!!  Population dynamics parameters    !!!!!!!!!!!!!!!!!!!!!!!!!!!!
201!------------------------------------------------------------------------
202
203  iflag_wk_pop_dyn = 0
204  CALL getin_p('iflag_wk_pop_dyn',iflag_wk_pop_dyn) ! switch between wdens prescribed
205                                                    ! and wdens prognostic
206  iflag_wk_act = 0
207  CALL getin_p('iflag_wk_act',iflag_wk_act) ! 0: act(:)=0.
208                                            ! 1: act(:)=1.
209                                            ! 2: act(:)=f(Wape)
210
[4294]211  iflag_wk_profile = 0
212  CALL getin_p('iflag_wk_profile',iflag_wk_profile) ! switch between wdens prescribed
213                                                    ! and wdens prognostic
[4085]214  tau_cv = 4000.
215  CALL getin_p('tau_cv', tau_cv)
216
217!------------------------------------------------------------------------
218
219  coefgw=4.
220  CALL getin_p('coefgw',coefgw)
221
222  WRITE(*,*) 'stark=', stark
223  WRITE(*,*) 'alpk=', alpk
[4453]224  WRITE(*,*) 'wk_pupper=', wk_pupper
[4085]225!jyg<
226!!  WRITE(*,*) 'wdens_ref=', wdens_ref
227  WRITE(*,*) 'wdens_ref_o=', wdens_ref(1)
228  WRITE(*,*) 'wdens_ref_l=', wdens_ref(2)
229!>jyg
230  WRITE(*,*) 'iflag_wk_pop_dyn=',iflag_wk_pop_dyn
231  WRITE(*,*) 'iflag_wk_act',iflag_wk_act
232  WRITE(*,*) 'coefgw=', coefgw
233
234  flag_wk_check_trgl=.false.
235  CALL getin_p('flag_wk_check_trgl ', flag_wk_check_trgl)
236  WRITE(*,*) 'flag_wk_check_trgl=', flag_wk_check_trgl
237  WRITE(*,*) 'flag_wk_check_trgl OBSOLETE. Utilisr iflag_wk_check_trgl plutot'
238  iflag_wk_check_trgl=0 ; IF (flag_wk_check_trgl) iflag_wk_check_trgl=1
239  CALL getin_p('iflag_wk_check_trgl ', iflag_wk_check_trgl)
240  WRITE(*,*) 'iflag_wk_check_trgl=', iflag_wk_check_trgl
241
242 RETURN
243
244END SUBROUTINE wake_ini
245
[4744]246
247
[4588]248END MODULE lmdz_wake_ini
Note: See TracBrowser for help on using the repository browser.