/[lmdze]/trunk/dyn3d/etat0.f
ViewVC logotype

Contents of /trunk/dyn3d/etat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 107 - (show annotations)
Thu Sep 11 15:09:15 2014 UTC (9 years, 8 months ago) by guez
File size: 11751 byte(s)
Imported procedure grilles_gcm_sub from LMDZ. Had then to transform
local variable phis of etat to argument.

Replaced calls to lnblnk by calls to trim.

Removed arguments nlat, klevel and griscal of filtreg. Replaced
integer arguments ifiltre and iaire by logical arguments direct and
intensive.

Changed default values of guide_t and guide_q to false.

1 module etat0_mod
2
3 use indicesol, only: nbsrf
4 use dimphy, only: klon
5
6 IMPLICIT NONE
7
8 REAL pctsrf(klon, nbsrf)
9 ! ("pctsrf(i, :)" is the composition of the surface at horizontal
10 ! position "i")
11
12 private nbsrf, klon
13
14 contains
15
16 SUBROUTINE etat0(phis)
17
18 ! From "etat0_netcdf.F", version 1.3, 2005/05/25 13:10:09
19
20 use caldyn0_m, only: caldyn0
21 use comconst, only: cpp, kappa, iniconst
22 use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &
23 cu_2d, cv_2d, inigeom
24 use conf_gcm_m, only: dayref, anneeref
25 use dimens_m, only: iim, jjm, llm, nqmx
26 use dimphy, only: zmasq
27 use dimsoil, only: nsoilmx
28 use disvert_m, only: ap, bp, preff, pa, disvert
29 use dynredem0_m, only: dynredem0
30 use dynredem1_m, only: dynredem1
31 use exner_hyb_m, only: exner_hyb
32 use geopot_m, only: geopot
33 use grid_atob, only: grille_m
34 use grid_change, only: init_dyn_phy, dyn_phy
35 use histclo_m, only: histclo
36 use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
37 use iniadvtrac_m, only: iniadvtrac
38 use inifilr_m, only: inifilr
39 use massdair_m, only: massdair
40 use netcdf, only: nf90_nowrite
41 use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &
42 nf95_inq_varid, nf95_open
43 use nr_util, only: pi, assert
44 use paramet_m, only: ip1jm, ip1jmp1
45 use phyredem_m, only: phyredem
46 use q_sat_m, only: q_sat
47 use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
48 use regr_pr_o3_m, only: regr_pr_o3
49 use serre, only: alphax
50 use startdyn, only: start_init_dyn
51 USE start_init_orog_m, only: start_init_orog, mask
52 use start_init_phys_m, only: start_init_phys
53 use start_inter_3d_m, only: start_inter_3d
54 use temps, only: itau_phy, annee_ref, day_ref
55 use test_disvert_m, only: test_disvert
56
57 REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
58 ! surface geopotential, in m2 s-2
59
60 ! Local:
61
62 REAL latfi(klon), lonfi(klon)
63 ! (latitude and longitude of a point of the scalar grid identified
64 ! by a simple index, in degrees)
65
66 REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
67 REAL vcov(iim + 1, jjm, llm)
68
69 REAL q(iim + 1, jjm + 1, llm, nqmx)
70 ! (mass fractions of trace species
71 ! "q(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)"
72 ! and pressure level "pls(i, j, l)".)
73
74 real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor
75 REAL sn(klon)
76 REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
77 REAL albe(klon, nbsrf), evap(klon, nbsrf)
78 REAL alblw(klon, nbsrf)
79 REAL tsoil(klon, nsoilmx, nbsrf)
80 REAL radsol(klon), rain_fall(klon), snow_fall(klon)
81 REAL solsw(klon), sollw(klon), fder(klon)
82 !IM "slab" ocean
83 real seaice(klon) ! kg m-2
84 REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
85 REAL rugmer(klon)
86 real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d
87 real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
88 real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
89 REAL zmea(klon), zstd(klon)
90 REAL zsig(klon), zgam(klon)
91 REAL zthe(klon)
92 REAL zpic(klon), zval(klon)
93 REAL t_ancien(klon, llm), q_ancien(klon, llm)
94 REAL run_off_lic_0(klon)
95 real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
96
97 ! D\'eclarations pour lecture glace de mer :
98 INTEGER iml_lic, jml_lic
99 INTEGER ncid, varid
100 REAL, pointer:: dlon_lic(:), dlat_lic(:)
101 REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice
102 REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
103
104 INTEGER l, ji
105
106 REAL pk(iim + 1, jjm + 1, llm) ! fonction d'Exner aux milieux des couches
107 real pks(iim + 1, jjm + 1)
108
109 REAL masse(iim + 1, jjm + 1, llm)
110 REAL phi(iim + 1, jjm + 1, llm)
111 REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
112 REAL w(iim + 1, jjm + 1, llm)
113
114 real sig1(klon, llm) ! section adiabatic updraft
115 real w01(klon, llm) ! vertical velocity within adiabatic updraft
116
117 real pls(iim + 1, jjm + 1, llm)
118 ! (pressure at mid-layer of LMDZ grid, in Pa)
119 ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
120 ! for layer "l")
121
122 REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
123 ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
124 ! for interface "l")
125
126 !---------------------------------
127
128 print *, "Call sequence information: etat0"
129
130 CALL iniconst
131
132 ! Construct a grid:
133
134 pa = 5e4
135 CALL disvert
136 call test_disvert
137 CALL inigeom
138 CALL inifilr
139
140 latfi(1) = 90.
141 latfi(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi
142 ! (with conversion to degrees)
143 latfi(klon) = - 90.
144
145 lonfi(1) = 0.
146 lonfi(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi
147 ! (with conversion to degrees)
148 lonfi(klon) = 0.
149
150 call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &
151 zpic_2d, zval_2d) ! also compute "mask"
152 call init_dyn_phy ! define the mask "dyn_phy" for distinct grid points
153 zmasq = pack(mask, dyn_phy)
154 PRINT *, 'Masque construit'
155
156 call start_init_phys(tsol_2d, qsol_2d)
157 CALL start_init_dyn(tsol_2d, phis, ps)
158
159 ! Compute pressure on intermediate levels:
160 forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
161 CALL exner_hyb(ps, p3d, pks, pk)
162 call assert(MINVAL(pk) /= MAXVAL(pk), '"pk" should not be constant')
163
164 pls = preff * (pk / cpp)**(1. / kappa)
165 PRINT *, "minval(pls) = ", minval(pls)
166 print *, "maxval(pls) = ", maxval(pls)
167
168 call start_inter_3d('U', rlonv, rlatv, pls, ucov)
169 forall (l = 1: llm) ucov(:iim, :, l) = ucov(:iim, :, l) * cu_2d(:iim, :)
170 ucov(iim+1, :, :) = ucov(1, :, :)
171
172 call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vcov)
173 forall (l = 1: llm) vcov(:iim, :, l) = vcov(:iim, :, l) * cv_2d(:iim, :)
174 vcov(iim + 1, :, :) = vcov(1, :, :)
175
176 call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
177 PRINT *, 'minval(t3d) = ', minval(t3d)
178 print *, "maxval(t3d) = ", maxval(t3d)
179
180 teta(:iim, :, :) = t3d(:iim, :, :) * cpp / pk(:iim, :, :)
181 teta(iim + 1, :, :) = teta(1, :, :)
182 DO l = 1, llm
183 teta(:, 1, l) = SUM(aire_2d(:, 1) * teta(:, 1, l)) / apoln
184 teta(:, jjm + 1, l) = SUM(aire_2d(:, jjm + 1) * teta(:, jjm + 1, l)) &
185 / apols
186 ENDDO
187
188 ! Calcul de l'humidit\'e \`a saturation :
189 qsat = q_sat(t3d, pls)
190 PRINT *, "minval(qsat) = ", minval(qsat)
191 print *, "maxval(qsat) = ", maxval(qsat)
192 IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
193
194 ! Water vapor:
195 call start_inter_3d('R', rlonu, rlatv, pls, q(:, :, :, 1))
196 q(:, :, :, 1) = 0.01 * q(:, :, :, 1) * qsat
197 WHERE (q(:, :, :, 1) < 0.) q(:, :, :, 1) = 1E-10
198 DO l = 1, llm
199 q(:, 1, l, 1) = SUM(aire_2d(:, 1) * q(:, 1, l, 1)) / apoln
200 q(:, jjm + 1, l, 1) &
201 = SUM(aire_2d(:, jjm + 1) * q(:, jjm + 1, l, 1)) / apols
202 ENDDO
203
204 q(:, :, :, 2:4) = 0. ! liquid water, radon and lead
205
206 if (nqmx >= 5) then
207 ! Ozone:
208 call regr_lat_time_coefoz
209 call regr_pr_o3(p3d, q(:, :, :, 5))
210 ! Convert from mole fraction to mass fraction:
211 q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
212 end if
213
214 sn = 0. ! snow
215 radsol = 0.
216 seaice = 0.
217 rugmer = 0.001
218 zmea = pack(zmea_2d, dyn_phy)
219 zstd = pack(zstd_2d, dyn_phy)
220 zsig = pack(zsig_2d, dyn_phy)
221 zgam = pack(zgam_2d, dyn_phy)
222 zthe = pack(zthe_2d, dyn_phy)
223 zpic = pack(zpic_2d, dyn_phy)
224 zval = pack(zval_2d, dyn_phy)
225
226 ! On initialise les sous-surfaces.
227 ! Lecture du fichier glace de terre pour fixer la fraction de terre
228 ! et de glace de terre :
229
230 call nf95_open("landiceref.nc", nf90_nowrite, ncid)
231
232 call nf95_inq_varid(ncid, 'longitude', varid)
233 call nf95_gw_var(ncid, varid, dlon_lic)
234 iml_lic = size(dlon_lic)
235
236 call nf95_inq_varid(ncid, 'latitude', varid)
237 call nf95_gw_var(ncid, varid, dlat_lic)
238 jml_lic = size(dlat_lic)
239
240 call nf95_inq_varid(ncid, 'landice', varid)
241 ALLOCATE(fraclic(iml_lic, jml_lic))
242 call nf95_get_var(ncid, varid, fraclic)
243
244 call nf95_close(ncid)
245
246 ! Interpolation sur la grille T du mod\`ele :
247 PRINT *, 'Dimensions de "landiceref.nc"'
248 print *, "iml_lic = ", iml_lic
249 print *, "jml_lic = ", jml_lic
250
251 ! Si les coordonn\'ees sont en degr\'es, on les transforme :
252 IF (MAXVAL(dlon_lic) > pi) THEN
253 dlon_lic = dlon_lic * pi / 180.
254 ENDIF
255 IF (maxval(dlat_lic) > pi) THEN
256 dlat_lic = dlat_lic * pi/ 180.
257 ENDIF
258
259 flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &
260 rlatu)
261 flic_tmp(iim + 1, :) = flic_tmp(1, :)
262
263 deallocate(dlon_lic, dlat_lic) ! pointers
264
265 ! Passage sur la grille physique
266 pctsrf = 0.
267 pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
268 ! Ad\'equation avec le maque terre/mer
269 WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
270 WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
271 pctsrf(:, is_ter) = zmasq
272 where (zmasq > EPSFRA)
273 where (pctsrf(:, is_lic) >= zmasq)
274 pctsrf(:, is_lic) = zmasq
275 pctsrf(:, is_ter) = 0.
276 elsewhere
277 pctsrf(:, is_ter) = zmasq - pctsrf(:, is_lic)
278 where (pctsrf(:, is_ter) < EPSFRA)
279 pctsrf(:, is_ter) = 0.
280 pctsrf(:, is_lic) = zmasq
281 end where
282 end where
283 end where
284
285 ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace
286 ! de mer \`a 0) :
287 pctsrf(:, is_oce) = 1. - zmasq
288 WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
289
290 ! V\'erification que somme des sous-surfaces vaut 1 :
291 ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
292 IF (ji /= 0) then
293 PRINT *, 'Bad surface percentages for ', ji, 'points'
294 end IF
295
296 ! Calcul interm\'ediaire :
297 CALL massdair(p3d, masse)
298
299 print *, 'ALPHAX = ', alphax
300
301 forall (l = 1:llm)
302 masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln
303 masse(:, jjm + 1, l) = &
304 SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
305 END forall
306
307 ! Initialisation pour traceurs:
308 call iniadvtrac
309 itau_phy = 0
310 day_ref = dayref
311 annee_ref = anneeref
312
313 CALL geopot(teta, pk , pks, phis, phi)
314 CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &
315 pbarv)
316 CALL dynredem0("start.nc", dayref, phis)
317 CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
318
319 ! Initialisations :
320 snsrf(:, is_ter) = sn
321 snsrf(:, is_lic) = sn
322 snsrf(:, is_oce) = sn
323 snsrf(:, is_sic) = sn
324 albe(:, is_ter) = 0.08
325 albe(:, is_lic) = 0.6
326 albe(:, is_oce) = 0.5
327 albe(:, is_sic) = 0.6
328 alblw = albe
329 evap = 0.
330 qsolsrf = 150.
331 tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
332 rain_fall = 0.
333 snow_fall = 0.
334 solsw = 165.
335 sollw = -53.
336 t_ancien = 273.15
337 q_ancien = 0.
338 agesno = 0.
339 seaice = 0.
340
341 frugs(:, is_oce) = rugmer
342 frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
343 frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
344 frugs(:, is_sic) = 0.001
345 fder = 0.
346 clwcon = 0.
347 rnebcon = 0.
348 ratqs = 0.
349 run_off_lic_0 = 0.
350 sig1 = 0.
351 w01 = 0.
352
353 call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &
354 tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
355 albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
356 frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
357 q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
358 CALL histclo
359
360 END SUBROUTINE etat0
361
362 end module etat0_mod

  ViewVC Help
Powered by ViewVC 1.1.21