1 | subroutine PHY________INI |
---|
2 | |
---|
3 | !------------------------------------------------------------------------------+ |
---|
4 | ! Sun 30-Jun-2013 MAR | |
---|
5 | ! MAR PHY________INI | |
---|
6 | ! subroutine PHY________INI intializes MAR PHYsical parameterizations | |
---|
7 | ! | |
---|
8 | ! version 3.p.4.1 created by H. Gallee, Tue 12-Mar-2013 | |
---|
9 | ! Last Modification by H. Gallee, Sun 30-Jun-2013 | |
---|
10 | ! | |
---|
11 | !------------------------------------------------------------------------------+ |
---|
12 | |
---|
13 | use Mod_Real |
---|
14 | use Mod_PHY____dat |
---|
15 | use Mod_PHY____grd |
---|
16 | use Mod_PHY_RT_grd |
---|
17 | use Mod_PHY____kkl |
---|
18 | |
---|
19 | |
---|
20 | IMPLICIT NONE |
---|
21 | |
---|
22 | |
---|
23 | logical :: search_argexp = .FALSE. ! Lapack used to compute MAX/MIN exponential arguments |
---|
24 | integer :: i, j, ikl ! |
---|
25 | |
---|
26 | |
---|
27 | |
---|
28 | |
---|
29 | !=============================================================================================! |
---|
30 | ! ! |
---|
31 | ! include 'MARphy.inc' ! MARthusalem constants |
---|
32 | ! ! |
---|
33 | !=============================================================================================! |
---|
34 | |
---|
35 | |
---|
36 | !=============================================================================================! |
---|
37 | ! ! |
---|
38 | ! Modification of Mod_PHY____dat (needed if constants slighly differ in the HOST model) ! |
---|
39 | ! ================================ (Here the chosen HOST model is MAR) ! |
---|
40 | ! ! |
---|
41 | ! Initialization of Mod_PHY____dat from MARphy.inc (MARphy.inc contains MARthusalem constants)! |
---|
42 | ! ------------------------------------------------ ! |
---|
43 | ! ! |
---|
44 | ! zer0 = 0.0 ! [-] ! |
---|
45 | ! half = 0.5 ! [-] ! |
---|
46 | ! un_1 = 1.0 ! [-] ! |
---|
47 | piNmbr = acos(-1.0) ! [-] ! |
---|
48 | ! eps6 = epsi ! [-] ! |
---|
49 | ! epsn = eps9 ! [-] ! |
---|
50 | ! A_MolV = 1.35e-5 ! Air Viscosity 1.35e-5 [m2/s] ! |
---|
51 | ! rhoIce = ro_Ice ! Ice Specific Mass 920.e0 [kg/m3] ! |
---|
52 | ! BSnoRo = blsno ! Blown Snow Specific Mass 2.55e+2 [kg/m3] ! |
---|
53 | ! LhfH2O = Lf_H2O ! |
---|
54 | ! LhvH2O = Lv_H2O ! Latent Heat Vaporisation, Water 2.5008e+6 [J/kg] ! |
---|
55 | ! LhsH2O = Ls_H2O ! |
---|
56 | ! CpdAir = Cp ! Air Heat Capacity (p=C) 1004.708845 [J/kg/K] ! |
---|
57 | ! R_DAir = RDryAi ! Dry Air Perfect Gas Law C 287.05967 [J/kg/K] ! |
---|
58 | ! RCp = cap ! RDryAi / Cp [-] ! |
---|
59 | ! p0_kap = pcap ! |
---|
60 | ! hC_Wat = C__Wat ! H2O Heat Capacity 4186.00e0 [J/kg/K] ! |
---|
61 | ! rhoWat = ro_Wat |
---|
62 | ! Tf_Sno = TfSnow |
---|
63 | ! Tf_Sea = tfrwat |
---|
64 | ! StefBo = stefan ! Stefan-Bolstzman Constant 5.67e-8 [W/m2/K4] ! |
---|
65 | ! Grav_F = gravit ! Gravity Acceleration 9.81e0 [m/s2] ! |
---|
66 | ! vonKrm = vonkar ! von Karman Constant 0.40e0 [-] ! |
---|
67 | ! A_Stab = A_Turb ! 5.8 [-] ! |
---|
68 | ! AhStab = AhTurb |
---|
69 | ! AsStab = AsTurb |
---|
70 | ! r_Stab = r_Turb |
---|
71 | ! ! |
---|
72 | !=============================================================================================! |
---|
73 | |
---|
74 | |
---|
75 | |
---|
76 | ! Initialization of Mod_PHY____dat (auxiliary Constants) ! |
---|
77 | ! ------------------------------------------------------ ! |
---|
78 | |
---|
79 | Grav_I = 1. / Grav_F ! [s2/m] ! |
---|
80 | GravF2 = Grav_F * Grav_F ! [m2/s4] ! |
---|
81 | RCp = R_DAir / CpdAir ! Case Sensitive [-] ! |
---|
82 | Lv_CPd = LhvH2O / CpdAir |
---|
83 | Ls_CPd = LhsH2O / CpdAir |
---|
84 | Lc_CPd = LhfH2O / CpdAir |
---|
85 | vonKrm = 0.35 ! von Karman Constant, Case Sensitive ! |
---|
86 | |
---|
87 | IF (search_argexp) THEN |
---|
88 | |
---|
89 | ! *************** |
---|
90 | call PHY_CPU_NumPrec |
---|
91 | ! *************** |
---|
92 | |
---|
93 | ELSE |
---|
94 | |
---|
95 | ea_MIN =-80. |
---|
96 | ea_MAX = 80. |
---|
97 | |
---|
98 | END IF |
---|
99 | |
---|
100 | |
---|
101 | |
---|
102 | |
---|
103 | ! Initialization of Mod_PHY____grd |
---|
104 | ! ================================ |
---|
105 | |
---|
106 | |
---|
107 | ! Correspondance entre la grille 2D horizontale dynamique et |
---|
108 | ! -------------------- la grille 2D horizontale physique utile mxp,myp,mzp |
---|
109 | ! --------------------------------------------------- |
---|
110 | mxp = mxpp-ixp1+1 ! |
---|
111 | myp = mypp-jyp1+1 ! |
---|
112 | !kcolp = mxp * myp ! Déja calculé en amont dans physiq.F90 Martin |
---|
113 | mzp = mzpp-1 |
---|
114 | PRINT*, 'mxpp=',mxpp |
---|
115 | PRINT*, 'mxp=',mxp |
---|
116 | PRINT*, 'ixp1=',ixp1 |
---|
117 | PRINT*, 'mypp=',mypp |
---|
118 | PRINT*, 'jyp1=',jyp1 |
---|
119 | PRINT*, 'myp=',myp |
---|
120 | |
---|
121 | |
---|
122 | ! Horizontal Cartesian Grid |
---|
123 | ! ------------------------- |
---|
124 | |
---|
125 | write(6,*) ' ' |
---|
126 | write(6,*) 'i_x0 , j_y0 = ' & |
---|
127 | & ,i_x0 , j_y0 |
---|
128 | |
---|
129 | |
---|
130 | ! dxHOST is Model Grid Size |
---|
131 | dx2inv = 0.5/dxHOST ! 1 / (2 dxHOST) |
---|
132 | dy2inv = 0.5/dxHOST ! 1 / (2 dxHOST) |
---|
133 | |
---|
134 | |
---|
135 | |
---|
136 | |
---|
137 | ! ALLOCATION |
---|
138 | ! ========== |
---|
139 | |
---|
140 | ! **************** |
---|
141 | CALL PHY________ALLOC |
---|
142 | ! **************** |
---|
143 | |
---|
144 | |
---|
145 | |
---|
146 | |
---|
147 | ! Initialization of Mod_PHY____grd |
---|
148 | ! ================================ |
---|
149 | |
---|
150 | ! Initialization of the Correspondance between 2-D cartesian and vector Grid |
---|
151 | ! -------------------------------------------------------------------------- |
---|
152 | |
---|
153 | ! Adapted for MAR/LMDZ coupling: |
---|
154 | |
---|
155 | ! ii__AP(1)=ixp1 |
---|
156 | ! jj__AP(1)=jyp1 |
---|
157 | ! PRINT*,'jyp1=',jyp1 |
---|
158 | ! PRINT*,'jj__AP(1)=',jj__AP(1) |
---|
159 | ! ii__AP(kcolp)=ixp1 |
---|
160 | ! jj__AP(kcolp)=mypp |
---|
161 | ! |
---|
162 | ! DO i=ixp1,mxpp |
---|
163 | ! DO j=jyp1+1,mypp-1 |
---|
164 | ! |
---|
165 | ! ikl = (j-(jyp1+1)) *mxpp +1 + (i-ixp1+1) ! Tout est décalé de 1 à cause du point isolé au pole dans la grille physique LMD |
---|
166 | ! ! ikl = (j-jyp1) *mxpp + i-ixp1+1 |
---|
167 | ! ! ikl = (j-jyp1) *(mxp-1) + i-ixp1+1 |
---|
168 | ! ii__AP(ikl) = i |
---|
169 | ! jj__AP(ikl) = j |
---|
170 | ! ikl_AP(i,j) = ikl |
---|
171 | ! PRINT*,'ii__AP(',ikl,')=',ii__AP(ikl) |
---|
172 | ! PRINT*,'jj__AP(',ikl,')=',jj__AP(ikl) |
---|
173 | ! ENDDO |
---|
174 | ! ENDDO |
---|
175 | |
---|
176 | ! Modification Gilles Delaygue 2014/07/14 ! |
---|
177 | ikl=1 |
---|
178 | ii__AP(ikl)=ixp1 |
---|
179 | jj__AP(ikl)=jyp1 |
---|
180 | ikl_AP(:,jyp1) = ikl |
---|
181 | |
---|
182 | DO j=jyp1+1,mypp-1 |
---|
183 | DO i=ixp1,mxpp |
---|
184 | ikl=ikl+1 |
---|
185 | ii__AP(ikl) = i |
---|
186 | jj__AP(ikl) = j |
---|
187 | ikl_AP(i,j) = ikl |
---|
188 | ENDDO |
---|
189 | ENDDO |
---|
190 | |
---|
191 | ikl=ikl+1 |
---|
192 | ii__AP(ikl)=ixp1 |
---|
193 | jj__AP(ikl)=mypp |
---|
194 | ikl_AP(:,mypp) = ikl |
---|
195 | |
---|
196 | |
---|
197 | |
---|
198 | |
---|
199 | |
---|
200 | PRINT*,'Control dans PHY_INI:' |
---|
201 | PRINT*,'ii__AP(1)=',ii__AP(1) |
---|
202 | PRINT*,'ii__AP(kcolp)=',ii__AP(kcolp) |
---|
203 | PRINT*,'jj__AP(1)=',jj__AP(1) |
---|
204 | PRINT*,'jj__AP(kcolp)=',jj__AP(kcolp) |
---|
205 | |
---|
206 | ! Martin control tout sauf les poles: |
---|
207 | WRITE(6,600)(ii__AP(ikl),ikl=2,kcolp-1) |
---|
208 | 600 FORMAT (48i2) |
---|
209 | WRITE(6,601)(jj__AP(ikl),ikl=2,kcolp-1) |
---|
210 | 601 FORMAT (48i2) |
---|
211 | |
---|
212 | ! DO i=ixp1,mxpp |
---|
213 | ! DO j=jyp1,mypp |
---|
214 | ! |
---|
215 | ! ikl = (j-jyp1) *mxp + i-ixp1+1 |
---|
216 | ! ii__AP(ikl) = i |
---|
217 | ! jj__AP(ikl) = j |
---|
218 | ! ikl_AP(i,j) = ikl |
---|
219 | ! |
---|
220 | ! ENDDO |
---|
221 | ! ENDDO |
---|
222 | |
---|
223 | ikl0 = ikl_AP(i_x0,j_y0) |
---|
224 | |
---|
225 | |
---|
226 | |
---|
227 | |
---|
228 | ! Allocation of radiative transfert Variables |
---|
229 | ! =========================================== |
---|
230 | |
---|
231 | |
---|
232 | ! Initialization of Mod_PHY_RT_grd |
---|
233 | ! -------------------------------- |
---|
234 | |
---|
235 | naero = 6 |
---|
236 | |
---|
237 | |
---|
238 | ! **************** |
---|
239 | CALL PHY_Atm_RT_ALLOC |
---|
240 | ! **************** |
---|
241 | |
---|
242 | |
---|
243 | |
---|
244 | |
---|
245 | ! Allocation of microphysical Variables |
---|
246 | ! =========================================== |
---|
247 | |
---|
248 | ! **************** |
---|
249 | CALL PHY_Atm_CM_ALLOC |
---|
250 | ! **************** |
---|
251 | |
---|
252 | |
---|
253 | |
---|
254 | |
---|
255 | ! Allocation of Turbulence Variables |
---|
256 | ! =========================================== |
---|
257 | |
---|
258 | ! **************** |
---|
259 | CALL PHY_Atm_AT_ALLOC |
---|
260 | ! **************** |
---|
261 | |
---|
262 | |
---|
263 | |
---|
264 | |
---|
265 | ! Allocation of Surface Variables |
---|
266 | ! =============================== |
---|
267 | |
---|
268 | ! **************** |
---|
269 | CALL PHY_SISVAT_ALLOC |
---|
270 | ! **************** |
---|
271 | |
---|
272 | |
---|
273 | |
---|
274 | |
---|
275 | ! OUTPUT |
---|
276 | ! ====== |
---|
277 | |
---|
278 | OPEN(unit=4,status='unknown',file='PHY___________.OUT') |
---|
279 | REWIND 4 |
---|
280 | |
---|
281 | |
---|
282 | |
---|
283 | end subroutine PHY________INI |
---|