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

Last change on this file since 967 was 967, checked in by Laurent Fairhead, 17 years ago

Pour des raisons pratiques (besoin de tester facilement les parametrisations
physiques en 1D et 3D), les arguments des routines de lecture et d'ecriture
de l'etat initial de la physique ont disparu des appels à ces routines et sont
maintenant passés par le module phys_state_var_mod
LF

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