/[lmdze]/trunk/libf/phylmd/phyredem.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/phyredem.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 54 - (show annotations)
Tue Dec 6 15:07:04 2011 UTC (12 years, 5 months ago) by guez
File size: 13599 byte(s)
Removed Numerical Recipes procedure "ran1". Replaced calls to "ran1"
in "inidissip" by calls to intrinsic procedures.

Split file "interface_surf.f90" into a file with a module containing
only variables, "interface_surf", and single-procedure files. Gathered
files into directory "Interface_surf".

Added argument "cdivu" to "gradiv" and "gradiv2", "cdivh" to
"divgrad2" and "divgrad", and "crot" to "nxgraro2" and
"nxgrarot". "dissip" now uses variables "cdivu", "cdivh" and "crot"
from module "inidissip_m", so it can pass them to "gradiv2",
etc. Thanks to this modification, we avoid a circular dependency
betwwen "inidissip.f90" and "gradiv2.f90", etc. The value -1. used by
"gradiv2", for instance, during computation of eigenvalues is not the
value "cdivu" computed by "inidissip".

Extracted procedure "start_inter_3d" from module "startdyn", to its
own module.

In "inidissip", unrolled loop on "ii". I find it clearer now.

Moved variables "matriceun", "matriceus", "matricevn", "matricevs",
"matrinvn" and "matrinvs" from module "parafilt" to module
"inifilr_m". Moved variables "jfiltnu", "jfiltnv", "jfiltsu",
"jfiltsv" from module "coefils" to module "inifilr_m".

1 module phyredem_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE phyredem(fichnom, rlat, rlon, pctsrf, tsol, tsoil, tslab, &
8 seaice, qsurf, qsol, snow, albedo, alblw, evap, rain_fall,&
9 snow_fall, solsw, sollw, fder, radsol, frugs, agesno, zmea,&
10 zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien,&
11 rnebcon, ratqs, clwcon, run_off_lic_0)
12
13 ! From phylmd/phyredem.F, v 1.3 2005/05/25 13:10:09
14 ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
15 ! Objet: Ecriture de l'etat de démarrage ou redémarrage pour la physique
16
17 USE indicesol, ONLY : is_lic, is_oce, is_sic, is_ter, nbsrf
18 USE dimphy, ONLY : klev, klon, zmasq
19 USE dimsoil, ONLY : nsoilmx
20 USE temps, ONLY : itau_phy
21 USE netcdf95, ONLY : nf95_create, nf95_put_att, nf95_def_dim, &
22 nf95_def_var, nf95_enddef, nf95_redef, nf95_put_var, nf95_close
23 USE netcdf, ONLY : nf90_clobber, nf90_global, nf90_float
24
25 CHARACTER(len=*) fichnom
26 REAL, INTENT (IN) :: rlat(klon), rlon(klon)
27 REAL :: tsol(klon, nbsrf)
28 REAL :: tsoil(klon, nsoilmx, nbsrf)
29
30 REAL :: tslab(klon), seaice(klon) !IM "slab" ocean
31 REAL :: qsurf(klon, nbsrf)
32 REAL, intent(in):: qsol(klon)
33 REAL :: snow(klon, nbsrf)
34 REAL :: albedo(klon, nbsrf)
35
36 REAL :: alblw(klon, nbsrf)
37
38 REAL :: evap(klon, nbsrf)
39 REAL :: rain_fall(klon)
40 REAL :: snow_fall(klon)
41 REAL :: solsw(klon)
42 REAL :: sollw(klon)
43 REAL :: fder(klon)
44 REAL :: radsol(klon)
45 REAL :: frugs(klon, nbsrf)
46 REAL :: agesno(klon, nbsrf)
47 REAL :: zmea(klon)
48 REAL, intent(in):: zstd(klon)
49 REAL, intent(in):: zsig(klon)
50 REAL :: zgam(klon)
51 REAL :: zthe(klon)
52 REAL :: zpic(klon)
53 REAL :: zval(klon)
54 REAL :: pctsrf(klon, nbsrf)
55 REAL :: t_ancien(klon, klev), q_ancien(klon, klev)
56 REAL :: clwcon(klon, klev), rnebcon(klon, klev), ratqs(klon, klev)
57 REAL :: run_off_lic_0(klon)
58
59 INTEGER :: nid, nvarid, idim2, idim3
60
61 INTEGER :: isoil, nsrf
62 CHARACTER (7) :: str7
63 CHARACTER (2) :: str2
64
65 !------------------------------------------------------------
66
67 PRINT *, 'Call sequence information: phyredem'
68 CALL nf95_create(fichnom, nf90_clobber, nid)
69
70 call nf95_put_att(nid, nf90_global, 'title', &
71 'Fichier redémarrage physique')
72 call nf95_put_att(nid, nf90_global, "itau_phy", itau_phy)
73
74 call nf95_def_dim(nid, 'points_physiques', klon, idim2)
75 call nf95_def_dim(nid, 'horizon_vertical', klon*klev, idim3)
76
77 call nf95_def_var(nid, 'longitude', nf90_float, idim2, nvarid)
78 call nf95_put_att(nid, nvarid, 'title', &
79 'Longitudes de la grille physique')
80 call nf95_enddef(nid)
81 call nf95_put_var(nid, nvarid, rlon)
82
83 call nf95_redef(nid)
84 call nf95_def_var(nid, 'latitude', nf90_float, idim2, nvarid)
85 call nf95_put_att(nid, nvarid, 'title', &
86 'Latitudes de la grille physique')
87 call nf95_enddef(nid)
88 call nf95_put_var(nid, nvarid, rlat)
89
90 ! PB ajout du masque terre/mer
91
92 call nf95_redef(nid)
93 call nf95_def_var(nid, 'masque', nf90_float, idim2, nvarid)
94 call nf95_put_att(nid, nvarid, 'title', 'masque terre mer')
95 call nf95_enddef(nid)
96 call nf95_put_var(nid, nvarid, zmasq)
97 ! BP ajout des fraction de chaque sous-surface
98
99 ! 1. fraction de terre
100
101 call nf95_redef(nid)
102 call nf95_def_var(nid, 'FTER', nf90_float, idim2, nvarid)
103 call nf95_put_att(nid, nvarid, 'title', 'fraction de continent')
104 call nf95_enddef(nid)
105 call nf95_put_var(nid, nvarid, pctsrf(:, is_ter))
106
107 ! 2. Fraction de glace de terre
108
109 call nf95_redef(nid)
110 call nf95_def_var(nid, 'FLIC', nf90_float, idim2, nvarid)
111 call nf95_put_att(nid, nvarid, 'title', 'fraction glace de terre')
112 call nf95_enddef(nid)
113 call nf95_put_var(nid, nvarid, pctsrf(:, is_lic))
114
115 ! 3. fraction ocean
116
117 call nf95_redef(nid)
118 call nf95_def_var(nid, 'FOCE', nf90_float, idim2, nvarid)
119 call nf95_put_att(nid, nvarid, 'title', 'fraction ocean')
120 call nf95_enddef(nid)
121 call nf95_put_var(nid, nvarid, pctsrf(:, is_oce))
122
123 ! 4. Fraction glace de mer
124
125 call nf95_redef(nid)
126 call nf95_def_var(nid, 'FSIC', nf90_float, idim2, nvarid)
127 call nf95_put_att(nid, nvarid, 'title', 'fraction glace mer')
128 call nf95_enddef(nid)
129 call nf95_put_var(nid, nvarid, pctsrf(:, is_sic))
130
131 DO nsrf = 1, nbsrf
132 IF (nsrf<=99) THEN
133 WRITE (str2, '(i2.2)') nsrf
134 call nf95_redef(nid)
135 call nf95_def_var(nid, 'TS'//str2, nf90_float, idim2, nvarid)
136 call nf95_put_att(nid, nvarid, 'title', &
137 'Temperature de surface No.'//str2)
138 call nf95_enddef(nid)
139 ELSE
140 PRINT *, 'Trop de sous-mailles'
141 STOP 1
142 END IF
143 call nf95_put_var(nid, nvarid, tsol(:, nsrf))
144 END DO
145
146 DO nsrf = 1, nbsrf
147 DO isoil = 1, nsoilmx
148 IF (isoil<=99 .AND. nsrf<=99) THEN
149 WRITE (str7, '(i2.2, "srf", i2.2)') isoil, nsrf
150 call nf95_redef(nid)
151 call nf95_def_var(nid, 'Tsoil'//str7, nf90_float, idim2, nvarid)
152 call nf95_put_att(nid, nvarid, 'title', &
153 'Temperature du sol No.'//str7)
154 call nf95_enddef(nid)
155 ELSE
156 PRINT *, 'Trop de couches'
157 STOP 1
158 END IF
159 call nf95_put_var(nid, nvarid, tsoil(:, isoil, nsrf))
160 END DO
161 END DO
162
163 !IM "slab" ocean
164 call nf95_redef(nid)
165 call nf95_def_var(nid, 'TSLAB', nf90_float, idim2, nvarid)
166 call nf95_put_att(nid, nvarid, 'title', &
167 'Ecart de la SST (pour slab-ocean)')
168 call nf95_enddef(nid)
169 call nf95_put_var(nid, nvarid, tslab)
170
171 call nf95_redef(nid)
172 call nf95_def_var(nid, 'SEAICE', nf90_float, idim2, nvarid)
173 call nf95_put_att(nid, nvarid, 'title', &
174 'Glace de mer kg/m2 (pour slab-ocean)')
175 call nf95_enddef(nid)
176 call nf95_put_var(nid, nvarid, seaice)
177
178 DO nsrf = 1, nbsrf
179 IF (nsrf<=99) THEN
180 WRITE (str2, '(i2.2)') nsrf
181 call nf95_redef(nid)
182 call nf95_def_var(nid, 'QS'//str2, nf90_float, idim2, nvarid)
183 call nf95_put_att(nid, nvarid, 'title', &
184 'Humidite de surface No.'//str2)
185 call nf95_enddef(nid)
186 ELSE
187 PRINT *, 'Trop de sous-mailles'
188 STOP 1
189 END IF
190 call nf95_put_var(nid, nvarid, qsurf(:, nsrf))
191 END DO
192
193 call nf95_redef(nid)
194 call nf95_def_var(nid, 'QSOL', nf90_float, idim2, nvarid)
195 call nf95_put_att(nid, nvarid, 'title', 'Eau dans le sol (mm)')
196 call nf95_enddef(nid)
197 call nf95_put_var(nid, nvarid, qsol)
198
199 DO nsrf = 1, nbsrf
200 IF (nsrf<=99) THEN
201 WRITE (str2, '(i2.2)') nsrf
202 call nf95_redef(nid)
203 call nf95_def_var(nid, 'ALBE'//str2, nf90_float, idim2, nvarid)
204 call nf95_put_att(nid, nvarid, 'title', &
205 'albedo de surface No.'//str2)
206 call nf95_enddef(nid)
207 ELSE
208 PRINT *, 'Trop de sous-mailles'
209 STOP 1
210 END IF
211 call nf95_put_var(nid, nvarid, albedo(:, nsrf))
212 END DO
213
214 !IM BEG albedo LW
215 DO nsrf = 1, nbsrf
216 IF (nsrf<=99) THEN
217 WRITE (str2, '(i2.2)') nsrf
218 call nf95_redef(nid)
219 call nf95_def_var(nid, 'ALBLW'//str2, nf90_float, idim2, nvarid)
220 call nf95_put_att(nid, nvarid, 'title', &
221 'albedo LW de surface No.'//str2)
222 call nf95_enddef(nid)
223 ELSE
224 PRINT *, 'Trop de sous-mailles'
225 STOP 1
226 END IF
227 call nf95_put_var(nid, nvarid, alblw(:, nsrf))
228 END DO
229 !IM END albedo LW
230
231 DO nsrf = 1, nbsrf
232 IF (nsrf<=99) THEN
233 WRITE (str2, '(i2.2)') nsrf
234 call nf95_redef(nid)
235 call nf95_def_var(nid, 'EVAP'//str2, nf90_float, idim2, nvarid)
236 call nf95_put_att(nid, nvarid, 'title', &
237 'Evaporation de surface No.'//str2)
238 call nf95_enddef(nid)
239 ELSE
240 PRINT *, 'Trop de sous-mailles'
241 STOP 1
242 END IF
243 call nf95_put_var(nid, nvarid, evap(:, nsrf))
244 END DO
245
246 DO nsrf = 1, nbsrf
247 IF (nsrf<=99) THEN
248 WRITE (str2, '(i2.2)') nsrf
249 call nf95_redef(nid)
250 call nf95_def_var(nid, 'SNOW'//str2, nf90_float, idim2, nvarid)
251 call nf95_put_att(nid, nvarid, 'title', &
252 'Neige de surface No.'//str2)
253 call nf95_enddef(nid)
254 ELSE
255 PRINT *, 'Trop de sous-mailles'
256 STOP 1
257 END IF
258 call nf95_put_var(nid, nvarid, snow(:, nsrf))
259 END DO
260
261 call nf95_redef(nid)
262 call nf95_def_var(nid, 'RADS', nf90_float, idim2, nvarid)
263 call nf95_put_att(nid, nvarid, 'title', &
264 'Rayonnement net a la surface')
265 call nf95_enddef(nid)
266 call nf95_put_var(nid, nvarid, radsol)
267
268 call nf95_redef(nid)
269 call nf95_def_var(nid, 'solsw', nf90_float, idim2, nvarid)
270 call nf95_put_att(nid, nvarid, 'title', &
271 'Rayonnement solaire a la surface')
272 call nf95_enddef(nid)
273 call nf95_put_var(nid, nvarid, solsw)
274
275 call nf95_redef(nid)
276 call nf95_def_var(nid, 'sollw', nf90_float, idim2, nvarid)
277 call nf95_put_att(nid, nvarid, 'title', &
278 'Rayonnement IF a la surface')
279 call nf95_enddef(nid)
280 call nf95_put_var(nid, nvarid, sollw)
281
282 call nf95_redef(nid)
283 call nf95_def_var(nid, 'fder', nf90_float, idim2, nvarid)
284 call nf95_put_att(nid, nvarid, 'title', 'Derive de flux')
285 call nf95_enddef(nid)
286 call nf95_put_var(nid, nvarid, fder)
287
288 call nf95_redef(nid)
289 call nf95_def_var(nid, 'rain_f', nf90_float, idim2, nvarid)
290 call nf95_put_att(nid, nvarid, 'title', 'precipitation liquide')
291 call nf95_enddef(nid)
292 call nf95_put_var(nid, nvarid, rain_fall)
293
294 call nf95_redef(nid)
295 call nf95_def_var(nid, 'snow_f', nf90_float, idim2, nvarid)
296 call nf95_put_att(nid, nvarid, 'title', 'precipitation solide')
297 call nf95_enddef(nid)
298 call nf95_put_var(nid, nvarid, snow_fall)
299
300 DO nsrf = 1, nbsrf
301 IF (nsrf<=99) THEN
302 WRITE (str2, '(i2.2)') nsrf
303 call nf95_redef(nid)
304 call nf95_def_var(nid, 'RUG'//str2, nf90_float, idim2, nvarid)
305 call nf95_put_att(nid, nvarid, 'title', &
306 'rugosite de surface No.'//str2)
307 call nf95_enddef(nid)
308 ELSE
309 PRINT *, 'Trop de sous-mailles'
310 STOP 1
311 END IF
312 call nf95_put_var(nid, nvarid, frugs(:, nsrf))
313 END DO
314
315 DO nsrf = 1, nbsrf
316 IF (nsrf<=99) THEN
317 WRITE (str2, '(i2.2)') nsrf
318 call nf95_redef(nid)
319 call nf95_def_var(nid, 'AGESNO'//str2, nf90_float, idim2, nvarid)
320 call nf95_put_att(nid, nvarid, 'title', &
321 'Age de la neige surface No.'//str2)
322 call nf95_enddef(nid)
323 ELSE
324 PRINT *, 'Trop de sous-mailles'
325 STOP 1
326 END IF
327 call nf95_put_var(nid, nvarid, agesno(:, nsrf))
328 END DO
329
330 call nf95_redef(nid)
331 call nf95_def_var(nid, 'ZMEA', nf90_float, idim2, nvarid)
332 call nf95_enddef(nid)
333 call nf95_put_var(nid, nvarid, zmea)
334
335 call nf95_redef(nid)
336 call nf95_def_var(nid, 'ZSTD', nf90_float, idim2, nvarid)
337 call nf95_enddef(nid)
338 call nf95_put_var(nid, nvarid, zstd)
339 call nf95_redef(nid)
340 call nf95_def_var(nid, 'ZSIG', nf90_float, idim2, nvarid)
341 call nf95_enddef(nid)
342 call nf95_put_var(nid, nvarid, zsig)
343 call nf95_redef(nid)
344 call nf95_def_var(nid, 'ZGAM', nf90_float, idim2, nvarid)
345 call nf95_enddef(nid)
346 call nf95_put_var(nid, nvarid, zgam)
347 call nf95_redef(nid)
348 call nf95_def_var(nid, 'ZTHE', nf90_float, idim2, nvarid)
349 call nf95_enddef(nid)
350 call nf95_put_var(nid, nvarid, zthe)
351 call nf95_redef(nid)
352 call nf95_def_var(nid, 'ZPIC', nf90_float, idim2, nvarid)
353 call nf95_enddef(nid)
354 call nf95_put_var(nid, nvarid, zpic)
355 call nf95_redef(nid)
356 call nf95_def_var(nid, 'ZVAL', nf90_float, idim2, nvarid)
357 call nf95_enddef(nid)
358 call nf95_put_var(nid, nvarid, zval)
359
360 call nf95_redef(nid)
361 call nf95_def_var(nid, 'TANCIEN', nf90_float, idim3, nvarid)
362 call nf95_enddef(nid)
363 call nf95_put_var(nid, nvarid, pack(t_ancien, .true.))
364
365 call nf95_redef(nid)
366 call nf95_def_var(nid, 'QANCIEN', nf90_float, idim3, nvarid)
367 call nf95_enddef(nid)
368 call nf95_put_var(nid, nvarid, pack(q_ancien, .true.))
369
370 call nf95_redef(nid)
371 call nf95_def_var(nid, 'RUGMER', nf90_float, idim2, nvarid)
372 call nf95_put_att(nid, nvarid, 'title', &
373 'Longueur de rugosite sur mer')
374 call nf95_enddef(nid)
375 call nf95_put_var(nid, nvarid, frugs(:, is_oce))
376
377 call nf95_redef(nid)
378 call nf95_def_var(nid, 'CLWCON', nf90_float, idim2, nvarid)
379 call nf95_put_att(nid, nvarid, 'title', 'Eau liquide convective')
380 call nf95_enddef(nid)
381 call nf95_put_var(nid, nvarid, clwcon)
382
383 call nf95_redef(nid)
384 call nf95_def_var(nid, 'RNEBCON', nf90_float, idim2, nvarid)
385 call nf95_put_att(nid, nvarid, 'title', 'Nebulosite convective')
386 call nf95_enddef(nid)
387 call nf95_put_var(nid, nvarid, rnebcon)
388
389 call nf95_redef(nid)
390 call nf95_def_var(nid, 'RATQS', nf90_float, idim2, nvarid)
391 call nf95_put_att(nid, nvarid, 'title', 'Ratqs')
392 call nf95_enddef(nid)
393 call nf95_put_var(nid, nvarid, ratqs)
394
395 ! run_off_lic_0
396
397 call nf95_redef(nid)
398 call nf95_def_var(nid, 'RUNOFFLIC0', nf90_float, idim2, nvarid)
399 call nf95_put_att(nid, nvarid, 'title', 'Runofflic0')
400 call nf95_enddef(nid)
401 call nf95_put_var(nid, nvarid, run_off_lic_0)
402
403 call nf95_close(nid)
404
405 END SUBROUTINE phyredem
406
407 end module phyredem_m

  ViewVC Help
Powered by ViewVC 1.1.21