source: LMDZ4/tags/Merge_V3_conv/libf/phylmd/phyetat0.F @ 1399

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

Merge entre la version V3_conv et le HEAD
YM, JG, LF

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