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

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

Encore quelques bugs consecutifs au renommage des variables YM
LF

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