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

Last change on this file since 2242 was 2241, checked in by fhourdin, 9 years ago

Nettoyage des anciens albedo. Elimination de alb1 et alb2
dans pbl_surface (il s'agissait de commentaires) et dans
le etats de démarrage.

Some cleaning of old albedo specification (alb1/alb2)

  • 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.1 KB
Line 
1! $Id: phyetat0.F90 2241 2015-03-23 21:02:32Z 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, 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 evaporation: 
393
394  CALL get_field("EVAP", evap(:, 1), found)
395  IF (.NOT. found) THEN
396     PRINT*, 'phyetat0: Le champ <EVAP> est absent'
397     PRINT*, '          Mais je vais essayer de lire EVAP**'
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("EVAP"//str2, evap(:, nsrf))
405        xmin = 1.0E+20
406        xmax = -1.0E+20
407        DO i = 1, klon
408           xmin = MIN(evap(i, nsrf), xmin)
409           xmax = MAX(evap(i, nsrf), xmax)
410        ENDDO
411        PRINT*, 'evap du sol EVAP**:', nsrf, xmin, xmax
412     ENDDO
413  ELSE
414     PRINT*, 'phyetat0: Le champ <EVAP> est present'
415     PRINT*, '          J ignore donc les autres EVAP**'
416     xmin = 1.0E+20
417     xmax = -1.0E+20
418     DO i = 1, klon
419        xmin = MIN(evap(i, 1), xmin)
420        xmax = MAX(evap(i, 1), xmax)
421     ENDDO
422     PRINT*, 'Evap du sol <EVAP>', xmin, xmax
423     DO nsrf = 2, nbsrf
424        DO i = 1, klon
425           evap(i, nsrf) = evap(i, 1)
426        ENDDO
427     ENDDO
428  ENDIF
429
430  ! Lecture precipitation liquide:
431
432  CALL get_field("rain_f", rain_fall)
433  xmin = 1.0E+20
434  xmax = -1.0E+20
435  DO i = 1, klon
436     xmin = MIN(rain_fall(i), xmin)
437     xmax = MAX(rain_fall(i), xmax)
438  ENDDO
439  PRINT*, 'Precipitation liquide rain_f:', xmin, xmax
440
441  ! Lecture precipitation solide:
442
443  CALL get_field("snow_f", snow_fall)
444  xmin = 1.0E+20
445  xmax = -1.0E+20
446  DO i = 1, klon
447     xmin = MIN(snow_fall(i), xmin)
448     xmax = MAX(snow_fall(i), xmax)
449  ENDDO
450  PRINT*, 'Precipitation solide snow_f:', xmin, xmax
451
452  ! Lecture rayonnement solaire au sol:
453
454  CALL get_field("solsw", solsw, found)
455  IF (.NOT. found) THEN
456     PRINT*, 'phyetat0: Le champ <solsw> est absent'
457     PRINT*, 'mis a zero'
458     solsw(:) = 0.
459  ENDIF
460  xmin = 1.0E+20
461  xmax = -1.0E+20
462  DO i = 1, klon
463     xmin = MIN(solsw(i), xmin)
464     xmax = MAX(solsw(i), xmax)
465  ENDDO
466  PRINT*, 'Rayonnement solaire au sol solsw:', xmin, xmax
467
468  ! Lecture rayonnement IF au sol:
469
470  CALL get_field("sollw", sollw, found)
471  IF (.NOT. found) THEN
472     PRINT*, 'phyetat0: Le champ <sollw> est absent'
473     PRINT*, 'mis a zero'
474     sollw = 0.
475  ENDIF
476  xmin = 1.0E+20
477  xmax = -1.0E+20
478  DO i = 1, klon
479     xmin = MIN(sollw(i), xmin)
480     xmax = MAX(sollw(i), xmax)
481  ENDDO
482  PRINT*, 'Rayonnement IF au sol sollw:', xmin, xmax
483
484  CALL get_field("sollwdown", sollwdown, found)
485  IF (.NOT. found) THEN
486     PRINT*, 'phyetat0: Le champ <sollwdown> est absent'
487     PRINT*, 'mis a zero'
488     sollwdown = 0.
489     zts=0.
490     do nsrf=1,nbsrf
491        zts(:)=zts(:)+ftsol(:,nsrf)*pctsrf(:,nsrf)
492     enddo
493     sollwdown(:)=sollw(:)+RSIGMA*zts(:)**4
494  ENDIF
495!  print*,'TS SOLL',zts(klon/2),sollw(klon/2),sollwdown(klon/2)
496  xmin = 1.0E+20
497  xmax = -1.0E+20
498  DO i = 1, klon
499     xmin = MIN(sollwdown(i), xmin)
500     xmax = MAX(sollwdown(i), xmax)
501  ENDDO
502  PRINT*, 'Rayonnement IF au sol sollwdown:', xmin, xmax
503
504
505  ! Lecture derive des flux:
506
507  CALL get_field("fder", fder, found)
508  IF (.NOT. found) THEN
509     PRINT*, 'phyetat0: Le champ <fder> est absent'
510     PRINT*, 'mis a zero'
511     fder = 0.
512  ENDIF
513  xmin = 1.0E+20
514  xmax = -1.0E+20
515  DO i = 1, klon
516     xmin = MIN(fder(i), xmin)
517     xmax = MAX(fder(i), xmax)
518  ENDDO
519  PRINT*, 'Derive des flux fder:', xmin, xmax
520
521  ! Lecture du rayonnement net au sol:
522
523  CALL get_field("RADS", radsol)
524  xmin = 1.0E+20
525  xmax = -1.0E+20
526  DO i = 1, klon
527     xmin = MIN(radsol(i), xmin)
528     xmax = MAX(radsol(i), xmax)
529  ENDDO
530  PRINT*, 'Rayonnement net au sol radsol:', xmin, xmax
531
532  ! Lecture de la longueur de rugosite
533
534  CALL get_field("RUG", frugs(:, 1), found)
535  IF (.NOT. found) THEN
536     PRINT*, 'phyetat0: Le champ <RUG> est absent'
537     PRINT*, '          Mais je vais essayer de lire RUG**'
538     DO nsrf = 1, nbsrf
539        IF (nsrf.GT.99) THEN
540           PRINT*, "Trop de sous-mailles"
541           call abort_gcm("phyetat0", "", 1)
542        ENDIF
543        WRITE(str2, '(i2.2)') nsrf
544        CALL get_field("RUG"//str2, frugs(:, nsrf))
545        xmin = 1.0E+20
546        xmax = -1.0E+20
547        DO i = 1, klon
548           xmin = MIN(frugs(i, nsrf), xmin)
549           xmax = MAX(frugs(i, nsrf), xmax)
550        ENDDO
551        PRINT*, 'rugosite du sol RUG**:', nsrf, xmin, xmax
552     ENDDO
553  ELSE
554     PRINT*, 'phyetat0: Le champ <RUG> est present'
555     PRINT*, '          J ignore donc les autres RUG**'
556     xmin = 1.0E+20
557     xmax = -1.0E+20
558     DO i = 1, klon
559        xmin = MIN(frugs(i, 1), xmin)
560        xmax = MAX(frugs(i, 1), xmax)
561     ENDDO
562     PRINT*, 'rugosite <RUG>', xmin, xmax
563     DO nsrf = 2, nbsrf
564        DO i = 1, klon
565           frugs(i, nsrf) = frugs(i, 1)
566        ENDDO
567     ENDDO
568  ENDIF
569
570  ! Lecture de l'age de la neige:
571
572  CALL get_field("AGESNO", agesno(:, 1), found)
573  IF (.NOT. found) THEN
574     PRINT*, 'phyetat0: Le champ <AGESNO> est absent'
575     PRINT*, '          Mais je vais essayer de lire AGESNO**'
576     DO nsrf = 1, nbsrf
577        IF (nsrf.GT.99) THEN
578           PRINT*, "Trop de sous-mailles"
579           call abort_gcm("phyetat0", "", 1)
580        ENDIF
581        WRITE(str2, '(i2.2)') nsrf
582        CALL get_field("AGESNO"//str2, agesno(:, nsrf), found)
583        IF (.NOT. found) THEN
584           PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
585           agesno = 50.0
586        ENDIF
587        xmin = 1.0E+20
588        xmax = -1.0E+20
589        DO i = 1, klon
590           xmin = MIN(agesno(i, nsrf), xmin)
591           xmax = MAX(agesno(i, nsrf), xmax)
592        ENDDO
593        PRINT*, 'Age de la neige AGESNO**:', nsrf, xmin, xmax
594     ENDDO
595  ELSE
596     PRINT*, 'phyetat0: Le champ <AGESNO> est present'
597     PRINT*, '          J ignore donc les autres AGESNO**'
598     xmin = 1.0E+20
599     xmax = -1.0E+20
600     DO i = 1, klon
601        xmin = MIN(agesno(i, 1), xmin)
602        xmax = MAX(agesno(i, 1), xmax)
603     ENDDO
604     PRINT*, 'Age de la neige <AGESNO>', xmin, xmax
605     DO nsrf = 2, nbsrf
606        DO i = 1, klon
607           agesno(i, nsrf) = agesno(i, 1)
608        ENDDO
609     ENDDO
610  ENDIF
611
612  CALL get_field("ZMEA", zmea)
613  xmin = 1.0E+20
614  xmax = -1.0E+20
615  DO i = 1, klon
616     xmin = MIN(zmea(i), xmin)
617     xmax = MAX(zmea(i), xmax)
618  ENDDO
619  PRINT*, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
620
621  CALL get_field("ZSTD", zstd)
622  xmin = 1.0E+20
623  xmax = -1.0E+20
624  DO i = 1, klon
625     xmin = MIN(zstd(i), xmin)
626     xmax = MAX(zstd(i), xmax)
627  ENDDO
628  PRINT*, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
629
630  CALL get_field("ZSIG", zsig)
631  xmin = 1.0E+20
632  xmax = -1.0E+20
633  DO i = 1, klon
634     xmin = MIN(zsig(i), xmin)
635     xmax = MAX(zsig(i), xmax)
636  ENDDO
637  PRINT*, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
638
639  CALL get_field("ZGAM", zgam)
640  xmin = 1.0E+20
641  xmax = -1.0E+20
642  DO i = 1, klon
643     xmin = MIN(zgam(i), xmin)
644     xmax = MAX(zgam(i), xmax)
645  ENDDO
646  PRINT*, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
647
648  CALL get_field("ZTHE", zthe)
649  xmin = 1.0E+20
650  xmax = -1.0E+20
651  DO i = 1, klon
652     xmin = MIN(zthe(i), xmin)
653     xmax = MAX(zthe(i), xmax)
654  ENDDO
655  PRINT*, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
656
657  CALL get_field("ZPIC", zpic)
658  xmin = 1.0E+20
659  xmax = -1.0E+20
660  DO i = 1, klon
661     xmin = MIN(zpic(i), xmin)
662     xmax = MAX(zpic(i), xmax)
663  ENDDO
664  PRINT*, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
665
666  CALL get_field("ZVAL", zval)
667  xmin = 1.0E+20
668  xmax = -1.0E+20
669  DO i = 1, klon
670     xmin = MIN(zval(i), xmin)
671     xmax = MAX(zval(i), xmax)
672  ENDDO
673  PRINT*, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
674
675  CALL get_field("RUGSREL", rugoro)
676  xmin = 1.0E+20
677  xmax = -1.0E+20
678  DO i = 1, klon
679     xmin = MIN(rugoro(i), xmin)
680     xmax = MAX(rugoro(i), xmax)
681  ENDDO
682  PRINT*, 'Rugosite relief (ecart-type) rugsrel:', xmin, xmax
683
684  ancien_ok = .TRUE.
685
686  CALL get_field("TANCIEN", t_ancien, found)
687  IF (.NOT. found) THEN
688     PRINT*, "phyetat0: Le champ <TANCIEN> est absent"
689     PRINT*, "Depart legerement fausse. Mais je continue"
690     ancien_ok = .FALSE.
691  ENDIF
692
693  CALL get_field("QANCIEN", q_ancien, found)
694  IF (.NOT. found) THEN
695     PRINT*, "phyetat0: Le champ <QANCIEN> est absent"
696     PRINT*, "Depart legerement fausse. Mais je continue"
697     ancien_ok = .FALSE.
698  ENDIF
699
700  CALL get_field("UANCIEN", u_ancien, found)
701  IF (.NOT. found) THEN
702     PRINT*, "phyetat0: Le champ <UANCIEN> est absent"
703     PRINT*, "Depart legerement fausse. Mais je continue"
704     ancien_ok = .FALSE.
705  ENDIF
706
707  CALL get_field("VANCIEN", v_ancien, found)
708  IF (.NOT. found) THEN
709     PRINT*, "phyetat0: Le champ <VANCIEN> est absent"
710     PRINT*, "Depart legerement fausse. Mais je continue"
711     ancien_ok = .FALSE.
712  ENDIF
713
714  clwcon=0.
715  CALL get_field("CLWCON", clwcon, found)
716  IF (.NOT. found) THEN
717     PRINT*, "phyetat0: Le champ CLWCON est absent"
718     PRINT*, "Depart legerement fausse. Mais je continue"
719  ENDIF
720  xmin = 1.0E+20
721  xmax = -1.0E+20
722  xmin = MINval(clwcon)
723  xmax = MAXval(clwcon)
724  PRINT*, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
725
726  rnebcon = 0.
727  CALL get_field("RNEBCON", rnebcon, found)
728  IF (.NOT. found) THEN
729     PRINT*, "phyetat0: Le champ RNEBCON est absent"
730     PRINT*, "Depart legerement fausse. Mais je continue"
731  ENDIF
732  xmin = 1.0E+20
733  xmax = -1.0E+20
734  xmin = MINval(rnebcon)
735  xmax = MAXval(rnebcon)
736  PRINT*, 'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
737
738  ! Lecture ratqs
739
740  ratqs=0.
741  CALL get_field("RATQS", ratqs, found)
742  IF (.NOT. found) THEN
743     PRINT*, "phyetat0: Le champ <RATQS> est absent"
744     PRINT*, "Depart legerement fausse. Mais je continue"
745  ENDIF
746  xmin = 1.0E+20
747  xmax = -1.0E+20
748  xmin = MINval(ratqs)
749  xmax = MAXval(ratqs)
750  PRINT*, '(ecart-type) ratqs:', xmin, xmax
751
752  ! Lecture run_off_lic_0
753
754  CALL get_field("RUNOFFLIC0", run_off_lic_0, found)
755  IF (.NOT. found) THEN
756     PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"
757     PRINT*, "Depart legerement fausse. Mais je continue"
758     run_off_lic_0 = 0.
759  ENDIF
760  xmin = 1.0E+20
761  xmax = -1.0E+20
762  xmin = MINval(run_off_lic_0)
763  xmax = MAXval(run_off_lic_0)
764  PRINT*, '(ecart-type) run_off_lic_0:', xmin, xmax
765
766  ! Lecture de l'energie cinetique turbulente
767
768  IF (iflag_pbl>1) then
769     DO nsrf = 1, nbsrf
770        IF (nsrf.GT.99) THEN
771           PRINT*, "Trop de sous-mailles"
772           call abort_gcm("phyetat0", "", 1)
773        ENDIF
774        WRITE(str2, '(i2.2)') nsrf
775        CALL get_field("TKE"//str2, pbl_tke(:, 1:klev+1, nsrf), found)
776        IF (.NOT. found) THEN
777           PRINT*, "phyetat0: <TKE"//str2//"> est absent"
778           pbl_tke(:, :, nsrf)=1.e-8
779        ENDIF
780        xmin = 1.0E+20
781        xmax = -1.0E+20
782        DO k = 1, klev+1
783           DO i = 1, klon
784              xmin = MIN(pbl_tke(i, k, nsrf), xmin)
785              xmax = MAX(pbl_tke(i, k, nsrf), xmax)
786           ENDDO
787        ENDDO
788        PRINT*, 'Turbulent kinetic energyl TKE**:', nsrf, xmin, xmax
789     ENDDO
790  ENDIF
791
792! Lecture de l'ecart de TKE (w) - (x)
793!
794  IF (iflag_pbl>1 .AND. iflag_wake>=1  &
795           .AND. iflag_pbl_split >=1 ) then
796    DO nsrf = 1, nbsrf
797      IF (nsrf.GT.99) THEN
798        PRINT*, "Trop de sous-mailles"
799        call abort_gcm("phyetat0", "", 1)
800      ENDIF
801      WRITE(str2,'(i2.2)') nsrf
802      CALL get_field("DELTATKE"//str2, &
803                    wake_delta_pbl_tke(:,1:klev+1,nsrf),found)
804      IF (.NOT. found) THEN
805        PRINT*, "phyetat0: <DELTATKE"//str2//"> est absent"
806        wake_delta_pbl_tke(:,:,nsrf)=0.
807      ENDIF
808      xmin = 1.0E+20
809      xmax = -1.0E+20
810      DO k = 1, klev+1
811        DO i = 1, klon
812          xmin = MIN(wake_delta_pbl_tke(i,k,nsrf),xmin)
813          xmax = MAX(wake_delta_pbl_tke(i,k,nsrf),xmax)
814        ENDDO
815      ENDDO
816      PRINT*,'TKE difference (w)-(x) DELTATKE**:', nsrf, xmin, xmax
817    ENDDO
818
819  ! delta_tsurf
820
821    DO nsrf = 1, nbsrf
822       IF (nsrf.GT.99) THEN
823         PRINT*, "Trop de sous-mailles"
824         call abort_gcm("phyetat0", "", 1)
825       ENDIF
826       WRITE(str2,'(i2.2)') nsrf
827     CALL get_field("DELTA_TSURF"//str2, delta_tsurf(:,nsrf), found)
828     IF (.NOT. found) THEN
829        PRINT*, "phyetat0: Le champ <DELTA_TSURF"//str2//"> est absent"
830        PRINT*, "Depart legerement fausse. Mais je continue"
831        delta_tsurf(:,nsrf)=0.
832     ELSE
833        xmin = 1.0E+20
834        xmax = -1.0E+20
835         DO i = 1, klon
836            xmin = MIN(delta_tsurf(i, nsrf), xmin)
837            xmax = MAX(delta_tsurf(i, nsrf), xmax)
838         ENDDO
839        PRINT*, 'delta_tsurf:', xmin, xmax
840     ENDIF
841    ENDDO  ! nsrf = 1, nbsrf
842  ENDIF   !(iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 )
843
844  ! zmax0
845  CALL get_field("ZMAX0", zmax0, found)
846  IF (.NOT. found) THEN
847     PRINT*, "phyetat0: Le champ <ZMAX0> est absent"
848     PRINT*, "Depart legerement fausse. Mais je continue"
849     zmax0=40.
850  ENDIF
851  xmin = 1.0E+20
852  xmax = -1.0E+20
853  xmin = MINval(zmax0)
854  xmax = MAXval(zmax0)
855  PRINT*, '(ecart-type) zmax0:', xmin, xmax
856
857  !           f0(ig)=1.e-5
858  ! f0
859  CALL get_field("F0", f0, found)
860  IF (.NOT. found) THEN
861     PRINT*, "phyetat0: Le champ <f0> est absent"
862     PRINT*, "Depart legerement fausse. Mais je continue"
863     f0=1.e-5
864  ENDIF
865  xmin = 1.0E+20
866  xmax = -1.0E+20
867  xmin = MINval(f0)
868  xmax = MAXval(f0)
869  PRINT*, '(ecart-type) f0:', xmin, xmax
870
871  ! sig1 or ema_work1
872
873  CALL get_field("sig1", sig1, found)
874  IF (.NOT. found) CALL get_field("EMA_WORK1", sig1, found)
875  IF (.NOT. found) THEN
876     PRINT*, "phyetat0: Le champ sig1 est absent"
877     PRINT*, "Depart legerement fausse. Mais je continue"
878     sig1=0.
879  ELSE
880     xmin = 1.0E+20
881     xmax = -1.0E+20
882     DO k = 1, klev
883        DO i = 1, klon
884           xmin = MIN(sig1(i, k), xmin)
885           xmax = MAX(sig1(i, k), xmax)
886        ENDDO
887     ENDDO
888     PRINT*, 'sig1:', xmin, xmax
889  ENDIF
890
891  ! w01 or ema_work2
892
893  CALL get_field("w01", w01, found)
894  IF (.NOT. found) CALL get_field("EMA_WORK2", w01, found)
895  IF (.NOT. found) THEN
896     PRINT*, "phyetat0: Le champ w01 est absent"
897     PRINT*, "Depart legerement fausse. Mais je continue"
898     w01=0.
899  ELSE
900     xmin = 1.0E+20
901     xmax = -1.0E+20
902     DO k = 1, klev
903        DO i = 1, klon
904           xmin = MIN(w01(i, k), xmin)
905           xmax = MAX(w01(i, k), xmax)
906        ENDDO
907     ENDDO
908     PRINT*, 'w01:', xmin, xmax
909  ENDIF
910
911  ! wake_deltat
912
913  CALL get_field("WAKE_DELTAT", wake_deltat, found)
914  IF (.NOT. found) THEN
915     PRINT*, "phyetat0: Le champ <WAKE_DELTAT> est absent"
916     PRINT*, "Depart legerement fausse. Mais je continue"
917     wake_deltat=0.
918  ELSE
919     xmin = 1.0E+20
920     xmax = -1.0E+20
921     DO k = 1, klev
922        DO i = 1, klon
923           xmin = MIN(wake_deltat(i, k), xmin)
924           xmax = MAX(wake_deltat(i, k), xmax)
925        ENDDO
926     ENDDO
927     PRINT*, 'wake_deltat:', xmin, xmax
928  ENDIF
929
930  ! wake_deltaq
931
932  CALL get_field("WAKE_DELTAQ", wake_deltaq, found)
933  IF (.NOT. found) THEN
934     PRINT*, "phyetat0: Le champ <WAKE_DELTAQ> est absent"
935     PRINT*, "Depart legerement fausse. Mais je continue"
936     wake_deltaq=0.
937  ELSE
938     xmin = 1.0E+20
939     xmax = -1.0E+20
940     DO k = 1, klev
941        DO i = 1, klon
942           xmin = MIN(wake_deltaq(i, k), xmin)
943           xmax = MAX(wake_deltaq(i, k), xmax)
944        ENDDO
945     ENDDO
946     PRINT*, 'wake_deltaq:', xmin, xmax
947  ENDIF
948
949  ! wake_s
950
951  CALL get_field("WAKE_S", wake_s, found)
952  IF (.NOT. found) THEN
953     PRINT*, "phyetat0: Le champ <WAKE_S> est absent"
954     PRINT*, "Depart legerement fausse. Mais je continue"
955     wake_s=0.
956  ENDIF
957  xmin = 1.0E+20
958  xmax = -1.0E+20
959  xmin = MINval(wake_s)
960  xmax = MAXval(wake_s)
961  PRINT*, '(ecart-type) wake_s:', xmin, xmax
962
963  ! wake_cstar
964
965  CALL get_field("WAKE_CSTAR", wake_cstar, found)
966  IF (.NOT. found) THEN
967     PRINT*, "phyetat0: Le champ <WAKE_CSTAR> est absent"
968     PRINT*, "Depart legerement fausse. Mais je continue"
969     wake_cstar=0.
970  ENDIF
971  xmin = 1.0E+20
972  xmax = -1.0E+20
973  xmin = MINval(wake_cstar)
974  xmax = MAXval(wake_cstar)
975  PRINT*, '(ecart-type) wake_cstar:', xmin, xmax
976
977  ! wake_pe
978
979  CALL get_field("WAKE_PE", wake_pe, found)
980  IF (.NOT. found) THEN
981     PRINT*, "phyetat0: Le champ <WAKE_PE> est absent"
982     PRINT*, "Depart legerement fausse. Mais je continue"
983     wake_pe=0.
984  ENDIF
985  xmin = 1.0E+20
986  xmax = -1.0E+20
987  xmin = MINval(wake_pe)
988  xmax = MAXval(wake_pe)
989  PRINT*, '(ecart-type) wake_pe:', xmin, xmax
990
991  ! wake_fip
992
993  CALL get_field("WAKE_FIP", wake_fip, found)
994  IF (.NOT. found) THEN
995     PRINT*, "phyetat0: Le champ <WAKE_FIP> est absent"
996     PRINT*, "Depart legerement fausse. Mais je continue"
997     wake_fip=0.
998  ENDIF
999  xmin = 1.0E+20
1000  xmax = -1.0E+20
1001  xmin = MINval(wake_fip)
1002  xmax = MAXval(wake_fip)
1003  PRINT*, '(ecart-type) wake_fip:', xmin, xmax
1004
1005  !  thermiques
1006
1007  CALL get_field("FM_THERM", fm_therm, found)
1008  IF (.NOT. found) THEN
1009     PRINT*, "phyetat0: Le champ <fm_therm> est absent"
1010     PRINT*, "Depart legerement fausse. Mais je continue"
1011     fm_therm=0.
1012  ENDIF
1013  xmin = 1.0E+20
1014  xmax = -1.0E+20
1015  xmin = MINval(fm_therm)
1016  xmax = MAXval(fm_therm)
1017  PRINT*, '(ecart-type) fm_therm:', xmin, xmax
1018
1019  CALL get_field("ENTR_THERM", entr_therm, found)
1020  IF (.NOT. found) THEN
1021     PRINT*, "phyetat0: Le champ <entr_therm> est absent"
1022     PRINT*, "Depart legerement fausse. Mais je continue"
1023     entr_therm=0.
1024  ENDIF
1025  xmin = 1.0E+20
1026  xmax = -1.0E+20
1027  xmin = MINval(entr_therm)
1028  xmax = MAXval(entr_therm)
1029  PRINT*, '(ecart-type) entr_therm:', xmin, xmax
1030
1031  CALL get_field("DETR_THERM", detr_therm, found)
1032  IF (.NOT. found) THEN
1033     PRINT*, "phyetat0: Le champ <detr_therm> est absent"
1034     PRINT*, "Depart legerement fausse. Mais je continue"
1035     detr_therm=0.
1036  ENDIF
1037  xmin = 1.0E+20
1038  xmax = -1.0E+20
1039  xmin = MINval(detr_therm)
1040  xmax = MAXval(detr_therm)
1041  PRINT*, '(ecart-type) detr_therm:', xmin, xmax
1042
1043  CALL get_field("ALE_BL", ale_bl, found)
1044  IF (.NOT. found) THEN
1045     PRINT*, "phyetat0: Le champ <ale_bl> est absent"
1046     PRINT*, "Depart legerement fausse. Mais je continue"
1047     ale_bl=0.
1048  ENDIF
1049  xmin = 1.0E+20
1050  xmax = -1.0E+20
1051  xmin = MINval(ale_bl)
1052  xmax = MAXval(ale_bl)
1053  PRINT*, '(ecart-type) ale_bl:', xmin, xmax
1054
1055  CALL get_field("ALE_BL_TRIG", ale_bl_trig, found)
1056  IF (.NOT. found) THEN
1057     PRINT*, "phyetat0: Le champ <ale_bl_trig> est absent"
1058     PRINT*, "Depart legerement fausse. Mais je continue"
1059     ale_bl_trig=0.
1060  ENDIF
1061  xmin = 1.0E+20
1062  xmax = -1.0E+20
1063  xmin = MINval(ale_bl_trig)
1064  xmax = MAXval(ale_bl_trig)
1065  PRINT*, '(ecart-type) ale_bl_trig:', xmin, xmax
1066
1067  CALL get_field("ALP_BL", alp_bl, found)
1068  IF (.NOT. found) THEN
1069     PRINT*, "phyetat0: Le champ <alp_bl> est absent"
1070     PRINT*, "Depart legerement fausse. Mais je continue"
1071     alp_bl=0.
1072  ENDIF
1073  xmin = 1.0E+20
1074  xmax = -1.0E+20
1075  xmin = MINval(alp_bl)
1076  xmax = MAXval(alp_bl)
1077  PRINT*, '(ecart-type) alp_bl:', xmin, xmax
1078
1079  ! Read and send field trs to traclmdz
1080
1081  IF (type_trac == 'lmdz') THEN
1082     DO it=1, nbtr
1083        iiq=niadv(it+2)
1084        CALL get_field("trs_"//tname(iiq), trs(:, it), found)
1085        IF (.NOT. found) THEN
1086           PRINT*,  &
1087                "phyetat0: Le champ <trs_"//tname(iiq)//"> est absent"
1088           PRINT*, "Depart legerement fausse. Mais je continue"
1089           trs(:, it) = 0.
1090        ENDIF
1091        xmin = 1.0E+20
1092        xmax = -1.0E+20
1093        xmin = MINval(trs(:, it))
1094        xmax = MAXval(trs(:, it))
1095        PRINT*, "(ecart-type) trs_"//tname(iiq)//" :", xmin, xmax
1096
1097     END DO
1098     CALL traclmdz_from_restart(trs)
1099
1100     IF (carbon_cycle_cpl) THEN
1101        ALLOCATE(co2_send(klon), stat=ierr)
1102        IF (ierr /= 0) CALL abort_gcm &
1103             ('phyetat0', 'pb allocation co2_send', 1)
1104        CALL get_field("co2_send", co2_send, found)
1105        IF (.NOT. found) THEN
1106           PRINT*, "phyetat0: Le champ <co2_send> est absent"
1107           PRINT*, "Initialisation uniforme a co2_ppm=", co2_ppm
1108           co2_send(:) = co2_ppm
1109        END IF
1110     END IF
1111  END IF
1112
1113  if (ok_gwd_rando) then
1114     call get_field("du_gwd_rando", du_gwd_rando, found)
1115     if (.not. found) then
1116        print *, "du_gwd_rando not found, setting it to 0."
1117        du_gwd_rando = 0.
1118     end if
1119
1120     call get_field("dv_gwd_rando", dv_gwd_rando, found)
1121     if (.not. found) then
1122        print *, "dv_gwd_rando not found, setting it to 0."
1123        dv_gwd_rando = 0.
1124     end if
1125  end if
1126
1127  ! Initialize Slab variables
1128  IF ( type_ocean == 'slab' ) THEN
1129      print*, "calling slab_init"
1130      CALL ocean_slab_init(dtime, pctsrf)
1131      ! tslab
1132      CALL get_field("tslab", tslab, found)
1133      IF (.NOT. found) THEN
1134          PRINT*, "phyetat0: Le champ <tslab> est absent"
1135          PRINT*, "Initialisation a tsol_oce"
1136          DO i=1,nslay
1137              tslab(:,i)=MAX(ftsol(:,is_oce),271.35)
1138          END DO
1139      END IF
1140      ! Sea ice variables
1141      IF (version_ocean == 'sicINT') THEN
1142          CALL get_field("slab_tice", tice, found)
1143          IF (.NOT. found) THEN
1144              PRINT*, "phyetat0: Le champ <tice> est absent"
1145              PRINT*, "Initialisation a tsol_sic"
1146                  tice(:)=ftsol(:,is_sic)
1147          END IF
1148          CALL get_field("seaice", seaice, found)
1149          IF (.NOT. found) THEN
1150              PRINT*, "phyetat0: Le champ <seaice> est absent"
1151              PRINT*, "Initialisation a 0/1m suivant fraction glace"
1152              seaice(:)=0.
1153              WHERE (pctsrf(:,is_sic).GT.EPSFRA)
1154                  seaice=917.
1155              END WHERE
1156          END IF
1157      END IF !sea ice INT
1158  END IF ! Slab       
1159
1160  ! on ferme le fichier
1161  CALL close_startphy
1162
1163  ! Initialize module pbl_surface_mod
1164
1165  CALL pbl_surface_init(qsol, fder, snow, qsurf, &
1166       evap, frugs, agesno, tsoil)
1167
1168  ! Initialize module ocean_cpl_mod for the case of coupled ocean
1169  IF ( type_ocean == 'couple' ) THEN
1170     CALL ocean_cpl_init(dtime, rlon, rlat)
1171  ENDIF
1172
1173  CALL init_iophy_new(rlat, rlon)
1174
1175  ! Initilialize module fonte_neige_mod     
1176  CALL fonte_neige_init(run_off_lic_0)
1177
1178END SUBROUTINE phyetat0
Note: See TracBrowser for help on using the repository browser.