source: LMDZ6/trunk/libf/phylmd/wake_ini_mod.F90 @ 4283

Last change on this file since 4283 was 4230, checked in by fhourdin, 21 months ago

New code for the wakes. Ready for new adventures.
Jean-Yves, Lamine, Frederic

File size: 7.0 KB
Line 
1MODULE wake_ini_mod
2IMPLICIT NONE
3
4
5  ! ============================================================================
6
7
8  ! But : Decrire le comportement des poches froides apparaissant dans les
9  ! grands systemes convectifs, et fournir l'energie disponible pour
10  ! le declenchement de nouvelles colonnes convectives.
11
12  ! State variables :
13  ! deltatw    : temperature difference between wake and off-wake regions
14  ! deltaqw    : specific humidity difference between wake and off-wake regions
15  ! sigmaw     : fractional area covered by wakes.
16  ! wdens      : number of wakes per unit area
17
18  ! -------------------------------------------------------------------------
19  ! Declaration de variables
20  ! -------------------------------------------------------------------------
21
22  ! Variables a fixer
23!jyg<
24!!  REAL, SAVE                                            :: stark, wdens_ref, coefgw, alpk
25  INTEGER, SAVE, PROTECTED                                         :: prt_level
26  REAL, SAVE, PROTECTED, DIMENSION(2)                              :: wdens_ref
27  REAL, SAVE, PROTECTED                                            :: stark, coefgw, alpk, pupperbyphs
28!>jyg
29  REAL, SAVE, PROTECTED                                            :: crep_upper, crep_sol 
30  !$OMP THREADPRIVATE(stark, wdens_ref, coefgw, alpk, pupperbyphs, crep_upper, crep_sol)
31
32  REAL, SAVE, PROTECTED                                            :: tau_cv
33  !$OMP THREADPRIVATE(tau_cv)
34  REAL, SAVE, PROTECTED                                            :: rzero, aa0 ! minimal wake radius and area
35  !$OMP THREADPRIVATE(rzero, aa0)
36
37  LOGICAL, SAVE, PROTECTED                                         :: flag_wk_check_trgl
38  !$OMP THREADPRIVATE(flag_wk_check_trgl)
39  INTEGER, SAVE, PROTECTED                                         :: iflag_wk_act
40  !$OMP THREADPRIVATE(iflag_wk_act)
41
42  INTEGER, SAVE, PROTECTED                                         :: iflag_wk_check_trgl
43  !$OMP THREADPRIVATE(iflag_wk_check_trgl)
44  INTEGER, SAVE, PROTECTED                                         :: iflag_wk_pop_dyn
45  !$OMP THREADPRIVATE(iflag_wk_pop_dyn)
46
47  REAL, SAVE, PROTECTED                                            :: wdensmin
48  !$OMP THREADPRIVATE(wdensmin)
49  REAL, SAVE, PROTECTED                                            :: sigmad, hwmin, wapecut, cstart
50  !$OMP THREADPRIVATE(sigmad, hwmin, wapecut, cstart)
51  REAL, SAVE, PROTECTED                                            :: sigmaw_max
52  !$OMP THREADPRIVATE(sigmaw_max) 
53  REAL, SAVE, PROTECTED                                            :: dens_rate
54  !$OMP THREADPRIVATE(dens_rate)
55  REAL, SAVE, PROTECTED                                            :: epsilon_loc
56  !$OMP THREADPRIVATE(epsilon_loc)
57  REAL, SAVE, PROTECTED                                            :: epsim1,RG,RD
58  !$OMP THREADPRIVATE(epsim1,RG,RD)
59
60
61
62CONTAINS
63
64  ! =========================================================================
65  SUBROUTINE wake_ini(rg_in,rd_in,rv_in,prt_lev)
66  ! =========================================================================
67
68  ! **************************************************************
69  ! *
70  ! WAKE                                                        *
71  ! retour a un Pupper fixe                                *
72  ! *
73  ! written by   :  GRANDPEIX Jean-Yves   09/03/2000            *
74  ! modified by :   ROEHRIG Romain        01/29/2007            *
75  ! **************************************************************
76
77  ! -------------------------------------------------------------------------
78  ! Initialisations
79  ! -------------------------------------------------------------------------
80
81  USE ioipsl_getin_p_mod, ONLY : getin_p
82  real eps
83  integer, intent(in) :: prt_lev
84  real, intent(in) :: rg_in,rd_in,rv_in
85
86  prt_level=prt_lev
87  epsilon_loc=1.E-15
88  wapecut=1. ! previously 5.
89  ! Essais d'initialisation avec sigmaw = 0.02 et hw = 10.
90  sigmad=0.02
91  hwmin=10.
92!!  DATA wdensmin/1.e-12/
93  wdensmin=1.e-14
94  ! cc nrlmd
95  sigmaw_max=0.4
96  dens_rate=0.1
97
98  eps = rd_in/rv_in
99  epsim1 = 1.0/eps - 1.0
100  RG=rg_in
101  RD=rd_in
102
103
104  ! cc
105  ! Longueur de maille (en m)
106  ! -------------------------------------------------------------------------
107
108  ! ALON = 3.e5
109  ! alon = 1.E6
110
111  ! Configuration de coefgw,stark,wdens (22/02/06 by YU Jingmei)
112
113  ! coefgw : Coefficient pour les ondes de gravite
114  ! stark : Coefficient k dans Cstar=k*sqrt(2*WAPE)
115  ! wdens : Densite surfacique de poche froide
116  ! -------------------------------------------------------------------------
117
118  ! cc nrlmd      coefgw=10
119  ! coefgw=1
120  ! wdens0 = 1.0/(alon**2)
121  ! cc nrlmd      wdens = 1.0/(alon**2)
122  ! cc nrlmd      stark = 0.50
123  ! CRtest
124  ! cc nrlmd      alpk=0.1
125  ! alpk = 1.0
126  ! alpk = 0.5
127  ! alpk = 0.05
128
129
130
131  crep_upper = 0.9
132  crep_sol = 1.0
133
134  ! Get wapecut from parameter file
135  wapecut = 1.
136
137print*,'wapecut',wapecut
138  CALL getin_p('wapecut', wapecut)
139print*,'wapecut',wapecut
140
141  ! cc nrlmd Lecture du fichier wake_param.data
142
143
144  ! cc nrlmd Lecture du fichier wake_param.data
145  stark=0.33
146  CALL getin_p('stark',stark)
147  cstart = stark*sqrt(2.*wapecut)
148
149  alpk=0.25
150  CALL getin_p('alpk',alpk)
151 
152  pupperbyphs=0.6
153  CALL getin_p('pupperbyphs',pupperbyphs)
154
155
156!jyg<
157!!  wdens_ref=8.E-12
158!!  CALL getin_p('wdens_ref',wdens_ref)
159  wdens_ref(1)=8.E-12
160  wdens_ref(2)=8.E-12
161  CALL getin_p('wdens_ref_o',wdens_ref(1))    !wake number per unit area ; ocean
162  CALL getin_p('wdens_ref_l',wdens_ref(2))    !wake number per unit area ; land
163!>jyg
164!
165!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
166!!!!!!!!!  Population dynamics parameters    !!!!!!!!!!!!!!!!!!!!!!!!!!!!
167!------------------------------------------------------------------------
168
169  iflag_wk_pop_dyn = 0
170  CALL getin_p('iflag_wk_pop_dyn',iflag_wk_pop_dyn) ! switch between wdens prescribed
171                                                    ! and wdens prognostic
172  iflag_wk_act = 0
173  CALL getin_p('iflag_wk_act',iflag_wk_act) ! 0: act(:)=0.
174                                            ! 1: act(:)=1.
175                                            ! 2: act(:)=f(Wape)
176
177  rzero = 5000.
178  CALL getin_p('rzero_wk', rzero)
179  aa0 = 3.14*rzero*rzero
180!
181  tau_cv = 4000.
182  CALL getin_p('tau_cv', tau_cv)
183
184!------------------------------------------------------------------------
185
186  coefgw=4.
187  CALL getin_p('coefgw',coefgw)
188
189  WRITE(*,*) 'stark=', stark
190  WRITE(*,*) 'alpk=', alpk
191  WRITE(*,*) 'pupperbyphs=', pupperbyphs
192!jyg<
193!!  WRITE(*,*) 'wdens_ref=', wdens_ref
194  WRITE(*,*) 'wdens_ref_o=', wdens_ref(1)
195  WRITE(*,*) 'wdens_ref_l=', wdens_ref(2)
196!>jyg
197  WRITE(*,*) 'iflag_wk_pop_dyn=',iflag_wk_pop_dyn
198  WRITE(*,*) 'iflag_wk_act',iflag_wk_act
199  WRITE(*,*) 'coefgw=', coefgw
200
201  flag_wk_check_trgl=.false.
202  CALL getin_p('flag_wk_check_trgl ', flag_wk_check_trgl)
203  WRITE(*,*) 'flag_wk_check_trgl=', flag_wk_check_trgl
204  WRITE(*,*) 'flag_wk_check_trgl OBSOLETE. Utilisr iflag_wk_check_trgl plutot'
205  iflag_wk_check_trgl=0 ; IF (flag_wk_check_trgl) iflag_wk_check_trgl=1
206  CALL getin_p('iflag_wk_check_trgl ', iflag_wk_check_trgl)
207  WRITE(*,*) 'iflag_wk_check_trgl=', iflag_wk_check_trgl
208
209 RETURN
210
211END SUBROUTINE wake_ini
212
213END MODULE wake_ini_mod
Note: See TracBrowser for help on using the repository browser.