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

Last change on this file since 2198 was 2190, checked in by fhourdin, 9 years ago

Correction lecture flux descendant LW

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