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

Last change on this file since 2209 was 2209, checked in by Ehouarn Millour, 9 years ago

Update of the slab ocean by Francis Codron. There are now 3 possibilities for the "version_ocean" slab type:
sicOBS = prescribed ice fraction. Water temperature nearby is set to -1.8°C and cannot become lower.
sicNO = ignore sea ice. One can prescribe a fraction, but the nearby ocean evolves freely, depending on surface fluxes: temperature can go below freezing point or above...
sicINT = interactive sea ice.
EM

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