source: LMDZ4/trunk/libf/phylmd/phyetat0.F @ 988

Last change on this file since 988 was 987, checked in by Laurent Fairhead, 16 years ago

Du nettoyage sur le parallelisme, inclusion de nouvelles interfaces pour OPA9
et ORCHIDEE YM
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 53.8 KB
Line 
1!
2! $Header$
3!
4c
5c
6      SUBROUTINE phyetat0 (fichnom,
7     .           ocean_in, ok_veget_in,
8     .           clesphy0,
9     .           tabcntr0)
10
11      USE dimphy
12      USE mod_grid_phy_lmdz
13      USE mod_phys_lmdz_para
14      USE iophy
15      USE ocean_slab_mod,   ONLY : ocean_slab_init
16      USE ocean_cpl_mod,    ONLY : ocean_cpl_init
17      USE ocean_forced_mod, ONLY : ocean_forced_init
18      USE fonte_neige_mod,  ONLY : fonte_neige_init
19      USE pbl_surface_mod,  ONLY : pbl_surface_init
20      USE surface_data,     ONLY : ocean, ok_veget
21      USE phys_state_var_mod
22
23      IMPLICIT none
24c======================================================================
25c Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
26c Objet: Lecture de l'etat initial pour la physique
27c======================================================================
28#include "dimensions.h"
29#include "netcdf.inc"
30#include "indicesol.h"
31#include "dimsoil.h"
32#include "clesphys.h"
33#include "temps.h"
34#include "thermcell.h"
35#include "compbl.h"
36c======================================================================
37      CHARACTER*(*) fichnom
38
39c les variables globales lues dans le fichier restart
40      REAL rlat_glo(klon_glo), rlon_glo(klon_glo)
41      REAL pctsrf_glo(klon_glo, nbsrf)
42      REAL tsol_glo(klon_glo,nbsrf)
43      REAL alb1_glo(klon_glo,nbsrf)
44      REAL alb2_glo(klon_glo,nbsrf)
45      REAL rain_fall_glo(klon_glo)
46      REAL snow_fall_glo(klon_glo)
47      real solsw_glo(klon_glo)
48      real sollw_glo(klon_glo)
49      REAL radsol_glo(klon_glo)
50      REAL zmea_glo(klon_glo)
51      REAL zstd_glo(klon_glo)
52      REAL zsig_glo(klon_glo)
53      REAL zgam_glo(klon_glo)
54      REAL zthe_glo(klon_glo)
55      REAL zpic_glo(klon_glo)
56      REAL zval_glo(klon_glo)
57      REAL rugsrel_glo(klon_glo)
58      REAL t_ancien_glo(klon_glo,klev), q_ancien_glo(klon_glo,klev)
59      REAL clwcon_glo(klon_glo,klev)
60      REAL rnebcon_glo(klon_glo,klev)
61      REAL ratqs_glo(klon_glo,klev)
62      REAL pbl_tke_glo(klon_glo,klev+1,nbsrf)
63      REAL zmax0_glo(klon_glo), f0_glo(klon)
64      REAL ema_work1_glo(klon_glo, klev), ema_work2_glo(klon_glo, klev)
65      REAL wake_deltat_glo(klon_glo,klev)
66      REAL wake_deltaq_glo(klon_glo,klev)
67      REAL wake_s_glo(klon_glo), wake_cstar_glo(klon_glo)
68      REAL wake_fip_glo(klon_glo)
69      REAL tsoil_p(klon,nsoilmx,nbsrf)
70      REAL tslab_p(klon), seaice_p(klon)
71      REAL qsurf_p(klon,nbsrf)
72      REAL qsol_p(klon)
73      REAL snow_p(klon,nbsrf)
74      REAL evap_p(klon,nbsrf)
75      real fder_p(klon)
76      REAL frugs_p(klon,nbsrf)
77      REAL agesno_p(klon,nbsrf)
78      REAL run_off_lic_0_p(klon)
79     
80      LOGICAL,SAVE ::  ancien_ok_glo
81!$OMP THREADPRIVATE(ancien_ok_glo) 
82   
83      REAL zmasq_glo(klon_glo)
84      REAL tsoil(klon_glo,nsoilmx,nbsrf)
85cIM "slab" ocean
86      REAL tslab(klon_glo), seaice(klon_glo)
87      REAL qsurf(klon_glo,nbsrf)
88      REAL qsol(klon_glo)
89      REAL snow(klon_glo,nbsrf)
90      REAL evap(klon_glo,nbsrf)
91      real fder(klon_glo)
92      REAL frugs(klon_glo,nbsrf)
93      REAL agesno(klon_glo,nbsrf)
94      REAL fractint(klon_glo)
95      REAL run_off_lic_0(klon_glo)
96
97      CHARACTER*6 ocean_in
98      LOGICAL ok_veget_in
99
100      INTEGER        longcles
101      PARAMETER    ( longcles = 20 )
102      REAL clesphy0( longcles )
103c
104      REAL xmin, xmax
105c
106      INTEGER nid, nvarid
107      INTEGER ierr, i, nsrf, isoil ,k
108      INTEGER length
109      PARAMETER (length=100)
110      REAL tab_cntrl(length), tabcntr0(length)
111      CHARACTER*7 str7
112      CHARACTER*2 str2
113
114c FH1D
115c     real iolat(jjm+1)
116      real iolat(jjm+1-1/iim)
117c
118c Ouvrir le fichier contenant l'etat initial:
119c
120
121c$OMP MASTER
122      print *,'MASTER -x , omp_rank=',omp_rank
123c$OMP END MASTER
124
125c$OMP MASTER
126      IF (is_mpi_root) THEN
127        print*,'fichnom ',fichnom
128        ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)
129        IF (ierr.NE.NF_NOERR) THEN
130          write(6,*)' Pb d''ouverture du fichier '//fichnom
131          write(6,*)' ierr = ', ierr
132          CALL ABORT
133        ENDIF
134      ENDIF
135c$OMP END MASTER
136c
137c Lecture des parametres de controle:
138c
139c$OMP MASTER
140      IF (is_mpi_root) THEN
141     
142      ierr = NF_INQ_VARID (nid, "controle", nvarid)
143      IF (ierr.NE.NF_NOERR) THEN
144         PRINT*, 'phyetat0: Le champ <controle> est absent'
145         CALL abort
146      ENDIF
147#ifdef NC_DOUBLE
148      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, tab_cntrl)
149#else
150      ierr = NF_GET_VAR_REAL(nid, nvarid, tab_cntrl)
151#endif
152      IF (ierr.NE.NF_NOERR) THEN
153         PRINT*, 'phyetat0: Lecture echouee pour <controle>'
154         CALL abort
155      ENDIF
156      ENDIF
157
158c$OMP END MASTER
159       
160       CALL bcast(tab_cntrl)
161       
162c
163!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
164! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
165! Les constantes de la physiques sont lues dans la physique seulement.
166! Les egalites du type
167!             tab_cntrl( 5 )=clesphy0(1)
168! sont remplacees par
169!             clesphy0(1)=tab_cntrl( 5 )
170! On inverse aussi la logique.
171! On remplit les tab_cntrl avec les parametres lus dans les .def
172!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
173
174         DO i = 1, length
175           tabcntr0( i ) = tab_cntrl( i )
176         ENDDO
177c
178         tab_cntrl(1)=dtime
179         tab_cntrl(2)=radpas
180         co2_ppm_etat0      = tab_cntrl(3)
181         solaire_etat0      = tab_cntrl(4)
182         tab_cntrl(5)=iflag_con
183         tab_cntrl(6)=nbapp_rad
184
185         if (cycle_diurne) tab_cntrl( 7) =1.
186         if (soil_model) tab_cntrl( 8) =1.
187         if (new_oliq) tab_cntrl( 9) =1.
188         if (ok_orodr) tab_cntrl(10) =1.
189         if (ok_orolf) tab_cntrl(11) =1.
190         if (ok_limitvrai) tab_cntrl(12) =1.
191
192
193      itau_phy = tab_cntrl(15)
194
195       
196
197         IF( clesphy0(1).NE.tab_cntrl( 5 ) )  THEN
198             clesphy0(1)=tab_cntrl( 5 )
199         ENDIF
200
201         IF( clesphy0(2).NE.tab_cntrl( 6 ) )  THEN
202             clesphy0(2)=tab_cntrl( 6 )
203         ENDIF
204
205         IF( clesphy0(3).NE.tab_cntrl( 7 ) )  THEN
206             clesphy0(3)=tab_cntrl( 7 )
207         ENDIF
208
209         IF( clesphy0(4).NE.tab_cntrl( 8 ) )  THEN
210             clesphy0(4)=tab_cntrl( 8 )
211         ENDIF
212
213         IF( clesphy0(5).NE.tab_cntrl( 9 ) )  THEN
214             clesphy0(5)=tab_cntrl( 9 )
215         ENDIF
216
217         IF( clesphy0(6).NE.tab_cntrl( 10 ) )  THEN
218             clesphy0(6)=tab_cntrl( 10 )
219         ENDIF
220
221         IF( clesphy0(7).NE.tab_cntrl( 11 ) )  THEN
222             clesphy0(7)=tab_cntrl( 11 )
223         ENDIF
224
225         IF( clesphy0(8).NE.tab_cntrl( 12 ) )  THEN
226             clesphy0(8)=tab_cntrl( 12 )
227         ENDIF
228
229
230c
231c Lecture des latitudes (coordonnees):
232c
233      IF (is_mpi_root .AND. is_omp_root) THEN
234     
235      ierr = NF_INQ_VARID (nid, "latitude", nvarid)
236      IF (ierr.NE.NF_NOERR) THEN
237         PRINT*, 'phyetat0: Le champ <latitude> est absent'
238         CALL abort
239      ENDIF
240#ifdef NC_DOUBLE
241      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, rlat_glo)
242#else
243      ierr = NF_GET_VAR_REAL(nid, nvarid, rlat_glo)
244#endif
245      IF (ierr.NE.NF_NOERR) THEN
246         PRINT*, 'phyetat0: Lecture echouee pour <latitude>'
247         CALL abort
248      ENDIF
249
250c
251c Lecture des longitudes (coordonnees):
252c
253      ierr = NF_INQ_VARID (nid, "longitude", nvarid)
254      IF (ierr.NE.NF_NOERR) THEN
255         PRINT*, 'phyetat0: Le champ <longitude> est absent'
256         CALL abort
257      ENDIF
258#ifdef NC_DOUBLE
259      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, rlon_glo)
260#else
261      ierr = NF_GET_VAR_REAL(nid, nvarid, rlon_glo)
262#endif
263      IF (ierr.NE.NF_NOERR) THEN
264         PRINT*, 'phyetat0: Lecture echouee pour <latitude>'
265         CALL abort
266      ENDIF
267C
268C
269C Lecture du masque terre mer
270C
271
272      ierr = NF_INQ_VARID (nid, "masque", nvarid)
273      IF (ierr .EQ.  NF_NOERR) THEN
274#ifdef NC_DOUBLE
275          ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zmasq_glo)
276#else
277          ierr = NF_GET_VAR_REAL(nid, nvarid, zmasq_glo)
278#endif
279          IF (ierr.NE.NF_NOERR) THEN
280              PRINT*, 'phyetat0: Lecture echouee pour <masque>'
281              CALL abort
282          ENDIF
283      else
284          PRINT*, 'phyetat0: Le champ <masque> est absent'
285          PRINT*, 'fichier startphy non compatible avec phyetat0'
286C      CALL abort
287      ENDIF
288
289       
290C Lecture des fractions pour chaque sous-surface
291C
292C initialisation des sous-surfaces
293C
294      pctsrf = 0.
295C
296C fraction de terre
297C
298
299      ierr = NF_INQ_VARID (nid, "FTER", nvarid)
300      IF (ierr .EQ.  NF_NOERR) THEN
301#ifdef NC_DOUBLE
302          ierr = NF_GET_VAR_DOUBLE(nid, nvarid,       
303     .                             pctsrf_glo(1 : klon_glo,is_ter))
304#else
305          ierr = NF_GET_VAR_REAL(nid, nvarid,
306     .                           pctsrf_glo(1 : klon_glo,is_ter))
307#endif
308          IF (ierr.NE.NF_NOERR) THEN
309              PRINT*, 'phyetat0: Lecture echouee pour <FTER>'
310              CALL abort
311          ENDIF
312      else
313          PRINT*, 'phyetat0: Le champ <FTER> est absent'
314c@$$         CALL abort
315      ENDIF
316
317C
318C fraction de glace de terre
319C
320      ierr = NF_INQ_VARID (nid, "FLIC", nvarid)
321      IF (ierr .EQ.  NF_NOERR) THEN
322#ifdef NC_DOUBLE
323          ierr = NF_GET_VAR_DOUBLE(nid, nvarid,
324     .                             pctsrf_glo(1 : klon_glo,is_lic))
325#else
326          ierr = NF_GET_VAR_REAL(nid, nvarid,
327     .                           pctsrf_glo(1 : klon_glo,is_lic))
328#endif
329          IF (ierr.NE.NF_NOERR) THEN
330              PRINT*, 'phyetat0: Lecture echouee pour <FLIC>'
331              CALL abort
332          ENDIF
333      else
334          PRINT*, 'phyetat0: Le champ <FLIC> est absent'
335c@$$         CALL abort
336      ENDIF
337C
338C fraction d'ocean
339C
340      ierr = NF_INQ_VARID (nid, "FOCE", nvarid)
341      IF (ierr .EQ.  NF_NOERR) THEN
342#ifdef NC_DOUBLE
343          ierr = NF_GET_VAR_DOUBLE(nid, nvarid,
344     .                             pctsrf_glo(1 : klon_glo,is_oce))
345#else
346          ierr = NF_GET_VAR_REAL(nid, nvarid,
347     .                           pctsrf_glo(1 : klon_glo,is_oce))
348#endif
349          IF (ierr.NE.NF_NOERR) THEN
350              PRINT*, 'phyetat0: Lecture echouee pour <FOCE>'
351              CALL abort
352          ENDIF
353      else
354          PRINT*, 'phyetat0: Le champ <FOCE> est absent'
355c@$$         CALL abort
356      ENDIF
357
358C
359C fraction glace de mer
360C
361      ierr = NF_INQ_VARID (nid, "FSIC", nvarid)
362      IF (ierr .EQ.  NF_NOERR) THEN
363#ifdef NC_DOUBLE
364          ierr = NF_GET_VAR_DOUBLE(nid, nvarid,
365     .                             pctsrf_glo(1 : klon_glo,is_sic))
366#else
367          ierr = NF_GET_VAR_REAL(nid, nvarid,
368     .                           pctsrf_glo(1 : klon_glo, is_sic))
369#endif
370          IF (ierr.NE.NF_NOERR) THEN
371              PRINT*, 'phyetat0: Lecture echouee pour <FSIC>'
372              CALL abort
373          ENDIF
374      else
375          PRINT*, 'phyetat0: Le champ <FSIC> est absent'
376c@$$         CALL abort
377      ENDIF
378
379C
380C  Verification de l'adequation entre le masque et les sous-surfaces
381C
382      fractint( 1 : klon_glo) = pctsrf_glo(1 : klon_glo, is_ter)
383     $    + pctsrf_glo(1 : klon_glo, is_lic)
384      DO i = 1 , klon_glo
385        IF ( abs(fractint(i) - zmasq_glo(i) ) .GT. EPSFRA ) THEN
386            WRITE(*,*) 'phyetat0: attention fraction terre pas ',
387     $          'coherente ', i, zmasq_glo(i), pctsrf_glo(i, is_ter)
388     $          ,pctsrf_glo(i, is_lic)
389        ENDIF
390      END DO
391      fractint (1 : klon_glo) =  pctsrf_glo(1 : klon_glo, is_oce)
392     $    + pctsrf_glo(1 : klon_glo, is_sic)
393      DO i = 1 , klon_glo
394        IF ( abs( fractint(i) - (1. - zmasq_glo(i))) .GT. EPSFRA ) THEN
395            WRITE(*,*) 'phyetat0 attention fraction ocean pas ',
396     $          'coherente ', i, zmasq_glo(i) , pctsrf_glo(i, is_oce)
397     $          ,pctsrf_glo(i, is_sic)
398        ENDIF
399      END DO
400
401C
402c Lecture des temperatures du sol:
403c
404
405      ierr = NF_INQ_VARID (nid, "TS", nvarid)
406      IF (ierr.NE.NF_NOERR) THEN
407         PRINT*, 'phyetat0: Le champ <TS> est absent'
408         PRINT*, '          Mais je vais essayer de lire TS**'
409         DO nsrf = 1, nbsrf
410           IF (nsrf.GT.99) THEN
411             PRINT*, "Trop de sous-mailles"
412             CALL abort
413           ENDIF
414           WRITE(str2,'(i2.2)') nsrf
415           ierr = NF_INQ_VARID (nid, "TS"//str2, nvarid)
416           IF (ierr.NE.NF_NOERR) THEN
417              PRINT*, "phyetat0: Le champ <TS"//str2//"> est absent"
418              CALL abort
419           ENDIF
420#ifdef NC_DOUBLE
421           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, tsol_glo(1,nsrf))
422#else
423           ierr = NF_GET_VAR_REAL(nid, nvarid, tsol_glo(1,nsrf))
424#endif
425           IF (ierr.NE.NF_NOERR) THEN
426             PRINT*, "phyetat0: Lecture echouee pour <TS"//str2//">"
427             CALL abort
428           ENDIF
429
430           xmin = 1.0E+20
431           xmax = -1.0E+20
432           DO i = 1, klon_glo
433              xmin = MIN(tsol_glo(i,nsrf),xmin)
434              xmax = MAX(tsol_glo(i,nsrf),xmax)
435           ENDDO
436           PRINT*,'Temperature du sol TS**:', nsrf, xmin, xmax
437         ENDDO
438      ELSE
439         PRINT*, 'phyetat0: Le champ <TS> est present'
440         PRINT*, '          J ignore donc les autres temperatures TS**'
441#ifdef NC_DOUBLE
442         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, tsol_glo(1,1))
443#else
444         ierr = NF_GET_VAR_REAL(nid, nvarid, tsol_glo(1,1))
445#endif
446         IF (ierr.NE.NF_NOERR) THEN
447            PRINT*, "phyetat0: Lecture echouee pour <TS>"
448            CALL abort
449         ENDIF
450         xmin = 1.0E+20
451         xmax = -1.0E+20
452         DO i = 1, klon_glo
453            xmin = MIN(tsol_glo(i,1),xmin)
454            xmax = MAX(tsol_glo(i,1),xmax)
455         ENDDO
456         PRINT*,'Temperature du sol <TS>', xmin, xmax
457         DO nsrf = 2, nbsrf
458         DO i = 1, klon_glo
459            tsol_glo(i,nsrf) = tsol_glo(i,1)
460         ENDDO
461         ENDDO
462      ENDIF
463
464c
465c Lecture des temperatures du sol profond:
466c
467      DO nsrf = 1, nbsrf
468      DO isoil=1, nsoilmx
469      IF (isoil.GT.99 .AND. nsrf.GT.99) THEN
470         PRINT*, "Trop de couches ou sous-mailles"
471         CALL abort
472      ENDIF
473      WRITE(str7,'(i2.2,"srf",i2.2)') isoil, nsrf
474      ierr = NF_INQ_VARID (nid, 'Tsoil'//str7, nvarid)
475      IF (ierr.NE.NF_NOERR) THEN
476         PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
477         PRINT*, "          Il prend donc la valeur de surface"
478         DO i=1, klon_glo
479             tsoil(i,isoil,nsrf)=tsol_glo(i,nsrf)
480         ENDDO
481      ELSE
482#ifdef NC_DOUBLE
483         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, tsoil(1,isoil,nsrf))
484#else
485         ierr = NF_GET_VAR_REAL(nid, nvarid, tsoil(1,isoil,nsrf))
486#endif
487         IF (ierr.NE.NF_NOERR) THEN
488            PRINT*, "Lecture echouee pour <Tsoil"//str7//">"
489            CALL abort
490         ENDIF
491      ENDIF
492      ENDDO
493      ENDDO
494c
495cIM "slab" ocean
496c
497c Lecture de tslab (pour slab ocean seulement):     
498c
499      IF (ocean_in .eq. 'slab  ') then
500        ierr = NF_INQ_VARID (nid, "TSLAB", nvarid)
501        IF (ierr.NE.NF_NOERR) THEN
502          PRINT*, "phyetat0: Le champ <TSLAB> est absent"
503          CALL abort
504        ENDIF
505#ifdef NC_DOUBLE
506        ierr = NF_GET_VAR_DOUBLE(nid, nvarid, tslab)
507#else
508        ierr = NF_GET_VAR_REAL(nid, nvarid, tslab)
509#endif
510        IF (ierr.NE.NF_NOERR) THEN
511          PRINT*, "phyetat0: Lecture echouee pour <TSLAB>"
512          CALL abort
513        ENDIF
514        xmin = 1.0E+20
515        xmax = -1.0E+20
516        DO i = 1, klon_glo
517          xmin = MIN(tslab(i),xmin)
518          xmax = MAX(tslab(i),xmax)
519        ENDDO
520        PRINT*,'Min, Max tslab (utilise si OCEAN=slab )', xmin, xmax
521c
522c Lecture de seaice (pour slab ocean seulement):
523c
524        ierr = NF_INQ_VARID (nid, "SEAICE", nvarid)
525        IF (ierr.NE.NF_NOERR) THEN
526          PRINT*, "phyetat0: Le champ <SEAICE> est absent"
527          CALL abort
528        ENDIF
529#ifdef NC_DOUBLE
530        ierr = NF_GET_VAR_DOUBLE(nid, nvarid, seaice)
531#else
532        ierr = NF_GET_VAR_REAL(nid, nvarid, seaice)
533#endif
534        IF (ierr.NE.NF_NOERR) THEN
535          PRINT*, "phyetat0: Lecture echouee pour <SEAICE>"
536          CALL abort
537        ENDIF
538        xmin = 1.0E+20
539        xmax = -1.0E+20
540        DO i = 1, klon_glo
541          xmin = MIN(seaice(i),xmin)
542          xmax = MAX(seaice(i),xmax)
543        ENDDO
544        PRINT*,'Masse de la glace de mer (utilise si OCEAN=slab)',
545     $  xmin, xmax
546      ELSE
547        tslab = 0.
548        seaice = 0.
549      ENDIF
550c
551c Lecture de l'humidite de l'air juste au dessus du sol:
552c
553      ierr = NF_INQ_VARID (nid, "QS", nvarid)
554      IF (ierr.NE.NF_NOERR) THEN
555         PRINT*, 'phyetat0: Le champ <QS> est absent'
556         PRINT*, '          Mais je vais essayer de lire QS**'
557         DO nsrf = 1, nbsrf
558           IF (nsrf.GT.99) THEN
559             PRINT*, "Trop de sous-mailles"
560             CALL abort
561           ENDIF
562           WRITE(str2,'(i2.2)') nsrf
563           ierr = NF_INQ_VARID (nid, "QS"//str2, nvarid)
564           IF (ierr.NE.NF_NOERR) THEN
565              PRINT*, "phyetat0: Le champ <QS"//str2//"> est absent"
566              CALL abort
567           ENDIF
568#ifdef NC_DOUBLE
569           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, qsurf(1,nsrf))
570#else
571           ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,nsrf))
572#endif
573           IF (ierr.NE.NF_NOERR) THEN
574             PRINT*, "phyetat0: Lecture echouee pour <QS"//str2//">"
575             CALL abort
576           ENDIF
577           xmin = 1.0E+20
578           xmax = -1.0E+20
579           DO i = 1, klon_glo
580              xmin = MIN(qsurf(i,nsrf),xmin)
581              xmax = MAX(qsurf(i,nsrf),xmax)
582           ENDDO
583           PRINT*,'Humidite pres du sol QS**:', nsrf, xmin, xmax
584         ENDDO
585      ELSE
586         PRINT*, 'phyetat0: Le champ <QS> est present'
587         PRINT*, '          J ignore donc les autres humidites QS**'
588#ifdef NC_DOUBLE
589         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, qsurf(1,1))
590#else
591         ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,1))
592#endif
593         IF (ierr.NE.NF_NOERR) THEN
594            PRINT*, "phyetat0: Lecture echouee pour <QS>"
595            CALL abort
596         ENDIF
597         xmin = 1.0E+20
598         xmax = -1.0E+20
599         DO i = 1, klon_glo
600            xmin = MIN(qsurf(i,1),xmin)
601            xmax = MAX(qsurf(i,1),xmax)
602         ENDDO
603         PRINT*,'Humidite pres du sol <QS>', xmin, xmax
604         DO nsrf = 2, nbsrf
605         DO i = 1, klon_glo
606            qsurf(i,nsrf) = qsurf(i,1)
607         ENDDO
608         ENDDO
609      ENDIF
610C
611C Eau dans le sol (pour le modele de sol "bucket")
612C
613      ierr = NF_INQ_VARID (nid, "QSOL", nvarid)
614      IF (ierr .EQ.  NF_NOERR) THEN
615#ifdef NC_DOUBLE
616          ierr = NF_GET_VAR_DOUBLE(nid, nvarid, qsol)
617#else
618          ierr = NF_GET_VAR_REAL(nid, nvarid, qsol)
619#endif
620          IF (ierr.NE.NF_NOERR) THEN
621              PRINT*, 'phyetat0: Lecture echouee pour <QSOL>'
622              CALL abort
623          ENDIF
624      else
625          PRINT*, 'phyetat0: Le champ <QSOL> est absent'
626          PRINT*, '          Valeur par defaut nulle'
627          qsol(:)=0.
628c@$$         CALL abort
629      ENDIF
630      xmin = 1.0E+20
631      xmax = -1.0E+20
632      DO i = 1, klon_glo
633        xmin = MIN(qsol(i),xmin)
634        xmax = MAX(qsol(i),xmax)
635      ENDDO
636      PRINT*,'Eau dans le sol (mm) <QSOL>', xmin, xmax
637c
638c Lecture de neige au sol:
639c
640      ierr = NF_INQ_VARID (nid, "SNOW", nvarid)
641      IF (ierr.NE.NF_NOERR) THEN
642         PRINT*, 'phyetat0: Le champ <SNOW> est absent'
643         PRINT*, '          Mais je vais essayer de lire SNOW**'
644         DO nsrf = 1, nbsrf
645           IF (nsrf.GT.99) THEN
646             PRINT*, "Trop de sous-mailles"
647             CALL abort
648           ENDIF
649           WRITE(str2,'(i2.2)') nsrf
650           ierr = NF_INQ_VARID (nid, "SNOW"//str2, nvarid)
651           IF (ierr.NE.NF_NOERR) THEN
652              PRINT*, "phyetat0: Le champ <SNOW"//str2//"> est absent"
653              CALL abort
654           ENDIF
655#ifdef NC_DOUBLE
656           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, snow(1,nsrf))
657#else
658           ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,nsrf))
659#endif
660           IF (ierr.NE.NF_NOERR) THEN
661             PRINT*, "phyetat0: Lecture echouee pour <SNOW"//str2//">"
662             CALL abort
663           ENDIF
664           xmin = 1.0E+20
665           xmax = -1.0E+20
666           DO i = 1, klon_glo
667              xmin = MIN(snow(i,nsrf),xmin)
668              xmax = MAX(snow(i,nsrf),xmax)
669           ENDDO
670           PRINT*,'Neige du sol SNOW**:', nsrf, xmin, xmax
671         ENDDO
672      ELSE
673         PRINT*, 'phyetat0: Le champ <SNOW> est present'
674         PRINT*, '          J ignore donc les autres neiges SNOW**'
675#ifdef NC_DOUBLE
676         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, snow(1,1))
677#else
678         ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,1))
679#endif
680         IF (ierr.NE.NF_NOERR) THEN
681            PRINT*, "phyetat0: Lecture echouee pour <SNOW>"
682            CALL abort
683         ENDIF
684         xmin = 1.0E+20
685         xmax = -1.0E+20
686         DO i = 1, klon_glo
687            xmin = MIN(snow(i,1),xmin)
688            xmax = MAX(snow(i,1),xmax)
689         ENDDO
690         PRINT*,'Neige du sol <SNOW>', xmin, xmax
691         DO nsrf = 2, nbsrf
692         DO i = 1, klon_glo
693            snow(i,nsrf) = snow(i,1)
694         ENDDO
695         ENDDO
696      ENDIF
697c
698c Lecture de albedo de l'interval visible au sol:
699c
700      ierr = NF_INQ_VARID (nid, "ALBE", nvarid)
701      IF (ierr.NE.NF_NOERR) THEN
702         PRINT*, 'phyetat0: Le champ <ALBE> est absent'
703         PRINT*, '          Mais je vais essayer de lire ALBE**'
704         DO nsrf = 1, nbsrf
705           IF (nsrf.GT.99) THEN
706             PRINT*, "Trop de sous-mailles"
707             CALL abort
708           ENDIF
709           WRITE(str2,'(i2.2)') nsrf
710           ierr = NF_INQ_VARID (nid, "ALBE"//str2, nvarid)
711           IF (ierr.NE.NF_NOERR) THEN
712              PRINT*, "phyetat0: Le champ <ALBE"//str2//"> est absent"
713              CALL abort
714           ENDIF
715#ifdef NC_DOUBLE
716           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, alb1_glo(1,nsrf))
717#else
718           ierr = NF_GET_VAR_REAL(nid, nvarid, alb1_glo(1,nsrf))
719#endif
720           IF (ierr.NE.NF_NOERR) THEN
721             PRINT*, "phyetat0: Lecture echouee pour <ALBE"//str2//">"
722             CALL abort
723           ENDIF
724           xmin = 1.0E+20
725           xmax = -1.0E+20
726           DO i = 1, klon_glo
727              xmin = MIN(alb1_glo(i,nsrf),xmin)
728              xmax = MAX(alb1_glo(i,nsrf),xmax)
729           ENDDO
730           PRINT*,'Albedo du sol ALBE**:', nsrf, xmin, xmax
731         ENDDO
732      ELSE
733         PRINT*, 'phyetat0: Le champ <ALBE> est present'
734         PRINT*, '          J ignore donc les autres ALBE**'
735#ifdef NC_DOUBLE
736         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, alb1_glo(1,1))
737#else
738         ierr = NF_GET_VAR_REAL(nid, nvarid, alb1_glo(1,1))
739#endif
740         IF (ierr.NE.NF_NOERR) THEN
741            PRINT*, "phyetat0: Lecture echouee pour <ALBE>"
742            CALL abort
743         ENDIF
744         xmin = 1.0E+20
745         xmax = -1.0E+20
746         DO i = 1, klon_glo
747            xmin = MIN(alb1_glo(i,1),xmin)
748            xmax = MAX(alb1_glo(i,1),xmax)
749         ENDDO
750         PRINT*,'Neige du sol <ALBE>', xmin, xmax
751         DO nsrf = 2, nbsrf
752         DO i = 1, klon_glo
753            alb1_glo(i,nsrf) = alb1_glo(i,1)
754         ENDDO
755         ENDDO
756      ENDIF
757
758c
759c Lecture de albedo au sol dans l'interval proche infra-rouge:
760c
761      ierr = NF_INQ_VARID (nid, "ALBLW", nvarid)
762      IF (ierr.NE.NF_NOERR) THEN
763         PRINT*, 'phyetat0: Le champ <ALBLW> est absent'
764c        PRINT*, '          Mais je vais essayer de lire ALBLW**'
765         PRINT*, '          Mais je vais prendre ALBE**'
766         DO nsrf = 1, nbsrf
767           DO i = 1, klon_glo
768             alb2_glo(i,nsrf) = alb1_glo(i,nsrf)
769           ENDDO
770         ENDDO
771      ELSE
772         PRINT*, 'phyetat0: Le champ <ALBLW> est present'
773         PRINT*, '          J ignore donc les autres ALBLW**'
774#ifdef NC_DOUBLE
775         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, alb2_glo(1,1))
776#else
777         ierr = NF_GET_VAR_REAL(nid, nvarid, alb2_glo(1,1))
778#endif
779         IF (ierr.NE.NF_NOERR) THEN
780            PRINT*, "phyetat0: Lecture echouee pour <ALBLW>"
781            CALL abort
782         ENDIF
783         xmin = 1.0E+20
784         xmax = -1.0E+20
785         DO i = 1, klon_glo
786            xmin = MIN(alb2_glo(i,1),xmin)
787            xmax = MAX(alb2_glo(i,1),xmax)
788         ENDDO
789         PRINT*,'Neige du sol <ALBLW>', xmin, xmax
790         DO nsrf = 2, nbsrf
791         DO i = 1, klon_glo
792            alb2_glo(i,nsrf) = alb2_glo(i,1)
793         ENDDO
794         ENDDO
795      ENDIF
796c
797c Lecture de evaporation: 
798c
799      ierr = NF_INQ_VARID (nid, "EVAP", nvarid)
800      IF (ierr.NE.NF_NOERR) THEN
801         PRINT*, 'phyetat0: Le champ <EVAP> est absent'
802         PRINT*, '          Mais je vais essayer de lire EVAP**'
803         DO nsrf = 1, nbsrf
804           IF (nsrf.GT.99) THEN
805             PRINT*, "Trop de sous-mailles"
806             CALL abort
807           ENDIF
808           WRITE(str2,'(i2.2)') nsrf
809           ierr = NF_INQ_VARID (nid, "EVAP"//str2, nvarid)
810           IF (ierr.NE.NF_NOERR) THEN
811              PRINT*, "phyetat0: Le champ <EVAP"//str2//"> est absent"
812              CALL abort
813           ENDIF
814#ifdef NC_DOUBLE
815           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, evap(1,nsrf))
816#else
817           ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,nsrf))
818#endif
819           IF (ierr.NE.NF_NOERR) THEN
820             PRINT*, "phyetat0: Lecture echouee pour <EVAP"//str2//">"
821             CALL abort
822           ENDIF
823           xmin = 1.0E+20
824           xmax = -1.0E+20
825           DO i = 1, klon_glo
826              xmin = MIN(evap(i,nsrf),xmin)
827              xmax = MAX(evap(i,nsrf),xmax)
828           ENDDO
829           PRINT*,'evap du sol EVAP**:', nsrf, xmin, xmax
830         ENDDO
831      ELSE
832         PRINT*, 'phyetat0: Le champ <EVAP> est present'
833         PRINT*, '          J ignore donc les autres EVAP**'
834#ifdef NC_DOUBLE
835         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, evap(1,1))
836#else
837         ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,1))
838#endif
839         IF (ierr.NE.NF_NOERR) THEN
840            PRINT*, "phyetat0: Lecture echouee pour <EVAP>"
841            CALL abort
842         ENDIF
843         xmin = 1.0E+20
844         xmax = -1.0E+20
845         DO i = 1, klon_glo
846            xmin = MIN(evap(i,1),xmin)
847            xmax = MAX(evap(i,1),xmax)
848         ENDDO
849         PRINT*,'Evap du sol <EVAP>', xmin, xmax
850         DO nsrf = 2, nbsrf
851         DO i = 1, klon_glo
852            evap(i,nsrf) = evap(i,1)
853         ENDDO
854         ENDDO
855      ENDIF
856c
857c Lecture precipitation liquide:
858c
859      ierr = NF_INQ_VARID (nid, "rain_f", nvarid)
860      IF (ierr.NE.NF_NOERR) THEN
861         PRINT*, 'phyetat0: Le champ <rain_f> est absent'
862         CALL abort
863      ENDIF
864#ifdef NC_DOUBLE
865      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, rain_fall_glo)
866#else
867      ierr = NF_GET_VAR_REAL(nid, nvarid, rain_fall_glo)
868#endif
869      IF (ierr.NE.NF_NOERR) THEN
870         PRINT*, 'phyetat0: Lecture echouee pour <rain_f>'
871         CALL abort
872      ENDIF
873      xmin = 1.0E+20
874      xmax = -1.0E+20
875      DO i = 1, klon_glo
876         xmin = MIN(rain_fall_glo(i),xmin)
877         xmax = MAX(rain_fall_glo(i),xmax)
878      ENDDO
879      PRINT*,'Precipitation liquide rain_f:', xmin, xmax
880c
881c Lecture precipitation solide:
882c
883      ierr = NF_INQ_VARID (nid, "snow_f", nvarid)
884      IF (ierr.NE.NF_NOERR) THEN
885         PRINT*, 'phyetat0: Le champ <snow_f> est absent'
886         CALL abort
887      ENDIF
888#ifdef NC_DOUBLE
889      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, snow_fall_glo)
890#else
891      ierr = NF_GET_VAR_REAL(nid, nvarid, snow_fall_glo)
892#endif
893      IF (ierr.NE.NF_NOERR) THEN
894         PRINT*, 'phyetat0: Lecture echouee pour <snow_f>'
895         CALL abort
896      ENDIF
897      xmin = 1.0E+20
898      xmax = -1.0E+20
899      DO i = 1, klon_glo
900         xmin = MIN(snow_fall_glo(i),xmin)
901         xmax = MAX(snow_fall_glo(i),xmax)
902      ENDDO
903      PRINT*,'Precipitation solide snow_f:', xmin, xmax
904c
905c Lecture rayonnement solaire au sol:
906c
907      ierr = NF_INQ_VARID (nid, "solsw", nvarid)
908      IF (ierr.NE.NF_NOERR) THEN
909         PRINT*, 'phyetat0: Le champ <solsw> est absent'
910         PRINT*, 'mis a zero'
911         solsw_glo = 0.
912      ELSE
913#ifdef NC_DOUBLE
914        ierr = NF_GET_VAR_DOUBLE(nid, nvarid, solsw_glo)
915#else
916        ierr = NF_GET_VAR_REAL(nid, nvarid, solsw_glo)
917#endif
918        IF (ierr.NE.NF_NOERR) THEN
919          PRINT*, 'phyetat0: Lecture echouee pour <solsw>'
920          CALL abort
921        ENDIF
922      ENDIF
923      xmin = 1.0E+20
924      xmax = -1.0E+20
925      DO i = 1, klon_glo
926         xmin = MIN(solsw_glo(i),xmin)
927         xmax = MAX(solsw_glo(i),xmax)
928      ENDDO
929      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax
930c
931c Lecture rayonnement IF au sol:
932c
933      ierr = NF_INQ_VARID (nid, "sollw", nvarid)
934      IF (ierr.NE.NF_NOERR) THEN
935         PRINT*, 'phyetat0: Le champ <sollw> est absent'
936         PRINT*, 'mis a zero'
937         sollw_glo = 0.
938      ELSE
939#ifdef NC_DOUBLE
940        ierr = NF_GET_VAR_DOUBLE(nid, nvarid, sollw_glo)
941#else
942        ierr = NF_GET_VAR_REAL(nid, nvarid, sollw_glo)
943#endif
944        IF (ierr.NE.NF_NOERR) THEN
945          PRINT*, 'phyetat0: Lecture echouee pour <sollw>'
946          CALL abort
947        ENDIF
948      ENDIF
949      xmin = 1.0E+20
950      xmax = -1.0E+20
951      DO i = 1, klon_glo
952         xmin = MIN(sollw_glo(i),xmin)
953         xmax = MAX(sollw_glo(i),xmax)
954      ENDDO
955      PRINT*,'Rayonnement IF au sol sollw:', xmin, xmax
956     
957c
958c Lecture derive des flux:
959c
960      ierr = NF_INQ_VARID (nid, "fder", nvarid)
961      IF (ierr.NE.NF_NOERR) THEN
962         PRINT*, 'phyetat0: Le champ <fder> est absent'
963         PRINT*, 'mis a zero'
964         fder = 0.
965      ELSE
966#ifdef NC_DOUBLE
967        ierr = NF_GET_VAR_DOUBLE(nid, nvarid, fder)
968#else
969        ierr = NF_GET_VAR_REAL(nid, nvarid, fder)
970#endif
971        IF (ierr.NE.NF_NOERR) THEN
972          PRINT*, 'phyetat0: Lecture echouee pour <fder>'
973          CALL abort
974        ENDIF
975      ENDIF
976      xmin = 1.0E+20
977      xmax = -1.0E+20
978      DO i = 1, klon_glo
979         xmin = MIN(fder(i),xmin)
980         xmax = MAX(fder(i),xmax)
981      ENDDO
982      PRINT*,'Derive des flux fder:', xmin, xmax
983
984c
985c Lecture du rayonnement net au sol:
986c
987      ierr = NF_INQ_VARID (nid, "RADS", nvarid)
988      IF (ierr.NE.NF_NOERR) THEN
989         PRINT*, 'phyetat0: Le champ <RADS> est absent'
990         CALL abort
991      ENDIF
992#ifdef NC_DOUBLE
993      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, radsol_glo)
994#else
995      ierr = NF_GET_VAR_REAL(nid, nvarid, radsol_glo)
996#endif
997      IF (ierr.NE.NF_NOERR) THEN
998         PRINT*, 'phyetat0: Lecture echouee pour <RADS>'
999         CALL abort
1000      ENDIF
1001      xmin = 1.0E+20
1002      xmax = -1.0E+20
1003      DO i = 1, klon_glo
1004         xmin = MIN(radsol_glo(i),xmin)
1005         xmax = MAX(radsol_glo(i),xmax)
1006      ENDDO
1007      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax
1008c
1009c Lecture de la longueur de rugosite
1010c
1011c
1012      ierr = NF_INQ_VARID (nid, "RUG", nvarid)
1013      IF (ierr.NE.NF_NOERR) THEN
1014         PRINT*, 'phyetat0: Le champ <RUG> est absent'
1015         PRINT*, '          Mais je vais essayer de lire RUG**'
1016         DO nsrf = 1, nbsrf
1017           IF (nsrf.GT.99) THEN
1018             PRINT*, "Trop de sous-mailles"
1019             CALL abort
1020           ENDIF
1021           WRITE(str2,'(i2.2)') nsrf
1022           ierr = NF_INQ_VARID (nid, "RUG"//str2, nvarid)
1023           IF (ierr.NE.NF_NOERR) THEN
1024              PRINT*, "phyetat0: Le champ <RUG"//str2//"> est absent"
1025              CALL abort
1026           ENDIF
1027#ifdef NC_DOUBLE
1028           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, frugs(1,nsrf))
1029#else
1030           ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,nsrf))
1031#endif
1032           IF (ierr.NE.NF_NOERR) THEN
1033             PRINT*, "phyetat0: Lecture echouee pour <RUG"//str2//">"
1034             CALL abort
1035           ENDIF
1036           xmin = 1.0E+20
1037           xmax = -1.0E+20
1038           DO i = 1, klon_glo
1039              xmin = MIN(frugs(i,nsrf),xmin)
1040              xmax = MAX(frugs(i,nsrf),xmax)
1041           ENDDO
1042           PRINT*,'rugosite du sol RUG**:', nsrf, xmin, xmax
1043         ENDDO
1044      ELSE
1045         PRINT*, 'phyetat0: Le champ <RUG> est present'
1046         PRINT*, '          J ignore donc les autres RUG**'
1047#ifdef NC_DOUBLE
1048         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, frugs(1,1))
1049#else
1050         ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,1))
1051#endif
1052         IF (ierr.NE.NF_NOERR) THEN
1053            PRINT*, "phyetat0: Lecture echouee pour <RUG>"
1054            CALL abort
1055         ENDIF
1056         xmin = 1.0E+20
1057         xmax = -1.0E+20
1058         DO i = 1, klon_glo
1059            xmin = MIN(frugs(i,1),xmin)
1060            xmax = MAX(frugs(i,1),xmax)
1061         ENDDO
1062         PRINT*,'rugosite <RUG>', xmin, xmax
1063         DO nsrf = 2, nbsrf
1064         DO i = 1, klon_glo
1065            frugs(i,nsrf) = frugs(i,1)
1066         ENDDO
1067         ENDDO
1068      ENDIF
1069
1070c
1071c Lecture de l'age de la neige:
1072c
1073      ierr = NF_INQ_VARID (nid, "AGESNO", nvarid)
1074      IF (ierr.NE.NF_NOERR) THEN
1075         PRINT*, 'phyetat0: Le champ <AGESNO> est absent'
1076         PRINT*, '          Mais je vais essayer de lire AGESNO**'
1077         DO nsrf = 1, nbsrf
1078           IF (nsrf.GT.99) THEN
1079             PRINT*, "Trop de sous-mailles"
1080             CALL abort
1081           ENDIF
1082           WRITE(str2,'(i2.2)') nsrf
1083           ierr = NF_INQ_VARID (nid, "AGESNO"//str2, nvarid)
1084           IF (ierr.NE.NF_NOERR) THEN
1085              PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
1086              agesno = 50.0
1087           ENDIF
1088#ifdef NC_DOUBLE
1089           ierr = NF_GET_VAR_DOUBLE(nid, nvarid, agesno(1,nsrf))
1090#else
1091           ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,nsrf))
1092#endif
1093           IF (ierr.NE.NF_NOERR) THEN
1094             PRINT*, "phyetat0: Lecture echouee pour <AGESNO"//str2//">"
1095             CALL abort
1096           ENDIF
1097           xmin = 1.0E+20
1098           xmax = -1.0E+20
1099           DO i = 1, klon_glo
1100              xmin = MIN(agesno(i,nsrf),xmin)
1101              xmax = MAX(agesno(i,nsrf),xmax)
1102           ENDDO
1103           PRINT*,'Age de la neige AGESNO**:', nsrf, xmin, xmax
1104         ENDDO
1105      ELSE
1106         PRINT*, 'phyetat0: Le champ <AGESNO> est present'
1107         PRINT*, '          J ignore donc les autres AGESNO**'
1108#ifdef NC_DOUBLE
1109         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, agesno(1,1))
1110#else
1111         ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,1))
1112#endif
1113         IF (ierr.NE.NF_NOERR) THEN
1114            PRINT*, "phyetat0: Lecture echouee pour <AGESNO>"
1115            CALL abort
1116         ENDIF
1117         xmin = 1.0E+20
1118         xmax = -1.0E+20
1119         DO i = 1, klon_glo
1120            xmin = MIN(agesno(i,1),xmin)
1121            xmax = MAX(agesno(i,1),xmax)
1122         ENDDO
1123         PRINT*,'Age de la neige <AGESNO>', xmin, xmax
1124         DO nsrf = 2, nbsrf
1125         DO i = 1, klon_glo
1126            agesno(i,nsrf) = agesno(i,1)
1127         ENDDO
1128         ENDDO
1129      ENDIF
1130
1131c
1132      ierr = NF_INQ_VARID (nid, "ZMEA", nvarid)
1133      IF (ierr.NE.NF_NOERR) THEN
1134         PRINT*, 'phyetat0: Le champ <ZMEA> est absent'
1135         CALL abort
1136      ENDIF
1137#ifdef NC_DOUBLE
1138      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zmea_glo)
1139#else
1140      ierr = NF_GET_VAR_REAL(nid, nvarid, zmea_glo)
1141#endif
1142      IF (ierr.NE.NF_NOERR) THEN
1143         PRINT*, 'phyetat0: Lecture echouee pour <ZMEA>'
1144         CALL abort
1145      ENDIF
1146      xmin = 1.0E+20
1147      xmax = -1.0E+20
1148      DO i = 1, klon_glo
1149         xmin = MIN(zmea_glo(i),xmin)
1150         xmax = MAX(zmea_glo(i),xmax)
1151      ENDDO
1152      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
1153c
1154c
1155      ierr = NF_INQ_VARID (nid, "ZSTD", nvarid)
1156      IF (ierr.NE.NF_NOERR) THEN
1157         PRINT*, 'phyetat0: Le champ <ZSTD> est absent'
1158         CALL abort
1159      ENDIF
1160#ifdef NC_DOUBLE
1161      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zstd_glo)
1162#else
1163      ierr = NF_GET_VAR_REAL(nid, nvarid, zstd_glo)
1164#endif
1165      IF (ierr.NE.NF_NOERR) THEN
1166         PRINT*, 'phyetat0: Lecture echouee pour <ZSTD>'
1167         CALL abort
1168      ENDIF
1169      xmin = 1.0E+20
1170      xmax = -1.0E+20
1171      DO i = 1, klon_glo
1172         xmin = MIN(zstd_glo(i),xmin)
1173         xmax = MAX(zstd_glo(i),xmax)
1174      ENDDO
1175      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
1176c
1177c
1178      ierr = NF_INQ_VARID (nid, "ZSIG", nvarid)
1179      IF (ierr.NE.NF_NOERR) THEN
1180         PRINT*, 'phyetat0: Le champ <ZSIG> est absent'
1181         CALL abort
1182      ENDIF
1183#ifdef NC_DOUBLE
1184      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zsig_glo)
1185#else
1186      ierr = NF_GET_VAR_REAL(nid, nvarid, zsig_glo)
1187#endif
1188      IF (ierr.NE.NF_NOERR) THEN
1189         PRINT*, 'phyetat0: Lecture echouee pour <ZSIG>'
1190         CALL abort
1191      ENDIF
1192      xmin = 1.0E+20
1193      xmax = -1.0E+20
1194      DO i = 1, klon_glo
1195         xmin = MIN(zsig_glo(i),xmin)
1196         xmax = MAX(zsig_glo(i),xmax)
1197      ENDDO
1198      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
1199c
1200c
1201      ierr = NF_INQ_VARID (nid, "ZGAM", nvarid)
1202      IF (ierr.NE.NF_NOERR) THEN
1203         PRINT*, 'phyetat0: Le champ <ZGAM> est absent'
1204         CALL abort
1205      ENDIF
1206#ifdef NC_DOUBLE
1207      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zgam_glo)
1208#else
1209      ierr = NF_GET_VAR_REAL(nid, nvarid, zgam_glo)
1210#endif
1211      IF (ierr.NE.NF_NOERR) THEN
1212         PRINT*, 'phyetat0: Lecture echouee pour <ZGAM>'
1213         CALL abort
1214      ENDIF
1215      xmin = 1.0E+20
1216      xmax = -1.0E+20
1217      DO i = 1, klon_glo
1218         xmin = MIN(zgam_glo(i),xmin)
1219         xmax = MAX(zgam_glo(i),xmax)
1220      ENDDO
1221      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
1222c
1223c
1224      ierr = NF_INQ_VARID (nid, "ZTHE", nvarid)
1225      IF (ierr.NE.NF_NOERR) THEN
1226         PRINT*, 'phyetat0: Le champ <ZTHE> est absent'
1227         CALL abort
1228      ENDIF
1229#ifdef NC_DOUBLE
1230      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zthe_glo)
1231#else
1232      ierr = NF_GET_VAR_REAL(nid, nvarid, zthe_glo)
1233#endif
1234      IF (ierr.NE.NF_NOERR) THEN
1235         PRINT*, 'phyetat0: Lecture echouee pour <ZTHE>'
1236         CALL abort
1237      ENDIF
1238      xmin = 1.0E+20
1239      xmax = -1.0E+20
1240      DO i = 1, klon_glo
1241         xmin = MIN(zthe_glo(i),xmin)
1242         xmax = MAX(zthe_glo(i),xmax)
1243      ENDDO
1244      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
1245c
1246c
1247      ierr = NF_INQ_VARID (nid, "ZPIC", nvarid)
1248      IF (ierr.NE.NF_NOERR) THEN
1249         PRINT*, 'phyetat0: Le champ <ZPIC> est absent'
1250         CALL abort
1251      ENDIF
1252#ifdef NC_DOUBLE
1253      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zpic_glo)
1254#else
1255      ierr = NF_GET_VAR_REAL(nid, nvarid, zpic_glo)
1256#endif
1257      IF (ierr.NE.NF_NOERR) THEN
1258         PRINT*, 'phyetat0: Lecture echouee pour <ZPIC>'
1259         CALL abort
1260      ENDIF
1261      xmin = 1.0E+20
1262      xmax = -1.0E+20
1263      DO i = 1, klon_glo
1264         xmin = MIN(zpic_glo(i),xmin)
1265         xmax = MAX(zpic_glo(i),xmax)
1266      ENDDO
1267      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
1268c
1269      ierr = NF_INQ_VARID (nid, "ZVAL", nvarid)
1270      IF (ierr.NE.NF_NOERR) THEN
1271         PRINT*, 'phyetat0: Le champ <ZVAL> est absent'
1272         CALL abort
1273      ENDIF
1274#ifdef NC_DOUBLE
1275      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zval_glo)
1276#else
1277      ierr = NF_GET_VAR_REAL(nid, nvarid, zval_glo)
1278#endif
1279      IF (ierr.NE.NF_NOERR) THEN
1280         PRINT*, 'phyetat0: Lecture echouee pour <ZVAL>'
1281         CALL abort
1282      ENDIF
1283      xmin = 1.0E+20
1284      xmax = -1.0E+20
1285      DO i = 1, klon_glo
1286         xmin = MIN(zval_glo(i),xmin)
1287         xmax = MAX(zval_glo(i),xmax)
1288      ENDDO
1289      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
1290c
1291c
1292      ierr = NF_INQ_VARID (nid, "RUGSREL", nvarid)
1293      IF (ierr.NE.NF_NOERR) THEN
1294         PRINT*, 'phyetat0: Le champ <RUGSREL> est absent'
1295         CALL abort
1296      ENDIF
1297#ifdef NC_DOUBLE
1298      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, rugsrel_glo)
1299#else
1300      ierr = NF_GET_VAR_REAL(nid, nvarid, rugsrel_glo)
1301#endif
1302      IF (ierr.NE.NF_NOERR) THEN
1303         PRINT*, 'phyetat0: Lecture echouee pour <RUGSREL>'
1304         CALL abort
1305      ENDIF
1306      xmin = 1.0E+20
1307      xmax = -1.0E+20
1308      DO i = 1, klon_glo
1309         xmin = MIN(rugsrel_glo(i),xmin)
1310         xmax = MAX(rugsrel_glo(i),xmax)
1311      ENDDO
1312      PRINT*,'Rugosite relief (ecart-type) rugsrel:', xmin, xmax
1313c
1314c
1315      ancien_ok_glo = .TRUE.
1316c
1317      ierr = NF_INQ_VARID (nid, "TANCIEN", nvarid)
1318      IF (ierr.NE.NF_NOERR) THEN
1319         PRINT*, "phyetat0: Le champ <TANCIEN> est absent"
1320         PRINT*, "Depart legerement fausse. Mais je continue"
1321         ancien_ok_glo = .FALSE.
1322      ELSE
1323#ifdef NC_DOUBLE
1324         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, t_ancien_glo)
1325#else
1326         ierr = NF_GET_VAR_REAL(nid, nvarid, t_ancien_glo)
1327#endif
1328         IF (ierr.NE.NF_NOERR) THEN
1329            PRINT*, "phyetat0: Lecture echouee pour <TANCIEN>"
1330            CALL abort
1331         ENDIF
1332      ENDIF
1333c
1334      ierr = NF_INQ_VARID (nid, "QANCIEN", nvarid)
1335      IF (ierr.NE.NF_NOERR) THEN
1336         PRINT*, "phyetat0: Le champ <QANCIEN> est absent"
1337         PRINT*, "Depart legerement fausse. Mais je continue"
1338         ancien_ok_glo = .FALSE.
1339      ELSE
1340#ifdef NC_DOUBLE
1341         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, q_ancien_glo)
1342#else
1343         ierr = NF_GET_VAR_REAL(nid, nvarid, q_ancien_glo)
1344#endif
1345         IF (ierr.NE.NF_NOERR) THEN
1346            PRINT*, "phyetat0: Lecture echouee pour <QANCIEN>"
1347            CALL abort
1348         ENDIF
1349      ENDIF
1350c
1351      clwcon_glo=0.
1352      ierr = NF_INQ_VARID (nid, "CLWCON", nvarid)
1353      IF (ierr.NE.NF_NOERR) THEN
1354         PRINT*, "phyetat0: Le champ CLWCON est absent"
1355         PRINT*, "Depart legerement fausse. Mais je continue"
1356c        clwcon_glo = 0.
1357      ELSE
1358#ifdef NC_DOUBLE
1359         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, clwcon_glo)
1360#else
1361         ierr = NF_GET_VAR_REAL(nid, nvarid, clwcon_glo)
1362#endif
1363         IF (ierr.NE.NF_NOERR) THEN
1364            PRINT*, "phyetat0: Lecture echouee pour <CLWCON>"
1365            CALL abort
1366         ENDIF
1367      ENDIF
1368      xmin = 1.0E+20
1369      xmax = -1.0E+20
1370      xmin = MINval(clwcon_glo)
1371      xmax = MAXval(clwcon_glo)
1372      PRINT*,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
1373c
1374      rnebcon_glo = 0.
1375      ierr = NF_INQ_VARID (nid, "RNEBCON", nvarid)
1376      IF (ierr.NE.NF_NOERR) THEN
1377         PRINT*, "phyetat0: Le champ RNEBCON est absent"
1378         PRINT*, "Depart legerement fausse. Mais je continue"
1379c        rnebcon_glo = 0.
1380      ELSE
1381#ifdef NC_DOUBLE
1382         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, rnebcon_glo)
1383#else
1384         ierr = NF_GET_VAR_REAL(nid, nvarid, rnebcon_glo)
1385#endif
1386         IF (ierr.NE.NF_NOERR) THEN
1387            PRINT*, "phyetat0: Lecture echouee pour <RNEBCON>"
1388            CALL abort
1389         ENDIF
1390      ENDIF
1391      xmin = 1.0E+20
1392      xmax = -1.0E+20
1393      xmin = MINval(rnebcon_glo)
1394      xmax = MAXval(rnebcon_glo)
1395      PRINT*,'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
1396
1397c
1398c Lecture ratqs
1399c
1400      ratqs_glo=0.
1401      ierr = NF_INQ_VARID (nid, "RATQS", nvarid)
1402      IF (ierr.NE.NF_NOERR) THEN
1403         PRINT*, "phyetat0: Le champ <RATQS> est absent"
1404         PRINT*, "Depart legerement fausse. Mais je continue"
1405         ratqs_glo = 0.
1406      ELSE
1407#ifdef NC_DOUBLE
1408         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ratqs_glo)
1409#else
1410         ierr = NF_GET_VAR_REAL(nid, nvarid, ratqs_glo)
1411#endif
1412         IF (ierr.NE.NF_NOERR) THEN
1413            PRINT*, "phyetat0: Lecture echouee pour <RATQS>"
1414            CALL abort
1415         ENDIF
1416      ENDIF
1417      xmin = 1.0E+20
1418      xmax = -1.0E+20
1419      xmin = MINval(ratqs_glo)
1420      xmax = MAXval(ratqs_glo)
1421      PRINT*,'(ecart-type) ratqs:', xmin, xmax
1422c
1423c Lecture run_off_lic_0
1424c
1425      ierr = NF_INQ_VARID (nid, "RUNOFFLIC0", nvarid)
1426      IF (ierr.NE.NF_NOERR) THEN
1427         PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"
1428         PRINT*, "Depart legerement fausse. Mais je continue"
1429         run_off_lic_0 = 0.
1430      ELSE
1431#ifdef NC_DOUBLE
1432         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, run_off_lic_0)
1433#else
1434         ierr = NF_GET_VAR_REAL(nid, nvarid, run_off_lic_0)
1435#endif
1436         IF (ierr.NE.NF_NOERR) THEN
1437            PRINT*, "phyetat0: Lecture echouee pour <RUNOFFLIC0>"
1438            CALL abort
1439         ENDIF
1440      ENDIF
1441      xmin = 1.0E+20
1442      xmax = -1.0E+20
1443      xmin = MINval(run_off_lic_0)
1444      xmax = MAXval(run_off_lic_0)
1445      PRINT*,'(ecart-type) run_off_lic_0:', xmin, xmax
1446
1447
1448c Lecture de l'energie cinetique turbulente
1449c
1450
1451      IF (iflag_pbl>1) then
1452         PRINT*, 'phyetat0: Le champ <TKE> est absent'
1453         PRINT*, '          Mais je vais essayer de lire TKE**'
1454         DO nsrf = 1, nbsrf
1455           IF (nsrf.GT.99) THEN
1456             PRINT*, "Trop de sous-mailles"
1457             CALL abort
1458           ENDIF
1459           WRITE(str2,'(i2.2)') nsrf
1460           ierr = NF_INQ_VARID (nid, "TKE"//str2, nvarid)
1461           IF (ierr.NE.NF_NOERR) THEN
1462              PRINT*, "WARNING phyetat0: <TKE"//str2//"> est absent"
1463              pbl_tke_glo(:,:,nsrf)=1.e-8
1464           ELSE
1465#ifdef NC_DOUBLE
1466              ierr = NF_GET_VAR_DOUBLE(nid, nvarid,
1467     &                                pbl_tke_glo(1,1,nsrf))
1468#else
1469              ierr = NF_GET_VAR_REAL(nid, nvarid, pbl_tke_glo(1,1,nsrf))
1470#endif
1471              IF (ierr.NE.NF_NOERR) THEN
1472                PRINT*, "WARNING phyetat0: echec lect <TKE"//str2//">"
1473                CALL abort
1474              ENDIF
1475           ENDIF
1476
1477           xmin = 1.0E+20
1478           xmax = -1.0E+20
1479           DO k = 1, klev
1480           DO i = 1, klon_glo
1481              xmin = MIN(pbl_tke_glo(i,k,nsrf),xmin)
1482              xmax = MAX(pbl_tke_glo(i,k,nsrf),xmax)
1483           ENDDO
1484           ENDDO
1485           PRINT*,'Temperature du sol TKE**:', nsrf, xmin, xmax
1486         ENDDO
1487      ENDIF
1488c
1489c zmax0
1490      ierr = NF_INQ_VARID (nid, "ZMAX0", nvarid)
1491      IF (ierr.NE.NF_NOERR) THEN
1492         PRINT*, "phyetat0: Le champ <ZMAX0> est absent"
1493         PRINT*, "Depart legerement fausse. Mais je continue"
1494         zmax0_glo=40.
1495      ELSE
1496#ifdef NC_DOUBLE
1497         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zmax0_glo)
1498#else
1499         ierr = NF_GET_VAR_REAL(nid, nvarid, zmax0_glo)
1500#endif
1501         IF (ierr.NE.NF_NOERR) THEN
1502            PRINT*, "phyetat0: Lecture echouee pour <ZMAX0>"
1503            CALL abort
1504         ENDIF
1505      ENDIF
1506      xmin = 1.0E+20
1507      xmax = -1.0E+20
1508      xmin = MINval(zmax0_glo)
1509      xmax = MAXval(zmax0_glo)
1510      PRINT*,'(ecart-type) zmax0:', xmin, xmax
1511c
1512c           f0(ig)=1.e-5
1513c f0
1514      ierr = NF_INQ_VARID (nid, "f0", nvarid)
1515      IF (ierr.NE.NF_NOERR) THEN
1516         PRINT*, "phyetat0: Le champ <f0> est absent"
1517         PRINT*, "Depart legerement fausse. Mais je continue"
1518         f0_glo=1.e-5
1519      ELSE
1520#ifdef NC_DOUBLE
1521         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, f0_glo)
1522#else
1523         ierr = NF_GET_VAR_REAL(nid, nvarid, f0_glo)
1524#endif
1525         IF (ierr.NE.NF_NOERR) THEN
1526            PRINT*, "phyetat0: Lecture echouee pour <f0>"
1527            CALL abort
1528         ENDIF
1529      ENDIF
1530      xmin = 1.0E+20
1531      xmax = -1.0E+20
1532      xmin = MINval(f0_glo)
1533      xmax = MAXval(f0_glo)
1534      PRINT*,'(ecart-type) f0:', xmin, xmax
1535c
1536c ema_work1
1537c
1538      ierr = NF_INQ_VARID (nid, "EMA_WORK1", nvarid)
1539      IF (ierr.NE.NF_NOERR) THEN
1540         PRINT*, "phyetat0: Le champ <EMA_WORK1> est absent"
1541         PRINT*, "Depart legerement fausse. Mais je continue"
1542         ema_work1_glo=0.
1543      ELSE
1544#ifdef NC_DOUBLE
1545         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ema_work1_glo)
1546#else
1547         ierr = NF_GET_VAR_REAL(nid, nvarid, ema_work1_glo)
1548#endif
1549         IF (ierr.NE.NF_NOERR) THEN
1550            PRINT*, "phyetat0: Lecture echouee pour <EMA_WORK1>"
1551            CALL abort
1552         ENDIF
1553           xmin = 1.0E+20
1554           xmax = -1.0E+20
1555           DO k = 1, klev
1556           DO i = 1, klon
1557              xmin = MIN(ema_work1_glo(i,k),xmin)
1558              xmax = MAX(ema_work1_glo(i,k),xmax)
1559           ENDDO
1560           ENDDO
1561           PRINT*,'ema_work1:', xmin, xmax
1562      ENDIF
1563c
1564c ema_work2
1565c
1566      ierr = NF_INQ_VARID (nid, "EMA_WORK2", nvarid)
1567      IF (ierr.NE.NF_NOERR) THEN
1568         PRINT*, "phyetat0: Le champ <EMA_WORK2> est absent"
1569         PRINT*, "Depart legerement fausse. Mais je continue"
1570         ema_work2_glo=0.
1571      ELSE
1572#ifdef NC_DOUBLE
1573         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ema_work2_glo)
1574#else
1575         ierr = NF_GET_VAR_REAL(nid, nvarid, ema_work2_glo)
1576#endif
1577         IF (ierr.NE.NF_NOERR) THEN
1578            PRINT*, "phyetat0: Lecture echouee pour <EMA_WORK2>"
1579            CALL abort
1580         ENDIF
1581           xmin = 1.0E+20
1582           xmax = -1.0E+20
1583           DO k = 1, klev
1584           DO i = 1, klon
1585              xmin = MIN(ema_work2_glo(i,k),xmin)
1586              xmax = MAX(ema_work2_glo(i,k),xmax)
1587           ENDDO
1588           ENDDO
1589           PRINT*,'ema_work2:', xmin, xmax
1590      ENDIF
1591c
1592c wake_deltat
1593c
1594      ierr = NF_INQ_VARID (nid, "WAKE_DELTAT", nvarid)
1595      IF (ierr.NE.NF_NOERR) THEN
1596         PRINT*, "phyetat0: Le champ <WAKE_DELTAT> est absent"
1597         PRINT*, "Depart legerement fausse. Mais je continue"
1598         wake_deltat_glo=0.
1599      ELSE
1600#ifdef NC_DOUBLE
1601         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, wake_deltat_glo)
1602#else
1603         ierr = NF_GET_VAR_REAL(nid, nvarid, wake_deltat_glo)
1604#endif
1605         IF (ierr.NE.NF_NOERR) THEN
1606            PRINT*, "phyetat0: Lecture echouee pour <WAKE_DELTAT>"
1607            CALL abort
1608         ENDIF
1609           xmin = 1.0E+20
1610           xmax = -1.0E+20
1611           DO k = 1, klev
1612           DO i = 1, klon_glo
1613              xmin = MIN(wake_deltat_glo(i,k),xmin)
1614              xmax = MAX(wake_deltat_glo(i,k),xmax)
1615           ENDDO
1616           ENDDO
1617           PRINT*,'wake_deltat:', xmin, xmax
1618      ENDIF
1619c
1620c wake_deltaq
1621c
1622      ierr = NF_INQ_VARID (nid, "WAKE_DELTAQ", nvarid)
1623      IF (ierr.NE.NF_NOERR) THEN
1624         PRINT*, "phyetat0: Le champ <WAKE_DELTAQ> est absent"
1625         PRINT*, "Depart legerement fausse. Mais je continue"
1626         wake_deltaq_glo=0.
1627      ELSE
1628#ifdef NC_DOUBLE
1629         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, wake_deltaq_glo)
1630#else
1631         ierr = NF_GET_VAR_REAL(nid, nvarid, wake_deltaq_glo)
1632#endif
1633         IF (ierr.NE.NF_NOERR) THEN
1634            PRINT*, "phyetat0: Lecture echouee pour <WAKE_DELTAQ>"
1635            CALL abort
1636         ENDIF
1637           xmin = 1.0E+20
1638           xmax = -1.0E+20
1639           DO k = 1, klev
1640           DO i = 1, klon_glo
1641              xmin = MIN(wake_deltaq_glo(i,k),xmin)
1642              xmax = MAX(wake_deltaq_glo(i,k),xmax)
1643           ENDDO
1644           ENDDO
1645           PRINT*,'wake_deltaq:', xmin, xmax
1646      ENDIF
1647c
1648c wake_s
1649c
1650      ierr = NF_INQ_VARID (nid, "WAKE_S", nvarid)
1651      IF (ierr.NE.NF_NOERR) THEN
1652         PRINT*, "phyetat0: Le champ <WAKE_S> est absent"
1653         PRINT*, "Depart legerement fausse. Mais je continue"
1654         wake_s_glo=0.
1655      ELSE
1656#ifdef NC_DOUBLE
1657         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, wake_s_glo)
1658#else
1659         ierr = NF_GET_VAR_REAL(nid, nvarid, wake_s_glo)
1660#endif
1661         IF (ierr.NE.NF_NOERR) THEN
1662            PRINT*, "phyetat0: Lecture echouee pour <WAKE_S>"
1663            CALL abort
1664         ENDIF
1665      ENDIF
1666      xmin = 1.0E+20
1667      xmax = -1.0E+20
1668      xmin = MINval(wake_s_glo)
1669      xmax = MAXval(wake_s_glo)
1670      PRINT*,'(ecart-type) wake_s:', xmin, xmax
1671c
1672c wake_cstar
1673c
1674      ierr = NF_INQ_VARID (nid, "WAKE_CSTAR", nvarid)
1675      IF (ierr.NE.NF_NOERR) THEN
1676         PRINT*, "phyetat0: Le champ <WAKE_CSTAR> est absent"
1677         PRINT*, "Depart legerement fausse. Mais je continue"
1678         wake_cstar_glo=0.
1679      ELSE
1680#ifdef NC_DOUBLE
1681         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, wake_cstar_glo)
1682#else
1683         ierr = NF_GET_VAR_REAL(nid, nvarid, wake_cstar_glo)
1684#endif
1685         IF (ierr.NE.NF_NOERR) THEN
1686            PRINT*, "phyetat0: Lecture echouee pour <WAKE_CSTAR>"
1687            CALL abort
1688         ENDIF
1689      ENDIF
1690      xmin = 1.0E+20
1691      xmax = -1.0E+20
1692      xmin = MINval(wake_cstar_glo)
1693      xmax = MAXval(wake_cstar_glo)
1694      PRINT*,'(ecart-type) wake_cstar:', xmin, xmax
1695c
1696c wake_fip
1697c
1698      ierr = NF_INQ_VARID (nid, "WAKE_FIP", nvarid)
1699      IF (ierr.NE.NF_NOERR) THEN
1700         PRINT*, "phyetat0: Le champ <WAKE_FIP> est absent"
1701         PRINT*, "Depart legerement fausse. Mais je continue"
1702         wake_fip_glo=0.
1703      ELSE
1704#ifdef NC_DOUBLE
1705         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, wake_fip_glo)
1706#else
1707         ierr = NF_GET_VAR_REAL(nid, nvarid, wake_fip_glo)
1708#endif
1709         IF (ierr.NE.NF_NOERR) THEN
1710            PRINT*, "phyetat0: Lecture echouee pour <WAKE_FIP>"
1711            CALL abort
1712         ENDIF
1713      ENDIF
1714      xmin = 1.0E+20
1715      xmax = -1.0E+20
1716      xmin = MINval(wake_fip_glo)
1717      xmax = MAXval(wake_fip_glo)
1718      PRINT*,'(ecart-type) wake_fip:', xmin, xmax
1719c
1720c Fermer le fichier:
1721c
1722      ierr = NF_CLOSE(nid)
1723      ENDIF ! is_mpi_root .AND. is_omp_root
1724c
1725
1726c$OMP MASTER
1727cym  en attendant mieux
1728        iolat(1)=rlat_glo(1)
1729
1730!FH1D   
1731!iolat(jjm+1)=rlat(klon_glo)
1732        iolat(jjm+1-1/iim)=rlat_glo(klon_glo)
1733        if (iim.gt.1) then
1734        do i=2,jjm
1735          iolat(i)=rlat_glo(2+(i-2)*iim)
1736        enddo
1737        endif
1738
1739        CALL bcast_mpi(iolat)
1740        CALL bcast_mpi(rlon_glo)
1741
1742!FH1D
1743!       call init_iophy(iolat,rlon(2:iim+1))
1744        call init_iophy(iolat,rlon_glo(2-1/iim:iim+1-1/iim))
1745       
1746c$OMP END MASTER
1747       
1748      call Scatter( rlat_glo,rlat)
1749      call Scatter( rlon_glo,rlon)
1750      call Scatter( tsol_glo,ftsol)
1751      IF (iflag_pbl>1) then
1752         call Scatter( pbl_tke_glo,pbl_tke)
1753      endif
1754      call Scatter( zmax0_glo,zmax0)
1755      call Scatter( f0_glo,f0)
1756      call Scatter( ema_work1_glo, ema_work1)
1757      call Scatter( ema_work2_glo, ema_work2)
1758      call Scatter( wake_deltat_glo, wake_deltat)
1759      call Scatter( wake_deltaq_glo, wake_deltaq)
1760      call Scatter( wake_s_glo, wake_s)
1761      call Scatter( wake_cstar_glo, wake_cstar)
1762      call Scatter( wake_fip_glo, wake_fip)
1763      call Scatter( tsoil,tsoil_p)
1764      call Scatter( tslab,tslab_p)
1765      call Scatter( seaice,seaice_p)
1766      call Scatter( qsurf,qsurf_p)
1767      call Scatter( qsol,qsol_p)
1768      call Scatter( snow,snow_p)
1769      call Scatter( alb1_glo,falb1)
1770      call Scatter( alb2_glo,falb2)
1771      call Scatter( evap,evap_p)
1772      call Scatter( radsol_glo,radsol)
1773      call Scatter( rain_fall_glo,rain_fall)
1774      call Scatter( snow_fall_glo,snow_fall)
1775      call Scatter( sollw_glo,sollw)
1776      call Scatter( solsw_glo,solsw)
1777      call Scatter( fder,fder_p)
1778      call Scatter( frugs,frugs_p)
1779      call Scatter( agesno,agesno_p)
1780      call Scatter( zmea_glo,zmea)
1781      call Scatter( zstd_glo,zstd)
1782      call Scatter( zsig_glo,zsig)
1783      call Scatter( zgam_glo,zgam)
1784      call Scatter( zthe_glo,zthe)
1785      call Scatter( zpic_glo,zpic)
1786      call Scatter( zval_glo,zval)
1787      call Scatter( rugsrel_glo,rugoro)
1788      call Scatter( pctsrf_glo,pctsrf)
1789      call Scatter( run_off_lic_0,run_off_lic_0_p)
1790      call Scatter( t_ancien_glo,t_ancien)
1791      call Scatter( q_ancien_glo,q_ancien)
1792      call Scatter( rnebcon_glo,rnebcon)
1793      call Scatter( clwcon_glo,clwcon)
1794      call Scatter( ratqs_glo,ratqs)
1795      call Scatter( zmasq_glo,zmasq)
1796
1797c
1798c Initilalize variables in module surface_data
1799c
1800      ok_veget = ok_veget_in
1801      ocean    = ocean_in
1802c
1803c Initialize module pbl_surface_mod
1804c
1805      CALL pbl_surface_init(qsol_p, fder_p, snow_p, qsurf_p,
1806     $     evap_p, frugs_p, agesno_p, tsoil_p)
1807
1808c Initialize ocean module according to ocean type
1809      IF ( ocean == 'slab' ) THEN
1810c        initilalize module ocean_slab_init
1811         CALL ocean_slab_init(dtime, tslab_p, seaice_p, pctsrf)
1812      ELSEIF ( ocean == 'couple' ) THEN
1813c        initilalize module ocean_cpl_init
1814         CALL ocean_cpl_init(dtime, rlon, rlat)
1815      ELSE
1816c        initilalize module ocean_forced_init
1817         CALL ocean_forced_init
1818      ENDIF
1819c
1820c Initilialize module fonte_neige_mod     
1821c
1822      CALL fonte_neige_init(run_off_lic_0_p)
1823
1824
1825      RETURN
1826      END
Note: See TracBrowser for help on using the repository browser.