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

Contents of /trunk/dyn3d/etat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 78 - (show annotations)
Wed Feb 5 17:51:07 2014 UTC (10 years, 3 months ago) by guez
Original Path: trunk/dyn3d/etat0.f90
File size: 11964 byte(s)
Moved procedure inigeom into module comgeom.

In disvert, renamed s_sampling to vert_sampling, following
LMDZ. Removed choice strato1. In case read, read ap and bp instead of
s (following LMDZ).

Added argument phis to start_init_orog and start_init_dyn, and removed
variable phis of module start_init_orog_m. In etat0 and
start_init_orog, renamed relief to zmea_2d. In start_init_dyn, renamed
psol to ps.

In start_init_orog, renamed relief_hi to relief. No need to set
phis(iim + 1, :) = phis(1, :), already done in grid_noro.

Documentation for massbar out of SVN, in massbar.txt. Documentation
was duplicated in massdair, but not relevant in massdair.

In conflx, no need to initialize pen_[ud] and pde_[ud]. In flxasc,
used intermediary variable fact (following LMDZ).

In grid_noro, added local variable zmea0 for zmea not smoothed and
computed zphi from zmea instead of zmea0 (following LMDZ). This
changes the results of ce0l.

Removed arguments pen_u and pde_d of phytrac and nflxtr, which were
not used.

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

  ViewVC Help
Powered by ViewVC 1.1.21