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

Contents of /trunk/dyn3d/limit.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 97 - (show annotations)
Fri Apr 25 14:58:31 2014 UTC (10 years, 1 month ago) by guez
File size: 13785 byte(s)
Module pressure_var is now only used in gcm. Created local variables
pls and p3d in etat0, added argument p3d to regr_pr_o3.

In leapfrog, moved computation of p3d and exner function immediately
after integrd, for clarity (does not change the execution).

Removed unused arguments: ntra, tra1 and tra of cv3_compress; ntra,
tra and traent of cv3_mixing; ntra, ftra, ftra1 of cv3_uncompress;
ntra, tra, trap of cv3_unsat; ntra, tra, trap, traent, ftra of
cv3_yield; tra, tvp, pbase, bbase, dtvpdt1, dtvpdq1, dplcldt,
dplcldr, ntra of concvl; ndp1, ntra, tra1 of cv_driver

Removed argument d_tra and computation of d_tra in concvl. Removed
argument ftra1 and computation of ftra1 in cv_driver. ftra1 was just
set to 0 in cv_driver, associated to d_tra in concvl, and set again to
zero in concvl.

1 module limit_mod
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE limit
8
9 ! Authors: L. Fairhead, Z. X. Li, P. Le Van
10
11 ! This subroutine creates files containing boundary conditions.
12 ! It uses files with climatological data.
13 ! Both grids must be regular.
14
15 use comgeom, only: rlonu, rlatv
16 use conf_dat2d_m, only: conf_dat2d
17 use dimens_m, only: iim, jjm
18 use dimphy, only: klon, zmasq
19 use etat0_mod, only: pctsrf
20 use grid_change, only: dyn_phy
21 use indicesol, only: epsfra, nbsrf, is_ter, is_oce, is_lic, is_sic
22 use inter_barxy_m, only: inter_barxy
23 use netcdf95, only: handle_err, NF95_CLOSE, NF95_CREATE, NF95_DEF_DIM, &
24 nf95_enddef, nf95_get_var, nf95_gw_var, nf95_inq_dimid, &
25 nf95_inq_varid, nf95_inquire_dimension, NF95_OPEN
26 use netcdf, only: NF90_CLOBBER, nf90_def_var, NF90_FLOAT, NF90_GLOBAL, &
27 NF90_NOWRITE, NF90_PUT_ATT, NF90_PUT_VAR, NF90_UNLIMITED
28 use numer_rec_95, only: spline, splint
29 use start_init_orog_m, only: mask
30 use unit_nml_m, only: unit_nml
31
32 ! Variables local to the procedure:
33
34 LOGICAL:: extrap = .FALSE.
35 ! (extrapolation de données, comme pour les SST lorsque le fichier
36 ! ne contient pas uniquement des points océaniques)
37
38 REAL phy_alb(klon, 360)
39 REAL phy_sst(klon, 360)
40 REAL phy_bil(klon, 360)
41 REAL phy_rug(klon, 360)
42 REAL phy_ice(klon)
43
44 real pctsrf_t(klon, nbsrf, 360) ! composition of the surface
45
46 ! Pour le champ de départ:
47 INTEGER imdep, jmdep, lmdep
48
49 REAL, ALLOCATABLE:: dlon(:), dlat(:)
50 REAL, pointer:: dlon_ini(:), dlat_ini(:), timeyear(:)
51 REAL, ALLOCATABLE:: champ(:, :)
52 REAL, ALLOCATABLE:: work(:, :)
53
54 ! Pour le champ interpolé 3D :
55 REAL, allocatable:: champtime(:, :, :)
56 REAL champan(iim + 1, jjm + 1, 360)
57
58 ! Pour l'inteprolation verticale :
59 REAL, allocatable:: yder(:)
60
61 INTEGER ierr
62
63 INTEGER nid, ndim, ntim
64 INTEGER dims(2), debut(2)
65 INTEGER id_tim
66 INTEGER id_SST, id_BILS, id_RUG, id_ALB
67 INTEGER id_FOCE, id_FSIC, id_FTER, id_FLIC
68
69 INTEGER i, j, k, l
70 INTEGER ncid, varid, dimid
71
72 REAL, parameter:: tmidmonth(12) = (/(15. + 30. * i, i = 0, 11)/)
73
74 namelist /limit_nml/extrap
75
76 !--------------------
77
78 print *, "Call sequence information: limit"
79
80 print *, "Enter namelist 'limit_nml'."
81 read (unit=*, nml=limit_nml)
82 write(unit_nml, nml=limit_nml)
83
84 PRINT *, 'Processing rugosity...'
85
86 call NF95_OPEN('Rugos.nc', NF90_NOWRITE, ncid)
87
88 ! Read coordinate variables:
89
90 call nf95_inq_varid(ncid, "longitude", varid)
91 call nf95_gw_var(ncid, varid, dlon_ini)
92 imdep = size(dlon_ini)
93
94 call nf95_inq_varid(ncid, "latitude", varid)
95 call nf95_gw_var(ncid, varid, dlat_ini)
96 jmdep = size(dlat_ini)
97
98 call nf95_inq_varid(ncid, "temps", varid)
99 call nf95_gw_var(ncid, varid, timeyear)
100 lmdep = size(timeyear)
101
102 ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
103 allocate(dlon(imdep), dlat(jmdep))
104 call NF95_INQ_VARID(ncid, 'RUGOS', varid)
105
106 ! Read the primary variable day by day and regrid horizontally,
107 ! result in "champtime":
108 DO l = 1, lmdep
109 call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))
110 CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
111 CALL inter_barxy(dlon, dlat(:jmdep -1), LOG(champ), rlonu(:iim), &
112 rlatv, champtime(:, :, l))
113 champtime(:, :, l) = EXP(champtime(:, :, l))
114 where (nint(mask(:iim, :)) /= 1) champtime(:, :, l) = 0.001
115 end do
116
117 call NF95_CLOSE(ncid)
118
119 DEALLOCATE(dlon, dlat, champ, dlon_ini, dlat_ini)
120 allocate(yder(lmdep))
121
122 ! Interpolate monthly values to daily values, at each horizontal position:
123 DO j = 1, jjm + 1
124 DO i = 1, iim
125 yder = SPLINE(timeyear, champtime(i, j, :))
126 DO k = 1, 360
127 champan(i, j, k) = SPLINT(timeyear, champtime(i, j, :), yder, &
128 real(k-1))
129 ENDDO
130 ENDDO
131 ENDDO
132
133 deallocate(timeyear, champtime, yder)
134 champan(iim + 1, :, :) = champan(1, :, :)
135 forall (k = 1:360) phy_rug(:, k) = pack(champan(:, :, k), dyn_phy)
136
137 ! Process sea ice:
138
139 PRINT *, 'Processing sea ice...'
140 call NF95_OPEN('amipbc_sic_1x1.nc', NF90_NOWRITE, ncid)
141
142 call nf95_inq_varid(ncid, "longitude", varid)
143 call nf95_gw_var(ncid, varid, dlon_ini)
144 imdep = size(dlon_ini)
145
146 call nf95_inq_varid(ncid, "latitude", varid)
147 call nf95_gw_var(ncid, varid, dlat_ini)
148 jmdep = size(dlat_ini)
149
150 call nf95_inq_dimid(ncid, "time", dimid)
151 call NF95_INQuire_DIMension(ncid, dimid, nclen=lmdep)
152 print *, 'lmdep = ', lmdep
153 ! Coordonnée temporelle fichiers AMIP pas en jours. Ici on suppose
154 ! qu'on a 12 mois (de 30 jours).
155 IF (lmdep /= 12) then
156 print *, 'Unknown AMIP file: not 12 months?'
157 STOP 1
158 end IF
159
160 ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
161 ALLOCATE (dlon(imdep), dlat(jmdep))
162 call NF95_INQ_VARID(ncid, 'sicbcs', varid)
163 DO l = 1, lmdep
164 call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))
165 CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
166 CALL inter_barxy (dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &
167 champtime(:, :, l))
168 ENDDO
169
170 call NF95_CLOSE(ncid)
171
172 DEALLOCATE(dlon, dlat, champ, dlon_ini, dlat_ini)
173 PRINT *, 'Interpolation temporelle'
174 allocate(yder(lmdep))
175
176 DO j = 1, jjm + 1
177 DO i = 1, iim
178 yder = SPLINE(tmidmonth, champtime(i, j, :))
179 DO k = 1, 360
180 champan(i, j, k) = SPLINT(tmidmonth, champtime(i, j, :), yder, &
181 real(k-1))
182 ENDDO
183 ENDDO
184 ENDDO
185
186 deallocate(champtime, yder)
187
188 ! Convert from percentage to normal fraction and keep sea ice
189 ! between 0 and 1:
190 champan(:iim, :, :) = max(0., (min(1., (champan(:iim, :, :) / 100.))))
191 champan(iim + 1, :, :) = champan(1, :, :)
192
193 DO k = 1, 360
194 phy_ice = pack(champan(:, :, k), dyn_phy)
195
196 ! (utilisation de la sous-maille fractionnelle tandis que l'ancien
197 ! codage utilisait l'indicateur du sol (0, 1, 2, 3))
198 ! PB en attendant de mettre fraction de terre
199 WHERE (phy_ice < EPSFRA) phy_ice = 0.
200
201 pctsrf_t(:, is_ter, k) = pctsrf(:, is_ter)
202 pctsrf_t(:, is_lic, k) = pctsrf(:, is_lic)
203 pctsrf_t(:, is_sic, k) = max(phy_ice - pctsrf_t(:, is_lic, k), 0.)
204 ! Il y a des cas où il y a de la glace dans landiceref et
205 ! pas dans AMIP
206 WHERE (1. - zmasq < EPSFRA)
207 pctsrf_t(:, is_sic, k) = 0.
208 pctsrf_t(:, is_oce, k) = 0.
209 elsewhere
210 where (pctsrf_t(:, is_sic, k) >= 1 - zmasq)
211 pctsrf_t(:, is_sic, k) = 1. - zmasq
212 pctsrf_t(:, is_oce, k) = 0.
213 ELSEwhere
214 pctsrf_t(:, is_oce, k) = 1. - zmasq - pctsrf_t(:, is_sic, k)
215 where (pctsrf_t(:, is_oce, k) < EPSFRA)
216 pctsrf_t(:, is_oce, k) = 0.
217 pctsrf_t(:, is_sic, k) = 1 - zmasq
218 end where
219 end where
220 end where
221
222 DO i = 1, klon
223 if (pctsrf_t(i, is_oce, k) < 0.) then
224 print *, 'Problème sous maille : pctsrf_t(', i, &
225 ', is_oce, ', k, ') = ', pctsrf_t(i, is_oce, k)
226 ENDIF
227 IF (abs(pctsrf_t(i, is_ter, k) + pctsrf_t(i, is_lic, k) &
228 + pctsrf_t(i, is_oce, k) + pctsrf_t(i, is_sic, k) - 1.) &
229 > EPSFRA) THEN
230 print *, 'Problème sous surface :'
231 print *, "pctsrf_t(", i, ", :, ", k, ") = ", &
232 pctsrf_t(i, :, k)
233 print *, "phy_ice(", i, ") = ", phy_ice(i)
234 ENDIF
235 END DO
236 ENDDO
237
238 PRINT *, 'Traitement de la sst'
239 call NF95_OPEN('amipbc_sst_1x1.nc', NF90_NOWRITE, ncid)
240
241 call nf95_inq_varid(ncid, "longitude", varid)
242 call nf95_gw_var(ncid, varid, dlon_ini)
243 imdep = size(dlon_ini)
244
245 call nf95_inq_varid(ncid, "latitude", varid)
246 call nf95_gw_var(ncid, varid, dlat_ini)
247 jmdep = size(dlat_ini)
248
249 call nf95_inq_dimid(ncid, "time", dimid)
250 call NF95_INQuire_DIMension(ncid, dimid, nclen=lmdep)
251 print *, 'lmdep = ', lmdep
252 !PM28/02/2002 : nouvelle coord temporelle fichiers AMIP pas en jours
253 ! Ici on suppose qu'on a 12 mois (de 30 jours).
254 IF (lmdep /= 12) stop 'Unknown AMIP file: not 12 months?'
255
256 ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
257 IF(extrap) THEN
258 ALLOCATE (work(imdep, jmdep))
259 ENDIF
260 ALLOCATE(dlon(imdep), dlat(jmdep))
261 call NF95_INQ_VARID(ncid, 'tosbcs', varid)
262
263 DO l = 1, lmdep
264 call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))
265 CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
266 IF (extrap) THEN
267 CALL extrapol(champ, imdep, jmdep, 999999., .TRUE., .TRUE., 2, work)
268 ENDIF
269
270 CALL inter_barxy (dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &
271 champtime(:, :, l))
272 ENDDO
273
274 call NF95_CLOSE(ncid)
275
276 DEALLOCATE(dlon, dlat, champ, dlon_ini, dlat_ini)
277 allocate(yder(lmdep))
278
279 ! interpolation temporelle
280 DO j = 1, jjm + 1
281 DO i = 1, iim
282 yder = SPLINE(tmidmonth, champtime(i, j, :))
283 DO k = 1, 360
284 champan(i, j, k) = SPLINT(tmidmonth, champtime(i, j, :), yder, &
285 real(k-1))
286 ENDDO
287 ENDDO
288 ENDDO
289
290 deallocate(champtime, yder)
291 champan(iim + 1, :, :) = champan(1, :, :)
292
293 !IM14/03/2002 : SST amipbc greater then 271.38
294 PRINT *, 'SUB. limit_netcdf.F IM : SST Amipbc >= 271.38 '
295 DO k = 1, 360
296 DO j = 1, jjm + 1
297 DO i = 1, iim
298 champan(i, j, k) = amax1(champan(i, j, k), 271.38)
299 ENDDO
300 champan(iim + 1, j, k) = champan(1, j, k)
301 ENDDO
302 ENDDO
303 forall (k = 1:360) phy_sst(:, k) = pack(champan(:, :, k), dyn_phy)
304
305 PRINT *, "Traitement de l'albedo..."
306 call NF95_OPEN('Albedo.nc', NF90_NOWRITE, ncid)
307
308 call nf95_inq_varid(ncid, "longitude", varid)
309 call nf95_gw_var(ncid, varid, dlon_ini)
310 imdep = size(dlon_ini)
311
312 call nf95_inq_varid(ncid, "latitude", varid)
313 call nf95_gw_var(ncid, varid, dlat_ini)
314 jmdep = size(dlat_ini)
315
316 call nf95_inq_varid(ncid, "temps", varid)
317 call nf95_gw_var(ncid, varid, timeyear)
318 lmdep = size(timeyear)
319
320 ALLOCATE (champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
321 ALLOCATE (dlon(imdep), dlat(jmdep))
322 call NF95_INQ_VARID(ncid, 'ALBEDO', varid)
323
324 DO l = 1, lmdep
325 PRINT *, "timeyear(", l, ") =", timeyear(l)
326 call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))
327 CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
328 CALL inter_barxy(dlon, dlat(:jmdep-1), champ, rlonu(:iim), rlatv, &
329 champtime(:, :, l))
330 ENDDO
331
332 call NF95_CLOSE(ncid)
333
334 deallocate(dlon_ini, dlat_ini)
335 allocate(yder(lmdep))
336
337 ! interpolation temporelle
338 DO j = 1, jjm + 1
339 DO i = 1, iim
340 yder = SPLINE(timeyear, champtime(i, j, :))
341 DO k = 1, 360
342 champan(i, j, k) = SPLINT(timeyear, champtime(i, j, :), yder, &
343 real(k-1))
344 ENDDO
345 ENDDO
346 ENDDO
347 deallocate(timeyear)
348
349 champan(iim + 1, :, :) = champan(1, :, :)
350 forall (k = 1:360) phy_alb(:, k) = pack(champan(:, :, k), dyn_phy)
351
352 DO k = 1, 360
353 DO i = 1, klon
354 phy_bil(i, k) = 0.0
355 ENDDO
356 ENDDO
357
358 PRINT *, 'Ecriture du fichier limit'
359
360 call NF95_CREATE("limit.nc", NF90_CLOBBER, nid)
361
362 ierr = NF90_PUT_ATT(nid, NF90_GLOBAL, "title", &
363 "Fichier conditions aux limites")
364 call NF95_DEF_DIM (nid, "points_physiques", klon, ndim)
365 call NF95_DEF_DIM (nid, "time", NF90_UNLIMITED, ntim)
366
367 dims(1) = ndim
368 dims(2) = ntim
369
370 ierr = NF90_DEF_VAR (nid, "TEMPS", NF90_FLOAT, ntim, id_tim)
371 ierr = NF90_PUT_ATT (nid, id_tim, "title", "Jour dans l annee")
372 ierr = NF90_DEF_VAR (nid, "FOCE", NF90_FLOAT, dims, id_FOCE)
373 ierr = NF90_PUT_ATT (nid, id_FOCE, "title", "Fraction ocean")
374
375 ierr = NF90_DEF_VAR (nid, "FSIC", NF90_FLOAT, dims, id_FSIC)
376 ierr = NF90_PUT_ATT (nid, id_FSIC, "title", "Fraction glace de mer")
377
378 ierr = NF90_DEF_VAR (nid, "FTER", NF90_FLOAT, dims, id_FTER)
379 ierr = NF90_PUT_ATT (nid, id_FTER, "title", "Fraction terre")
380
381 ierr = NF90_DEF_VAR (nid, "FLIC", NF90_FLOAT, dims, id_FLIC)
382 ierr = NF90_PUT_ATT (nid, id_FLIC, "title", "Fraction land ice")
383
384 ierr = NF90_DEF_VAR (nid, "SST", NF90_FLOAT, dims, id_SST)
385 ierr = NF90_PUT_ATT (nid, id_SST, "title", &
386 "Temperature superficielle de la mer")
387 ierr = NF90_DEF_VAR (nid, "BILS", NF90_FLOAT, dims, id_BILS)
388 ierr = NF90_PUT_ATT (nid, id_BILS, "title", &
389 "Reference flux de chaleur au sol")
390 ierr = NF90_DEF_VAR (nid, "ALB", NF90_FLOAT, dims, id_ALB)
391 ierr = NF90_PUT_ATT (nid, id_ALB, "title", "Albedo a la surface")
392 ierr = NF90_DEF_VAR (nid, "RUG", NF90_FLOAT, dims, id_RUG)
393 ierr = NF90_PUT_ATT (nid, id_RUG, "title", "Rugosite")
394
395 call NF95_ENDDEF(nid)
396
397 DO k = 1, 360
398 debut(1) = 1
399 debut(2) = k
400
401 ierr = NF90_PUT_VAR(nid, id_tim, REAL(k), (/k/))
402 ierr = NF90_PUT_VAR(nid, id_FOCE, pctsrf_t(:, is_oce, k), debut)
403 ierr = NF90_PUT_VAR (nid, id_FSIC, pctsrf_t(:, is_sic, k), debut)
404 ierr = NF90_PUT_VAR (nid, id_FTER, pctsrf_t(:, is_ter, k), debut)
405 ierr = NF90_PUT_VAR (nid, id_FLIC, pctsrf_t(:, is_lic, k), debut)
406 ierr = NF90_PUT_VAR (nid, id_SST, phy_sst(:, k), debut)
407 ierr = NF90_PUT_VAR (nid, id_BILS, phy_bil(:, k), debut)
408 ierr = NF90_PUT_VAR (nid, id_ALB, phy_alb(:, k), debut)
409 ierr = NF90_PUT_VAR (nid, id_RUG, phy_rug(:, k), debut)
410 ENDDO
411
412 call NF95_CLOSE(nid)
413
414 END SUBROUTINE limit
415
416 end module limit_mod

  ViewVC Help
Powered by ViewVC 1.1.21