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

Last change on this file since 2174 was 2159, checked in by jyg, 10 years ago

1/ Splitting of the boundary layer : the climbing down and up of Pbl_surface is
split between the off-wake and wake regions ; the thermal scheme is applied
only to the off-wake region.
2/ Elimination of wake_scal and calwake_scal.

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