/[lmdze]/trunk/libf/dyn3d/limit.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/limit.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 15 - (show annotations)
Fri Aug 1 15:24:12 2008 UTC (15 years, 8 months ago) by guez
File size: 13958 byte(s)
-- Minor modification of input/output:

Added variable "Sigma_O3_Royer" to "histday.nc". "ecrit_day" is not
modified in "physiq". Removed variables "pyu1", "pyv1", "ftsol1",
"ftsol2", "ftsol3", "ftsol4", "psrf1", "psrf2", "psrf3", "psrf4"
"mfu", "mfd", "en_u", "en_d", "de_d", "de_u", "coefh" from
"histrac.nc".

Variable "raz_date" of module "conf_gcm_m" has logical type instead of
integer type.

-- Should not change any result at run time:

Modified calls to "IOIPSL_Lionel" procedures because the interfaces of
these procedures have been simplified.

Changed name of variable in module "start_init_orog_m": "masque" to
"mask".

Created a module containing procedure "phyredem".

Removed arguments "punjours", "pdayref" and "ptimestep" of procedure
"iniphysiq".

Renamed procedure "gr_phy_write" to "gr_phy_write_2d". Created
procedure "gr_phy_write_3d".

Removed procedures "ini_undefstd", "moy_undefSTD", "calcul_STDlev",
"calcul_divers".

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

  ViewVC Help
Powered by ViewVC 1.1.21