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

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

La latitude du pole nord n'est pas bien initialisee
LF

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