source: LMDZ5/trunk/libf/phylmd/phyetat0.F90 @ 2239

Last change on this file since 2239 was 2237, checked in by fhourdin, 9 years ago

Prise en compte des nouveaux alebedo dans les fichiers de redémarrage.
Retour à 1+1=2

Taking into account new albedos in restart files. 1+1=2

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 35.0 KB
Line 
1! $Id: phyetat0.F90 2237 2015-03-20 06:53:17Z emillour $
2
3SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0)
4
5  USE dimphy, only: klon, zmasq, klev, nslay
6  USE iophy, ONLY : init_iophy_new
7  USE ocean_cpl_mod,    ONLY : ocean_cpl_init
8  USE fonte_neige_mod,  ONLY : fonte_neige_init
9  USE pbl_surface_mod,  ONLY : pbl_surface_init
10  USE surface_data,     ONLY : type_ocean, version_ocean
11  USE phys_state_var_mod, ONLY : ancien_ok, clwcon, detr_therm, dtime, &
12       du_gwd_rando, dv_gwd_rando, entr_therm, f0, falb1, falb2, fm_therm, &
13       falb_dir, falb_dif, &
14       ftsol, pbl_tke, pctsrf, q_ancien, radpas, radsol, rain_fall, ratqs, &
15       rlat, rlon, rnebcon, rugoro, sig1, snow_fall, solaire_etat0, sollw, sollwdown, &
16       solsw, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
17       wake_deltat, wake_delta_pbl_TKE, delta_tsurf, wake_fip, wake_pe, &
18       wake_s, zgam, &
19       zmax0, zmea, zpic, zsig, &
20       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl
21  USE iostart, ONLY : close_startphy, get_field, get_var, open_startphy
22  USE infotrac, only: nbtr, type_trac, tname, niadv
23  USE traclmdz_mod,    ONLY : traclmdz_from_restart
24  USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl, co2_send
25  USE indice_sol_mod, only: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic
26  USE ocean_slab_mod, ONLY: tslab, seaice, tice, ocean_slab_init
27
28  IMPLICIT none
29  !======================================================================
30  ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
31  ! Objet: Lecture de l'etat initial pour la physique
32  !======================================================================
33  include "dimensions.h"
34  include "netcdf.inc"
35  include "dimsoil.h"
36  include "clesphys.h"
37  include "temps.h"
38  include "thermcell.h"
39  include "compbl.h"
40  include "YOMCST.h"
41  !======================================================================
42  CHARACTER*(*) fichnom
43
44  ! les variables globales lues dans le fichier restart
45
46  REAL tsoil(klon, nsoilmx, nbsrf)
47  REAL qsurf(klon, nbsrf)
48  REAL qsol(klon)
49  REAL snow(klon, nbsrf)
50  REAL evap(klon, nbsrf)
51  real fder(klon)
52  REAL frugs(klon, nbsrf)
53  REAL agesno(klon, nbsrf)
54  REAL run_off_lic_0(klon)
55  REAL fractint(klon)
56  REAL trs(klon, nbtr)
57  REAL zts(klon)
58
59  CHARACTER*6 ocean_in
60  LOGICAL ok_veget_in
61
62  INTEGER        longcles
63  PARAMETER    ( longcles = 20 )
64  REAL clesphy0( longcles )
65
66  REAL xmin, xmax
67
68  INTEGER nid, nvarid
69  INTEGER ierr, i, nsrf, isoil , k
70  INTEGER length
71  PARAMETER (length=100)
72  INTEGER it, iiq, isw
73  REAL tab_cntrl(length), tabcntr0(length)
74  CHARACTER*7 str7
75  CHARACTER*2 str2
76  LOGICAL :: found
77
78  ! FH1D
79  !     real iolat(jjm+1)
80  real iolat(jjm+1-1/(iim*jjm))
81
82  ! Ouvrir le fichier contenant l'etat initial:
83
84  CALL open_startphy(fichnom)
85
86  ! Lecture des parametres de controle:
87
88  CALL get_var("controle", tab_cntrl)
89
90!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
91  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
92  ! Les constantes de la physiques sont lues dans la physique seulement.
93  ! Les egalites du type
94  !             tab_cntrl( 5 )=clesphy0(1)
95  ! sont remplacees par
96  !             clesphy0(1)=tab_cntrl( 5 )
97  ! On inverse aussi la logique.
98  ! On remplit les tab_cntrl avec les parametres lus dans les .def
99!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
100
101  DO i = 1, length
102     tabcntr0( i ) = tab_cntrl( i )
103  ENDDO
104
105  tab_cntrl(1)=dtime
106  tab_cntrl(2)=radpas
107
108  ! co2_ppm : value from the previous time step
109  IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
110     co2_ppm = tab_cntrl(3)
111     RCO2    = co2_ppm * 1.0e-06  * 44.011/28.97
112     ! ELSE : keep value from .def
113  END IF
114
115  ! co2_ppm0 : initial value of atmospheric CO2 (from create_etat0_limit.e .def)
116  co2_ppm0   = tab_cntrl(16)
117
118  solaire_etat0      = tab_cntrl(4)
119  tab_cntrl(5)=iflag_con
120  tab_cntrl(6)=nbapp_rad
121
122  if (cycle_diurne) tab_cntrl( 7) =1.
123  if (soil_model) tab_cntrl( 8) =1.
124  if (new_oliq) tab_cntrl( 9) =1.
125  if (ok_orodr) tab_cntrl(10) =1.
126  if (ok_orolf) tab_cntrl(11) =1.
127  if (ok_limitvrai) tab_cntrl(12) =1.
128
129  itau_phy = tab_cntrl(15)
130
131  clesphy0(1)=tab_cntrl( 5 )
132  clesphy0(2)=tab_cntrl( 6 )
133  clesphy0(3)=tab_cntrl( 7 )
134  clesphy0(4)=tab_cntrl( 8 )
135  clesphy0(5)=tab_cntrl( 9 )
136  clesphy0(6)=tab_cntrl( 10 )
137  clesphy0(7)=tab_cntrl( 11 )
138  clesphy0(8)=tab_cntrl( 12 )
139
140  ! Lecture des latitudes (coordonnees):
141
142  CALL get_field("latitude", rlat)
143
144  ! Lecture des longitudes (coordonnees):
145
146  CALL get_field("longitude", rlon)
147
148  ! Lecture du masque terre mer
149
150  CALL get_field("masque", zmasq, found)
151  IF (.NOT. found) THEN
152     PRINT*, 'phyetat0: Le champ <masque> est absent'
153     PRINT *, 'fichier startphy non compatible avec phyetat0'
154  ENDIF
155
156  ! Lecture des fractions pour chaque sous-surface
157
158  ! initialisation des sous-surfaces
159
160  pctsrf = 0.
161
162  ! fraction de terre
163
164  CALL get_field("FTER", pctsrf(:, is_ter), found)
165  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FTER> est absent'
166
167  ! fraction de glace de terre
168
169  CALL get_field("FLIC", pctsrf(:, is_lic), found)
170  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FLIC> est absent'
171
172  ! fraction d'ocean
173
174  CALL get_field("FOCE", pctsrf(:, is_oce), found)
175  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FOCE> est absent'
176
177  ! fraction glace de mer
178
179  CALL get_field("FSIC", pctsrf(:, is_sic), found)
180  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FSIC> est absent'
181
182  !  Verification de l'adequation entre le masque et les sous-surfaces
183
184  fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &
185       + pctsrf(1 : klon, is_lic)
186  DO i = 1 , klon
187     IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN
188        WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &
189             'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
190             , pctsrf(i, is_lic)
191        WRITE(*, *) 'Je force la coherence zmasq=fractint'
192        zmasq(i) = fractint(i)
193     ENDIF
194  END DO
195  fractint (1 : klon) =  pctsrf(1 : klon, is_oce)  &
196       + pctsrf(1 : klon, is_sic)
197  DO i = 1 , klon
198     IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN
199        WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &
200             'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
201             , pctsrf(i, is_sic)
202        WRITE(*, *) 'Je force la coherence zmasq=1.-fractint'
203        zmasq(i) = 1. - fractint(i)
204     ENDIF
205  END DO
206
207  ! Lecture des temperatures du sol:
208
209  CALL get_field("TS", ftsol(:, 1), found)
210  IF (.NOT. found) THEN
211     PRINT*, 'phyetat0: Le champ <TS> est absent'
212     PRINT*, '          Mais je vais essayer de lire TS**'
213     DO nsrf = 1, nbsrf
214        IF (nsrf.GT.99) THEN
215           PRINT*, "Trop de sous-mailles"
216           call abort_gcm("phyetat0", "", 1)
217        ENDIF
218        WRITE(str2, '(i2.2)') nsrf
219        CALL get_field("TS"//str2, ftsol(:, nsrf))
220
221        xmin = 1.0E+20
222        xmax = -1.0E+20
223        DO i = 1, klon
224           xmin = MIN(ftsol(i, nsrf), xmin)
225           xmax = MAX(ftsol(i, nsrf), xmax)
226        ENDDO
227        PRINT*, 'Temperature du sol TS**:', nsrf, xmin, xmax
228     ENDDO
229  ELSE
230     PRINT*, 'phyetat0: Le champ <TS> est present'
231     PRINT*, '          J ignore donc les autres temperatures TS**'
232     xmin = 1.0E+20
233     xmax = -1.0E+20
234     DO i = 1, klon
235        xmin = MIN(ftsol(i, 1), xmin)
236        xmax = MAX(ftsol(i, 1), xmax)
237     ENDDO
238     PRINT*, 'Temperature du sol <TS>', xmin, xmax
239     DO nsrf = 2, nbsrf
240        DO i = 1, klon
241           ftsol(i, nsrf) = ftsol(i, 1)
242        ENDDO
243     ENDDO
244  ENDIF
245
246!===================================================================
247  ! Lecture des albedo difus et direct
248
249  DO nsrf = 1, nbsrf
250     DO isw=1, nsw
251        IF (isw.GT.99 .AND. nsrf.GT.99) THEN
252           PRINT*, "Trop de bandes SW ou sous-mailles"
253           call abort_gcm("phyetat0", "", 1)
254        ENDIF
255        WRITE(str7, '(i2.2, "srf", i2.2)') isw, nsrf
256
257        CALL get_field('A_dir_SW'//str7, falb_dir(:, isw, nsrf), found)
258        IF (.NOT. found) THEN
259           PRINT*, "phyetat0: Le champ <A_dir_SW"//str7//"> est absent"
260           PRINT*, "          Il prend donc la valeur de surface"
261           DO i=1, klon
262              falb_dir(i, isw, nsrf)=0.2
263           ENDDO
264        ENDIF
265        CALL get_field('A_dif_SW'//str7, falb_dif(:, isw, nsrf), found)
266        IF (.NOT. found) THEN
267           PRINT*, "phyetat0: Le champ <A_dif_SW"//str7//"> est absent"
268           PRINT*, "          Il prend donc la valeur de surface"
269           DO i=1, klon
270              falb_dif(i, isw, nsrf)=0.2
271           ENDDO
272        ENDIF
273     ENDDO
274  ENDDO
275
276!===================================================================
277  ! Lecture des temperatures du sol profond:
278
279  DO nsrf = 1, nbsrf
280     DO isoil=1, nsoilmx
281        IF (isoil.GT.99 .AND. nsrf.GT.99) THEN
282           PRINT*, "Trop de couches ou sous-mailles"
283           call abort_gcm("phyetat0", "", 1)
284        ENDIF
285        WRITE(str7, '(i2.2, "srf", i2.2)') isoil, nsrf
286
287        CALL get_field('Tsoil'//str7, tsoil(:, isoil, nsrf), found)
288        IF (.NOT. found) THEN
289           PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
290           PRINT*, "          Il prend donc la valeur de surface"
291           DO i=1, klon
292              tsoil(i, isoil, nsrf)=ftsol(i, nsrf)
293           ENDDO
294        ENDIF
295     ENDDO
296  ENDDO
297
298!===================================================================
299  ! Lecture de l'humidite de l'air juste au dessus du sol:
300
301  CALL get_field("QS", qsurf(:, 1), found)
302  IF (.NOT. found) THEN
303     PRINT*, 'phyetat0: Le champ <QS> est absent'
304     PRINT*, '          Mais je vais essayer de lire QS**'
305     DO nsrf = 1, nbsrf
306        IF (nsrf.GT.99) THEN
307           PRINT*, "Trop de sous-mailles"
308           call abort_gcm("phyetat0", "", 1)
309        ENDIF
310        WRITE(str2, '(i2.2)') nsrf
311        CALL get_field("QS"//str2, qsurf(:, nsrf))
312        xmin = 1.0E+20
313        xmax = -1.0E+20
314        DO i = 1, klon
315           xmin = MIN(qsurf(i, nsrf), xmin)
316           xmax = MAX(qsurf(i, nsrf), xmax)
317        ENDDO
318        PRINT*, 'Humidite pres du sol QS**:', nsrf, xmin, xmax
319     ENDDO
320  ELSE
321     PRINT*, 'phyetat0: Le champ <QS> est present'
322     PRINT*, '          J ignore donc les autres humidites QS**'
323     xmin = 1.0E+20
324     xmax = -1.0E+20
325     DO i = 1, klon
326        xmin = MIN(qsurf(i, 1), xmin)
327        xmax = MAX(qsurf(i, 1), xmax)
328     ENDDO
329     PRINT*, 'Humidite pres du sol <QS>', xmin, xmax
330     DO nsrf = 2, nbsrf
331        DO i = 1, klon
332           qsurf(i, nsrf) = qsurf(i, 1)
333        ENDDO
334     ENDDO
335  ENDIF
336
337  ! Eau dans le sol (pour le modele de sol "bucket")
338
339  CALL get_field("QSOL", qsol, found)
340  IF (.NOT. found) THEN
341     PRINT*, 'phyetat0: Le champ <QSOL> est absent'
342     PRINT*, '          Valeur par defaut nulle'
343     qsol(:)=0.
344  ENDIF
345
346  xmin = 1.0E+20
347  xmax = -1.0E+20
348  DO i = 1, klon
349     xmin = MIN(qsol(i), xmin)
350     xmax = MAX(qsol(i), xmax)
351  ENDDO
352  PRINT*, 'Eau dans le sol (mm) <QSOL>', xmin, xmax
353
354  ! Lecture de neige au sol:
355
356  CALL get_field("SNOW", snow(:, 1), found)
357  IF (.NOT. found) THEN
358     PRINT*, 'phyetat0: Le champ <SNOW> est absent'
359     PRINT*, '          Mais je vais essayer de lire SNOW**'
360     DO nsrf = 1, nbsrf
361        IF (nsrf.GT.99) THEN
362           PRINT*, "Trop de sous-mailles"
363           call abort_gcm("phyetat0", "", 1)
364        ENDIF
365        WRITE(str2, '(i2.2)') nsrf
366        CALL get_field( "SNOW"//str2, snow(:, nsrf))
367        xmin = 1.0E+20
368        xmax = -1.0E+20
369        DO i = 1, klon
370           xmin = MIN(snow(i, nsrf), xmin)
371           xmax = MAX(snow(i, nsrf), xmax)
372        ENDDO
373        PRINT*, 'Neige du sol SNOW**:', nsrf, xmin, xmax
374     ENDDO
375  ELSE
376     PRINT*, 'phyetat0: Le champ <SNOW> est present'
377     PRINT*, '          J ignore donc les autres neiges SNOW**'
378     xmin = 1.0E+20
379     xmax = -1.0E+20
380     DO i = 1, klon
381        xmin = MIN(snow(i, 1), xmin)
382        xmax = MAX(snow(i, 1), xmax)
383     ENDDO
384     PRINT*, 'Neige du sol <SNOW>', xmin, xmax
385     DO nsrf = 2, nbsrf
386        DO i = 1, klon
387           snow(i, nsrf) = snow(i, 1)
388        ENDDO
389     ENDDO
390  ENDIF
391
392  ! Lecture de albedo de l'interval visible au sol:
393
394  CALL get_field("ALBE", falb1(:, 1), found)
395  IF (.NOT. found) THEN
396     PRINT*, 'phyetat0: Le champ <ALBE> est absent'
397     PRINT*, '          Mais je vais essayer de lire ALBE**'
398     DO nsrf = 1, nbsrf
399        IF (nsrf.GT.99) THEN
400           PRINT*, "Trop de sous-mailles"
401           call abort_gcm("phyetat0", "", 1)
402        ENDIF
403        WRITE(str2, '(i2.2)') nsrf
404        CALL get_field("ALBE"//str2, falb1(:, nsrf))
405        xmin = 1.0E+20
406        xmax = -1.0E+20
407        DO i = 1, klon
408           xmin = MIN(falb1(i, nsrf), xmin)
409           xmax = MAX(falb1(i, nsrf), xmax)
410        ENDDO
411        PRINT*, 'Albedo du sol ALBE**:', nsrf, xmin, xmax
412     ENDDO
413  ELSE
414     PRINT*, 'phyetat0: Le champ <ALBE> est present'
415     PRINT*, '          J ignore donc les autres ALBE**'
416     xmin = 1.0E+20
417     xmax = -1.0E+20
418     DO i = 1, klon
419        xmin = MIN(falb1(i, 1), xmin)
420        xmax = MAX(falb1(i, 1), xmax)
421     ENDDO
422     PRINT*, 'Neige du sol <ALBE>', xmin, xmax
423     DO nsrf = 2, nbsrf
424        DO i = 1, klon
425           falb1(i, nsrf) = falb1(i, 1)
426        ENDDO
427     ENDDO
428  ENDIF
429
430  ! Lecture de albedo au sol dans l'interval proche infra-rouge:
431
432  CALL get_field("ALBLW", falb2(:, 1), found)
433  IF (.NOT. found) THEN
434     PRINT*, 'phyetat0: Le champ <ALBLW> est absent'
435     PRINT*, '          Mais je vais prendre ALBE**'
436     DO nsrf = 1, nbsrf
437        DO i = 1, klon
438           falb2(i, nsrf) = falb1(i, nsrf)
439        ENDDO
440     ENDDO
441  ELSE
442     PRINT*, 'phyetat0: Le champ <ALBLW> est present'
443     PRINT*, '          J ignore donc les autres ALBLW**'
444     xmin = 1.0E+20
445     xmax = -1.0E+20
446     DO i = 1, klon
447        xmin = MIN(falb2(i, 1), xmin)
448        xmax = MAX(falb2(i, 1), xmax)
449     ENDDO
450     PRINT*, 'Neige du sol <ALBLW>', xmin, xmax
451     DO nsrf = 2, nbsrf
452        DO i = 1, klon
453           falb2(i, nsrf) = falb2(i, 1)
454        ENDDO
455     ENDDO
456  ENDIF
457
458  ! Lecture de evaporation: 
459
460  CALL get_field("EVAP", evap(:, 1), found)
461  IF (.NOT. found) THEN
462     PRINT*, 'phyetat0: Le champ <EVAP> est absent'
463     PRINT*, '          Mais je vais essayer de lire EVAP**'
464     DO nsrf = 1, nbsrf
465        IF (nsrf.GT.99) THEN
466           PRINT*, "Trop de sous-mailles"
467           call abort_gcm("phyetat0", "", 1)
468        ENDIF
469        WRITE(str2, '(i2.2)') nsrf
470        CALL get_field("EVAP"//str2, evap(:, nsrf))
471        xmin = 1.0E+20
472        xmax = -1.0E+20
473        DO i = 1, klon
474           xmin = MIN(evap(i, nsrf), xmin)
475           xmax = MAX(evap(i, nsrf), xmax)
476        ENDDO
477        PRINT*, 'evap du sol EVAP**:', nsrf, xmin, xmax
478     ENDDO
479  ELSE
480     PRINT*, 'phyetat0: Le champ <EVAP> est present'
481     PRINT*, '          J ignore donc les autres EVAP**'
482     xmin = 1.0E+20
483     xmax = -1.0E+20
484     DO i = 1, klon
485        xmin = MIN(evap(i, 1), xmin)
486        xmax = MAX(evap(i, 1), xmax)
487     ENDDO
488     PRINT*, 'Evap du sol <EVAP>', xmin, xmax
489     DO nsrf = 2, nbsrf
490        DO i = 1, klon
491           evap(i, nsrf) = evap(i, 1)
492        ENDDO
493     ENDDO
494  ENDIF
495
496  ! Lecture precipitation liquide:
497
498  CALL get_field("rain_f", rain_fall)
499  xmin = 1.0E+20
500  xmax = -1.0E+20
501  DO i = 1, klon
502     xmin = MIN(rain_fall(i), xmin)
503     xmax = MAX(rain_fall(i), xmax)
504  ENDDO
505  PRINT*, 'Precipitation liquide rain_f:', xmin, xmax
506
507  ! Lecture precipitation solide:
508
509  CALL get_field("snow_f", snow_fall)
510  xmin = 1.0E+20
511  xmax = -1.0E+20
512  DO i = 1, klon
513     xmin = MIN(snow_fall(i), xmin)
514     xmax = MAX(snow_fall(i), xmax)
515  ENDDO
516  PRINT*, 'Precipitation solide snow_f:', xmin, xmax
517
518  ! Lecture rayonnement solaire au sol:
519
520  CALL get_field("solsw", solsw, found)
521  IF (.NOT. found) THEN
522     PRINT*, 'phyetat0: Le champ <solsw> est absent'
523     PRINT*, 'mis a zero'
524     solsw(:) = 0.
525  ENDIF
526  xmin = 1.0E+20
527  xmax = -1.0E+20
528  DO i = 1, klon
529     xmin = MIN(solsw(i), xmin)
530     xmax = MAX(solsw(i), xmax)
531  ENDDO
532  PRINT*, 'Rayonnement solaire au sol solsw:', xmin, xmax
533
534  ! Lecture rayonnement IF au sol:
535
536  CALL get_field("sollw", sollw, found)
537  IF (.NOT. found) THEN
538     PRINT*, 'phyetat0: Le champ <sollw> est absent'
539     PRINT*, 'mis a zero'
540     sollw = 0.
541  ENDIF
542  xmin = 1.0E+20
543  xmax = -1.0E+20
544  DO i = 1, klon
545     xmin = MIN(sollw(i), xmin)
546     xmax = MAX(sollw(i), xmax)
547  ENDDO
548  PRINT*, 'Rayonnement IF au sol sollw:', xmin, xmax
549
550  CALL get_field("sollwdown", sollwdown, found)
551  IF (.NOT. found) THEN
552     PRINT*, 'phyetat0: Le champ <sollwdown> est absent'
553     PRINT*, 'mis a zero'
554     sollwdown = 0.
555     zts=0.
556     do nsrf=1,nbsrf
557        zts(:)=zts(:)+ftsol(:,nsrf)*pctsrf(:,nsrf)
558     enddo
559     sollwdown(:)=sollw(:)+RSIGMA*zts(:)**4
560  ENDIF
561!  print*,'TS SOLL',zts(klon/2),sollw(klon/2),sollwdown(klon/2)
562  xmin = 1.0E+20
563  xmax = -1.0E+20
564  DO i = 1, klon
565     xmin = MIN(sollwdown(i), xmin)
566     xmax = MAX(sollwdown(i), xmax)
567  ENDDO
568  PRINT*, 'Rayonnement IF au sol sollwdown:', xmin, xmax
569
570
571  ! Lecture derive des flux:
572
573  CALL get_field("fder", fder, found)
574  IF (.NOT. found) THEN
575     PRINT*, 'phyetat0: Le champ <fder> est absent'
576     PRINT*, 'mis a zero'
577     fder = 0.
578  ENDIF
579  xmin = 1.0E+20
580  xmax = -1.0E+20
581  DO i = 1, klon
582     xmin = MIN(fder(i), xmin)
583     xmax = MAX(fder(i), xmax)
584  ENDDO
585  PRINT*, 'Derive des flux fder:', xmin, xmax
586
587  ! Lecture du rayonnement net au sol:
588
589  CALL get_field("RADS", radsol)
590  xmin = 1.0E+20
591  xmax = -1.0E+20
592  DO i = 1, klon
593     xmin = MIN(radsol(i), xmin)
594     xmax = MAX(radsol(i), xmax)
595  ENDDO
596  PRINT*, 'Rayonnement net au sol radsol:', xmin, xmax
597
598  ! Lecture de la longueur de rugosite
599
600  CALL get_field("RUG", frugs(:, 1), found)
601  IF (.NOT. found) THEN
602     PRINT*, 'phyetat0: Le champ <RUG> est absent'
603     PRINT*, '          Mais je vais essayer de lire RUG**'
604     DO nsrf = 1, nbsrf
605        IF (nsrf.GT.99) THEN
606           PRINT*, "Trop de sous-mailles"
607           call abort_gcm("phyetat0", "", 1)
608        ENDIF
609        WRITE(str2, '(i2.2)') nsrf
610        CALL get_field("RUG"//str2, frugs(:, nsrf))
611        xmin = 1.0E+20
612        xmax = -1.0E+20
613        DO i = 1, klon
614           xmin = MIN(frugs(i, nsrf), xmin)
615           xmax = MAX(frugs(i, nsrf), xmax)
616        ENDDO
617        PRINT*, 'rugosite du sol RUG**:', nsrf, xmin, xmax
618     ENDDO
619  ELSE
620     PRINT*, 'phyetat0: Le champ <RUG> est present'
621     PRINT*, '          J ignore donc les autres RUG**'
622     xmin = 1.0E+20
623     xmax = -1.0E+20
624     DO i = 1, klon
625        xmin = MIN(frugs(i, 1), xmin)
626        xmax = MAX(frugs(i, 1), xmax)
627     ENDDO
628     PRINT*, 'rugosite <RUG>', xmin, xmax
629     DO nsrf = 2, nbsrf
630        DO i = 1, klon
631           frugs(i, nsrf) = frugs(i, 1)
632        ENDDO
633     ENDDO
634  ENDIF
635
636  ! Lecture de l'age de la neige:
637
638  CALL get_field("AGESNO", agesno(:, 1), found)
639  IF (.NOT. found) THEN
640     PRINT*, 'phyetat0: Le champ <AGESNO> est absent'
641     PRINT*, '          Mais je vais essayer de lire AGESNO**'
642     DO nsrf = 1, nbsrf
643        IF (nsrf.GT.99) THEN
644           PRINT*, "Trop de sous-mailles"
645           call abort_gcm("phyetat0", "", 1)
646        ENDIF
647        WRITE(str2, '(i2.2)') nsrf
648        CALL get_field("AGESNO"//str2, agesno(:, nsrf), found)
649        IF (.NOT. found) THEN
650           PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
651           agesno = 50.0
652        ENDIF
653        xmin = 1.0E+20
654        xmax = -1.0E+20
655        DO i = 1, klon
656           xmin = MIN(agesno(i, nsrf), xmin)
657           xmax = MAX(agesno(i, nsrf), xmax)
658        ENDDO
659        PRINT*, 'Age de la neige AGESNO**:', nsrf, xmin, xmax
660     ENDDO
661  ELSE
662     PRINT*, 'phyetat0: Le champ <AGESNO> est present'
663     PRINT*, '          J ignore donc les autres AGESNO**'
664     xmin = 1.0E+20
665     xmax = -1.0E+20
666     DO i = 1, klon
667        xmin = MIN(agesno(i, 1), xmin)
668        xmax = MAX(agesno(i, 1), xmax)
669     ENDDO
670     PRINT*, 'Age de la neige <AGESNO>', xmin, xmax
671     DO nsrf = 2, nbsrf
672        DO i = 1, klon
673           agesno(i, nsrf) = agesno(i, 1)
674        ENDDO
675     ENDDO
676  ENDIF
677
678  CALL get_field("ZMEA", zmea)
679  xmin = 1.0E+20
680  xmax = -1.0E+20
681  DO i = 1, klon
682     xmin = MIN(zmea(i), xmin)
683     xmax = MAX(zmea(i), xmax)
684  ENDDO
685  PRINT*, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
686
687  CALL get_field("ZSTD", zstd)
688  xmin = 1.0E+20
689  xmax = -1.0E+20
690  DO i = 1, klon
691     xmin = MIN(zstd(i), xmin)
692     xmax = MAX(zstd(i), xmax)
693  ENDDO
694  PRINT*, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
695
696  CALL get_field("ZSIG", zsig)
697  xmin = 1.0E+20
698  xmax = -1.0E+20
699  DO i = 1, klon
700     xmin = MIN(zsig(i), xmin)
701     xmax = MAX(zsig(i), xmax)
702  ENDDO
703  PRINT*, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
704
705  CALL get_field("ZGAM", zgam)
706  xmin = 1.0E+20
707  xmax = -1.0E+20
708  DO i = 1, klon
709     xmin = MIN(zgam(i), xmin)
710     xmax = MAX(zgam(i), xmax)
711  ENDDO
712  PRINT*, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
713
714  CALL get_field("ZTHE", zthe)
715  xmin = 1.0E+20
716  xmax = -1.0E+20
717  DO i = 1, klon
718     xmin = MIN(zthe(i), xmin)
719     xmax = MAX(zthe(i), xmax)
720  ENDDO
721  PRINT*, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
722
723  CALL get_field("ZPIC", zpic)
724  xmin = 1.0E+20
725  xmax = -1.0E+20
726  DO i = 1, klon
727     xmin = MIN(zpic(i), xmin)
728     xmax = MAX(zpic(i), xmax)
729  ENDDO
730  PRINT*, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
731
732  CALL get_field("ZVAL", zval)
733  xmin = 1.0E+20
734  xmax = -1.0E+20
735  DO i = 1, klon
736     xmin = MIN(zval(i), xmin)
737     xmax = MAX(zval(i), xmax)
738  ENDDO
739  PRINT*, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
740
741  CALL get_field("RUGSREL", rugoro)
742  xmin = 1.0E+20
743  xmax = -1.0E+20
744  DO i = 1, klon
745     xmin = MIN(rugoro(i), xmin)
746     xmax = MAX(rugoro(i), xmax)
747  ENDDO
748  PRINT*, 'Rugosite relief (ecart-type) rugsrel:', xmin, xmax
749
750  ancien_ok = .TRUE.
751
752  CALL get_field("TANCIEN", t_ancien, found)
753  IF (.NOT. found) THEN
754     PRINT*, "phyetat0: Le champ <TANCIEN> est absent"
755     PRINT*, "Depart legerement fausse. Mais je continue"
756     ancien_ok = .FALSE.
757  ENDIF
758
759  CALL get_field("QANCIEN", q_ancien, found)
760  IF (.NOT. found) THEN
761     PRINT*, "phyetat0: Le champ <QANCIEN> est absent"
762     PRINT*, "Depart legerement fausse. Mais je continue"
763     ancien_ok = .FALSE.
764  ENDIF
765
766  CALL get_field("UANCIEN", u_ancien, found)
767  IF (.NOT. found) THEN
768     PRINT*, "phyetat0: Le champ <UANCIEN> est absent"
769     PRINT*, "Depart legerement fausse. Mais je continue"
770     ancien_ok = .FALSE.
771  ENDIF
772
773  CALL get_field("VANCIEN", v_ancien, found)
774  IF (.NOT. found) THEN
775     PRINT*, "phyetat0: Le champ <VANCIEN> est absent"
776     PRINT*, "Depart legerement fausse. Mais je continue"
777     ancien_ok = .FALSE.
778  ENDIF
779
780  clwcon=0.
781  CALL get_field("CLWCON", clwcon, found)
782  IF (.NOT. found) THEN
783     PRINT*, "phyetat0: Le champ CLWCON est absent"
784     PRINT*, "Depart legerement fausse. Mais je continue"
785  ENDIF
786  xmin = 1.0E+20
787  xmax = -1.0E+20
788  xmin = MINval(clwcon)
789  xmax = MAXval(clwcon)
790  PRINT*, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
791
792  rnebcon = 0.
793  CALL get_field("RNEBCON", rnebcon, found)
794  IF (.NOT. found) THEN
795     PRINT*, "phyetat0: Le champ RNEBCON est absent"
796     PRINT*, "Depart legerement fausse. Mais je continue"
797  ENDIF
798  xmin = 1.0E+20
799  xmax = -1.0E+20
800  xmin = MINval(rnebcon)
801  xmax = MAXval(rnebcon)
802  PRINT*, 'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
803
804  ! Lecture ratqs
805
806  ratqs=0.
807  CALL get_field("RATQS", ratqs, found)
808  IF (.NOT. found) THEN
809     PRINT*, "phyetat0: Le champ <RATQS> est absent"
810     PRINT*, "Depart legerement fausse. Mais je continue"
811  ENDIF
812  xmin = 1.0E+20
813  xmax = -1.0E+20
814  xmin = MINval(ratqs)
815  xmax = MAXval(ratqs)
816  PRINT*, '(ecart-type) ratqs:', xmin, xmax
817
818  ! Lecture run_off_lic_0
819
820  CALL get_field("RUNOFFLIC0", run_off_lic_0, found)
821  IF (.NOT. found) THEN
822     PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"
823     PRINT*, "Depart legerement fausse. Mais je continue"
824     run_off_lic_0 = 0.
825  ENDIF
826  xmin = 1.0E+20
827  xmax = -1.0E+20
828  xmin = MINval(run_off_lic_0)
829  xmax = MAXval(run_off_lic_0)
830  PRINT*, '(ecart-type) run_off_lic_0:', xmin, xmax
831
832  ! Lecture de l'energie cinetique turbulente
833
834  IF (iflag_pbl>1) then
835     DO nsrf = 1, nbsrf
836        IF (nsrf.GT.99) THEN
837           PRINT*, "Trop de sous-mailles"
838           call abort_gcm("phyetat0", "", 1)
839        ENDIF
840        WRITE(str2, '(i2.2)') nsrf
841        CALL get_field("TKE"//str2, pbl_tke(:, 1:klev+1, nsrf), found)
842        IF (.NOT. found) THEN
843           PRINT*, "phyetat0: <TKE"//str2//"> est absent"
844           pbl_tke(:, :, nsrf)=1.e-8
845        ENDIF
846        xmin = 1.0E+20
847        xmax = -1.0E+20
848        DO k = 1, klev+1
849           DO i = 1, klon
850              xmin = MIN(pbl_tke(i, k, nsrf), xmin)
851              xmax = MAX(pbl_tke(i, k, nsrf), xmax)
852           ENDDO
853        ENDDO
854        PRINT*, 'Turbulent kinetic energyl TKE**:', nsrf, xmin, xmax
855     ENDDO
856  ENDIF
857
858! Lecture de l'ecart de TKE (w) - (x)
859!
860  IF (iflag_pbl>1 .AND. iflag_wake>=1  &
861           .AND. iflag_pbl_split >=1 ) then
862    DO nsrf = 1, nbsrf
863      IF (nsrf.GT.99) THEN
864        PRINT*, "Trop de sous-mailles"
865        call abort_gcm("phyetat0", "", 1)
866      ENDIF
867      WRITE(str2,'(i2.2)') nsrf
868      CALL get_field("DELTATKE"//str2, &
869                    wake_delta_pbl_tke(:,1:klev+1,nsrf),found)
870      IF (.NOT. found) THEN
871        PRINT*, "phyetat0: <DELTATKE"//str2//"> est absent"
872        wake_delta_pbl_tke(:,:,nsrf)=0.
873      ENDIF
874      xmin = 1.0E+20
875      xmax = -1.0E+20
876      DO k = 1, klev+1
877        DO i = 1, klon
878          xmin = MIN(wake_delta_pbl_tke(i,k,nsrf),xmin)
879          xmax = MAX(wake_delta_pbl_tke(i,k,nsrf),xmax)
880        ENDDO
881      ENDDO
882      PRINT*,'TKE difference (w)-(x) DELTATKE**:', nsrf, xmin, xmax
883    ENDDO
884
885  ! delta_tsurf
886
887    DO nsrf = 1, nbsrf
888       IF (nsrf.GT.99) THEN
889         PRINT*, "Trop de sous-mailles"
890         call abort_gcm("phyetat0", "", 1)
891       ENDIF
892       WRITE(str2,'(i2.2)') nsrf
893     CALL get_field("DELTA_TSURF"//str2, delta_tsurf(:,nsrf), found)
894     IF (.NOT. found) THEN
895        PRINT*, "phyetat0: Le champ <DELTA_TSURF"//str2//"> est absent"
896        PRINT*, "Depart legerement fausse. Mais je continue"
897        delta_tsurf(:,nsrf)=0.
898     ELSE
899        xmin = 1.0E+20
900        xmax = -1.0E+20
901         DO i = 1, klon
902            xmin = MIN(delta_tsurf(i, nsrf), xmin)
903            xmax = MAX(delta_tsurf(i, nsrf), xmax)
904         ENDDO
905        PRINT*, 'delta_tsurf:', xmin, xmax
906     ENDIF
907    ENDDO  ! nsrf = 1, nbsrf
908  ENDIF   !(iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 )
909
910  ! zmax0
911  CALL get_field("ZMAX0", zmax0, found)
912  IF (.NOT. found) THEN
913     PRINT*, "phyetat0: Le champ <ZMAX0> est absent"
914     PRINT*, "Depart legerement fausse. Mais je continue"
915     zmax0=40.
916  ENDIF
917  xmin = 1.0E+20
918  xmax = -1.0E+20
919  xmin = MINval(zmax0)
920  xmax = MAXval(zmax0)
921  PRINT*, '(ecart-type) zmax0:', xmin, xmax
922
923  !           f0(ig)=1.e-5
924  ! f0
925  CALL get_field("F0", f0, found)
926  IF (.NOT. found) THEN
927     PRINT*, "phyetat0: Le champ <f0> est absent"
928     PRINT*, "Depart legerement fausse. Mais je continue"
929     f0=1.e-5
930  ENDIF
931  xmin = 1.0E+20
932  xmax = -1.0E+20
933  xmin = MINval(f0)
934  xmax = MAXval(f0)
935  PRINT*, '(ecart-type) f0:', xmin, xmax
936
937  ! sig1 or ema_work1
938
939  CALL get_field("sig1", sig1, found)
940  IF (.NOT. found) CALL get_field("EMA_WORK1", sig1, found)
941  IF (.NOT. found) THEN
942     PRINT*, "phyetat0: Le champ sig1 est absent"
943     PRINT*, "Depart legerement fausse. Mais je continue"
944     sig1=0.
945  ELSE
946     xmin = 1.0E+20
947     xmax = -1.0E+20
948     DO k = 1, klev
949        DO i = 1, klon
950           xmin = MIN(sig1(i, k), xmin)
951           xmax = MAX(sig1(i, k), xmax)
952        ENDDO
953     ENDDO
954     PRINT*, 'sig1:', xmin, xmax
955  ENDIF
956
957  ! w01 or ema_work2
958
959  CALL get_field("w01", w01, found)
960  IF (.NOT. found) CALL get_field("EMA_WORK2", w01, found)
961  IF (.NOT. found) THEN
962     PRINT*, "phyetat0: Le champ w01 est absent"
963     PRINT*, "Depart legerement fausse. Mais je continue"
964     w01=0.
965  ELSE
966     xmin = 1.0E+20
967     xmax = -1.0E+20
968     DO k = 1, klev
969        DO i = 1, klon
970           xmin = MIN(w01(i, k), xmin)
971           xmax = MAX(w01(i, k), xmax)
972        ENDDO
973     ENDDO
974     PRINT*, 'w01:', xmin, xmax
975  ENDIF
976
977  ! wake_deltat
978
979  CALL get_field("WAKE_DELTAT", wake_deltat, found)
980  IF (.NOT. found) THEN
981     PRINT*, "phyetat0: Le champ <WAKE_DELTAT> est absent"
982     PRINT*, "Depart legerement fausse. Mais je continue"
983     wake_deltat=0.
984  ELSE
985     xmin = 1.0E+20
986     xmax = -1.0E+20
987     DO k = 1, klev
988        DO i = 1, klon
989           xmin = MIN(wake_deltat(i, k), xmin)
990           xmax = MAX(wake_deltat(i, k), xmax)
991        ENDDO
992     ENDDO
993     PRINT*, 'wake_deltat:', xmin, xmax
994  ENDIF
995
996  ! wake_deltaq
997
998  CALL get_field("WAKE_DELTAQ", wake_deltaq, found)
999  IF (.NOT. found) THEN
1000     PRINT*, "phyetat0: Le champ <WAKE_DELTAQ> est absent"
1001     PRINT*, "Depart legerement fausse. Mais je continue"
1002     wake_deltaq=0.
1003  ELSE
1004     xmin = 1.0E+20
1005     xmax = -1.0E+20
1006     DO k = 1, klev
1007        DO i = 1, klon
1008           xmin = MIN(wake_deltaq(i, k), xmin)
1009           xmax = MAX(wake_deltaq(i, k), xmax)
1010        ENDDO
1011     ENDDO
1012     PRINT*, 'wake_deltaq:', xmin, xmax
1013  ENDIF
1014
1015  ! wake_s
1016
1017  CALL get_field("WAKE_S", wake_s, found)
1018  IF (.NOT. found) THEN
1019     PRINT*, "phyetat0: Le champ <WAKE_S> est absent"
1020     PRINT*, "Depart legerement fausse. Mais je continue"
1021     wake_s=0.
1022  ENDIF
1023  xmin = 1.0E+20
1024  xmax = -1.0E+20
1025  xmin = MINval(wake_s)
1026  xmax = MAXval(wake_s)
1027  PRINT*, '(ecart-type) wake_s:', xmin, xmax
1028
1029  ! wake_cstar
1030
1031  CALL get_field("WAKE_CSTAR", wake_cstar, found)
1032  IF (.NOT. found) THEN
1033     PRINT*, "phyetat0: Le champ <WAKE_CSTAR> est absent"
1034     PRINT*, "Depart legerement fausse. Mais je continue"
1035     wake_cstar=0.
1036  ENDIF
1037  xmin = 1.0E+20
1038  xmax = -1.0E+20
1039  xmin = MINval(wake_cstar)
1040  xmax = MAXval(wake_cstar)
1041  PRINT*, '(ecart-type) wake_cstar:', xmin, xmax
1042
1043  ! wake_pe
1044
1045  CALL get_field("WAKE_PE", wake_pe, found)
1046  IF (.NOT. found) THEN
1047     PRINT*, "phyetat0: Le champ <WAKE_PE> est absent"
1048     PRINT*, "Depart legerement fausse. Mais je continue"
1049     wake_pe=0.
1050  ENDIF
1051  xmin = 1.0E+20
1052  xmax = -1.0E+20
1053  xmin = MINval(wake_pe)
1054  xmax = MAXval(wake_pe)
1055  PRINT*, '(ecart-type) wake_pe:', xmin, xmax
1056
1057  ! wake_fip
1058
1059  CALL get_field("WAKE_FIP", wake_fip, found)
1060  IF (.NOT. found) THEN
1061     PRINT*, "phyetat0: Le champ <WAKE_FIP> est absent"
1062     PRINT*, "Depart legerement fausse. Mais je continue"
1063     wake_fip=0.
1064  ENDIF
1065  xmin = 1.0E+20
1066  xmax = -1.0E+20
1067  xmin = MINval(wake_fip)
1068  xmax = MAXval(wake_fip)
1069  PRINT*, '(ecart-type) wake_fip:', xmin, xmax
1070
1071  !  thermiques
1072
1073  CALL get_field("FM_THERM", fm_therm, found)
1074  IF (.NOT. found) THEN
1075     PRINT*, "phyetat0: Le champ <fm_therm> est absent"
1076     PRINT*, "Depart legerement fausse. Mais je continue"
1077     fm_therm=0.
1078  ENDIF
1079  xmin = 1.0E+20
1080  xmax = -1.0E+20
1081  xmin = MINval(fm_therm)
1082  xmax = MAXval(fm_therm)
1083  PRINT*, '(ecart-type) fm_therm:', xmin, xmax
1084
1085  CALL get_field("ENTR_THERM", entr_therm, found)
1086  IF (.NOT. found) THEN
1087     PRINT*, "phyetat0: Le champ <entr_therm> est absent"
1088     PRINT*, "Depart legerement fausse. Mais je continue"
1089     entr_therm=0.
1090  ENDIF
1091  xmin = 1.0E+20
1092  xmax = -1.0E+20
1093  xmin = MINval(entr_therm)
1094  xmax = MAXval(entr_therm)
1095  PRINT*, '(ecart-type) entr_therm:', xmin, xmax
1096
1097  CALL get_field("DETR_THERM", detr_therm, found)
1098  IF (.NOT. found) THEN
1099     PRINT*, "phyetat0: Le champ <detr_therm> est absent"
1100     PRINT*, "Depart legerement fausse. Mais je continue"
1101     detr_therm=0.
1102  ENDIF
1103  xmin = 1.0E+20
1104  xmax = -1.0E+20
1105  xmin = MINval(detr_therm)
1106  xmax = MAXval(detr_therm)
1107  PRINT*, '(ecart-type) detr_therm:', xmin, xmax
1108
1109  CALL get_field("ALE_BL", ale_bl, found)
1110  IF (.NOT. found) THEN
1111     PRINT*, "phyetat0: Le champ <ale_bl> est absent"
1112     PRINT*, "Depart legerement fausse. Mais je continue"
1113     ale_bl=0.
1114  ENDIF
1115  xmin = 1.0E+20
1116  xmax = -1.0E+20
1117  xmin = MINval(ale_bl)
1118  xmax = MAXval(ale_bl)
1119  PRINT*, '(ecart-type) ale_bl:', xmin, xmax
1120
1121  CALL get_field("ALE_BL_TRIG", ale_bl_trig, found)
1122  IF (.NOT. found) THEN
1123     PRINT*, "phyetat0: Le champ <ale_bl_trig> est absent"
1124     PRINT*, "Depart legerement fausse. Mais je continue"
1125     ale_bl_trig=0.
1126  ENDIF
1127  xmin = 1.0E+20
1128  xmax = -1.0E+20
1129  xmin = MINval(ale_bl_trig)
1130  xmax = MAXval(ale_bl_trig)
1131  PRINT*, '(ecart-type) ale_bl_trig:', xmin, xmax
1132
1133  CALL get_field("ALP_BL", alp_bl, found)
1134  IF (.NOT. found) THEN
1135     PRINT*, "phyetat0: Le champ <alp_bl> est absent"
1136     PRINT*, "Depart legerement fausse. Mais je continue"
1137     alp_bl=0.
1138  ENDIF
1139  xmin = 1.0E+20
1140  xmax = -1.0E+20
1141  xmin = MINval(alp_bl)
1142  xmax = MAXval(alp_bl)
1143  PRINT*, '(ecart-type) alp_bl:', xmin, xmax
1144
1145  ! Read and send field trs to traclmdz
1146
1147  IF (type_trac == 'lmdz') THEN
1148     DO it=1, nbtr
1149        iiq=niadv(it+2)
1150        CALL get_field("trs_"//tname(iiq), trs(:, it), found)
1151        IF (.NOT. found) THEN
1152           PRINT*,  &
1153                "phyetat0: Le champ <trs_"//tname(iiq)//"> est absent"
1154           PRINT*, "Depart legerement fausse. Mais je continue"
1155           trs(:, it) = 0.
1156        ENDIF
1157        xmin = 1.0E+20
1158        xmax = -1.0E+20
1159        xmin = MINval(trs(:, it))
1160        xmax = MAXval(trs(:, it))
1161        PRINT*, "(ecart-type) trs_"//tname(iiq)//" :", xmin, xmax
1162
1163     END DO
1164     CALL traclmdz_from_restart(trs)
1165
1166     IF (carbon_cycle_cpl) THEN
1167        ALLOCATE(co2_send(klon), stat=ierr)
1168        IF (ierr /= 0) CALL abort_gcm &
1169             ('phyetat0', 'pb allocation co2_send', 1)
1170        CALL get_field("co2_send", co2_send, found)
1171        IF (.NOT. found) THEN
1172           PRINT*, "phyetat0: Le champ <co2_send> est absent"
1173           PRINT*, "Initialisation uniforme a co2_ppm=", co2_ppm
1174           co2_send(:) = co2_ppm
1175        END IF
1176     END IF
1177  END IF
1178
1179  if (ok_gwd_rando) then
1180     call get_field("du_gwd_rando", du_gwd_rando, found)
1181     if (.not. found) then
1182        print *, "du_gwd_rando not found, setting it to 0."
1183        du_gwd_rando = 0.
1184     end if
1185
1186     call get_field("dv_gwd_rando", dv_gwd_rando, found)
1187     if (.not. found) then
1188        print *, "dv_gwd_rando not found, setting it to 0."
1189        dv_gwd_rando = 0.
1190     end if
1191  end if
1192
1193  ! Initialize Slab variables
1194  IF ( type_ocean == 'slab' ) THEN
1195      print*, "calling slab_init"
1196      CALL ocean_slab_init(dtime, pctsrf)
1197      ! tslab
1198      CALL get_field("tslab", tslab, found)
1199      IF (.NOT. found) THEN
1200          PRINT*, "phyetat0: Le champ <tslab> est absent"
1201          PRINT*, "Initialisation a tsol_oce"
1202          DO i=1,nslay
1203              tslab(:,i)=MAX(ftsol(:,is_oce),271.35)
1204          END DO
1205      END IF
1206      ! Sea ice variables
1207      IF (version_ocean == 'sicINT') THEN
1208          CALL get_field("slab_tice", tice, found)
1209          IF (.NOT. found) THEN
1210              PRINT*, "phyetat0: Le champ <tice> est absent"
1211              PRINT*, "Initialisation a tsol_sic"
1212                  tice(:)=ftsol(:,is_sic)
1213          END IF
1214          CALL get_field("seaice", seaice, found)
1215          IF (.NOT. found) THEN
1216              PRINT*, "phyetat0: Le champ <seaice> est absent"
1217              PRINT*, "Initialisation a 0/1m suivant fraction glace"
1218              seaice(:)=0.
1219              WHERE (pctsrf(:,is_sic).GT.EPSFRA)
1220                  seaice=917.
1221              END WHERE
1222          END IF
1223      END IF !sea ice INT
1224  END IF ! Slab       
1225
1226  ! on ferme le fichier
1227  CALL close_startphy
1228
1229  ! Initialize module pbl_surface_mod
1230
1231  CALL pbl_surface_init(qsol, fder, snow, qsurf, &
1232       evap, frugs, agesno, tsoil)
1233
1234  ! Initialize module ocean_cpl_mod for the case of coupled ocean
1235  IF ( type_ocean == 'couple' ) THEN
1236     CALL ocean_cpl_init(dtime, rlon, rlat)
1237  ENDIF
1238
1239  CALL init_iophy_new(rlat, rlon)
1240
1241  ! Initilialize module fonte_neige_mod     
1242  CALL fonte_neige_init(run_off_lic_0)
1243
1244END SUBROUTINE phyetat0
Note: See TracBrowser for help on using the repository browser.