source: lmdz_wrf/trunk/WRFV3/lmdz/phyetat0.F90 @ 354

Last change on this file since 354 was 186, checked in by lfita, 10 years ago

Removing checking printings

File size: 36.7 KB
Line 
1!
2! $Id: phyetat0.F 1795 2013-07-18 08:20:28Z emillour $
3!
4!c
5!c
6      SUBROUTINE phyetat0 (fichnom,                                                  &
7       &           clesphy0,                                                         &
8       &           tabcntr0)
9
10      USE dimphy
11      USE mod_grid_phy_lmdz
12      USE mod_phys_lmdz_para
13      USE iophy
14      USE ocean_cpl_mod,    ONLY : ocean_cpl_init
15      USE fonte_neige_mod,  ONLY : fonte_neige_init
16      USE pbl_surface_mod,  ONLY : pbl_surface_init
17      USE surface_data,     ONLY : type_ocean
18      USE phys_state_var_mod
19      USE iostart
20      USE write_field_phy
21      USE infotrac
22      USE traclmdz_mod,    ONLY : traclmdz_from_restart
23      USE carbon_cycle_mod,ONLY :                                                    &
24       &     carbon_cycle_tr, carbon_cycle_cpl, co2_send
25      USE indice_sol_mod
26!L. Fita. August, 2013
27      USE netcdf
28
29      IMPLICIT none
30!c======================================================================
31!c Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
32!c Objet: Lecture de l'etat initial pour la physique
33!c======================================================================
34#include "dimensions.h"
35!L. Fita. August, 2013
36!#include "netcdf.inc"
37#include "dimsoil.h"
38#include "clesphys.h"
39#include "temps.h"
40#include "thermcell.h"
41#include "compbl.h"
42!c======================================================================
43      CHARACTER*(*) fichnom
44
45!c les variables globales lues dans le fichier restart
46
47      REAL tsoil(klon,nsoilmx,nbsrf)
48      REAL tslab(klon), seaice(klon)
49      REAL qsurf(klon,nbsrf)
50      REAL qsol(klon)
51      REAL snow(klon,nbsrf)
52      REAL evap(klon,nbsrf)
53      real fder(klon)
54      REAL frugs(klon,nbsrf)
55      REAL agesno(klon,nbsrf)
56      REAL run_off_lic_0(klon)
57      REAL fractint(klon)
58      REAL trs(klon,nbtr)
59
60      CHARACTER*6 ocean_in
61      LOGICAL ok_veget_in
62
63      INTEGER        longcles
64      PARAMETER    ( longcles = 20 )
65      REAL clesphy0( longcles )
66!c
67      REAL xmin, xmax
68!c
69      INTEGER nid, nvarid
70      INTEGER ierr, i, nsrf, isoil ,k
71      INTEGER length
72      PARAMETER (length=100)
73      INTEGER it, iiq
74      REAL tab_cntrl(length), tabcntr0(length)
75      CHARACTER*7 str7
76      CHARACTER*2 str2
77      LOGICAL :: found
78
79!c FH1D
80!c     real iolat(jjm+1)
81      real iolat(jjm+1-1/(iim*jjm))
82
83!L. Fita, LMDZ March 2014. Removing reading of initial conditions
84      LOGICAL read_flag
85
86      read_flag=.FALSE.
87
88!c
89!c Ouvrir le fichier contenant l'etat initial:
90!c
91!                                                                                     &
92!       &      CALL open_startphy(fichnom)
93     
94
95!c
96!c Lecture des parametres de controle:
97!c
98!      CALL get_var("controle",tab_cntrl)
99       
100!c
101!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
102! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
103! Les constantes de la physiques sont lues dans la physique seulement.
104! Les egalites du type
105!             tab_cntrl( 5 )=clesphy0(1)
106! sont remplacees par
107!             clesphy0(1)=tab_cntrl( 5 )
108! On inverse aussi la logique.
109! On remplit les tab_cntrl avec les parametres lus dans les .def
110!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
111
112         DO i = 1, length
113           tabcntr0( i ) = tab_cntrl( i )
114         ENDDO
115!c
116         tab_cntrl(1)=dtime
117         tab_cntrl(2)=radpas
118
119!c co2_ppm : value from the previous time step
120         IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
121            co2_ppm = tab_cntrl(3)
122            RCO2    = co2_ppm * 1.0e-06  * 44.011/28.97
123!c ELSE : keep value from .def
124         END IF
125
126!c co2_ppm0 : initial value of atmospheric CO2 (from create_etat0_limit.e .def)
127         co2_ppm0   = tab_cntrl(16)
128
129         solaire_etat0      = tab_cntrl(4)
130         tab_cntrl(5)=iflag_con
131         tab_cntrl(6)=nbapp_rad
132
133         if (cycle_diurne) tab_cntrl( 7) =1.
134         if (soil_model) tab_cntrl( 8) =1.
135         if (new_oliq) tab_cntrl( 9) =1.
136         if (ok_orodr) tab_cntrl(10) =1.
137         if (ok_orolf) tab_cntrl(11) =1.
138         if (ok_limitvrai) tab_cntrl(12) =1.
139
140
141      itau_phy = tab_cntrl(15)
142
143       
144      clesphy0(1)=tab_cntrl( 5 )
145      clesphy0(2)=tab_cntrl( 6 )
146      clesphy0(3)=tab_cntrl( 7 )
147      clesphy0(4)=tab_cntrl( 8 )
148      clesphy0(5)=tab_cntrl( 9 )
149      clesphy0(6)=tab_cntrl( 10 )
150      clesphy0(7)=tab_cntrl( 11 )
151      clesphy0(8)=tab_cntrl( 12 )
152
153! L. Fita, LMD. March 2014. Removing adquisition of the variables
154      reading_file: IF (read_flag) THEN
155
156!c
157!c Lecture des latitudes (coordonnees):
158!c
159! L. Fita, LMD. November 2013. Removing adquisition of the variables
160!!      CALL get_field("latitude",rlat)
161
162!c
163!c Lecture des longitudes (coordonnees):
164!c
165! L. Fita, LMD. November 2013. Removing adquisition of the variables
166!!      CALL get_field("longitude",rlon)
167
168!C
169!C
170!C Lecture du masque terre mer
171!C
172! L. Fita, LMD. November 2013. Removing adquisition of the variables
173!!      CALL get_field("masque",zmasq,found)
174      found=.True.
175      IF (.NOT. found) THEN
176        PRINT*, 'phyetat0: Le champ <masque> est absent'
177        PRINT *, 'fichier startphy non compatible avec phyetat0'
178      ENDIF
179
180       
181!C Lecture des fractions pour chaque sous-surface
182!C
183!C initialisation des sous-surfaces
184!C
185! L. Fita, LMD. November 2013. Removing adquisition of the variables
186!      pctsrf = 0.
187!C
188!C fraction de terre
189!C
190
191! L. Fita, LMD. November 2013. Removing adquisition of the variables
192!!      CALL get_field("FTER",pctsrf(:,is_ter),found)
193      IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FTER> est absent'
194
195!C
196!C fraction de glace de terre
197!C
198! L. Fita, LMD. November 2013. Removing adquisition of the variables
199!!      CALL get_field("FLIC",pctsrf(:,is_lic),found)
200      IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FLIC> est absent'
201
202!C
203!C fraction d'ocean
204!C
205! L. Fita, LMD. November 2013. Removing adquisition of the variables
206!!      CALL get_field("FOCE",pctsrf(:,is_oce),found)
207      IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FOCE> est absent'
208
209!C
210!C fraction glace de mer
211!C
212! L. Fita, LMD. November 2013. Removing adquisition of the variables
213!!      CALL get_field("FSIC",pctsrf(:,is_sic),found)
214      IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FSIC> est absent'
215
216!C
217!C  Verification de l'adequation entre le masque et les sous-surfaces
218!C
219      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)                                 &
220       &    + pctsrf(1 : klon, is_lic)
221      DO i = 1 , klon
222        IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN
223            WRITE(*,*) 'phyetat0: attention fraction terre pas ',                    &
224       &          'coherente ', i, zmasq(i), pctsrf(i, is_ter)                       &
225       &          ,pctsrf(i, is_lic)
226            WRITE(*,*) 'Je force la coherence zmasq=fractint'
227            zmasq(i) = fractint(i)
228        ENDIF
229      END DO
230      fractint (1 : klon) =  pctsrf(1 : klon, is_oce)                                &
231       &    + pctsrf(1 : klon, is_sic)
232      DO i = 1 , klon
233        IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN
234            WRITE(*,*) 'phyetat0 attention fraction ocean pas ',                     &
235       &          'coherente ', i, zmasq(i) , pctsrf(i, is_oce)                      &
236       &          ,pctsrf(i, is_sic)
237            WRITE(*,*) 'Je force la coherence zmasq=fractint'
238            zmasq(i) = fractint(i)
239        ENDIF
240      END DO
241
242!C
243!c Lecture des temperatures du sol:
244!c
245
246! L. Fita, LMD. November 2013. Removing adquisition of the variables
247!!       CALL get_field("TS",ftsol(:,1),found)
248       IF (.NOT. found) THEN
249         PRINT*, 'phyetat0: Le champ <TS> est absent'
250         PRINT*, '          Mais je vais essayer de lire TS**'
251         DO nsrf = 1, nbsrf
252           IF (nsrf.GT.99) THEN
253             PRINT*, "Trop de sous-mailles"
254             CALL abort
255           ENDIF
256           WRITE(str2,'(i2.2)') nsrf
257! L. Fita, LMD. November 2013. Removing adquisition of the variables
258!!           CALL get_field("TS"//str2,ftsol(:,nsrf))
259
260           xmin = 1.0E+20
261           xmax = -1.0E+20
262           DO i = 1, klon
263              xmin = MIN(ftsol(i,nsrf),xmin)
264              xmax = MAX(ftsol(i,nsrf),xmax)
265           ENDDO
266           PRINT*,'Temperature du sol TS**:', nsrf, xmin, xmax
267         ENDDO
268      ELSE
269         PRINT*, 'phyetat0: Le champ <TS> est present'
270         PRINT*, '          J ignore donc les autres temperatures TS**'
271         xmin = 1.0E+20
272         xmax = -1.0E+20
273         DO i = 1, klon
274            xmin = MIN(ftsol(i,1),xmin)
275            xmax = MAX(ftsol(i,1),xmax)
276         ENDDO
277         PRINT*,'Temperature du sol <TS>', xmin, xmax
278         DO nsrf = 2, nbsrf
279         DO i = 1, klon
280            ftsol(i,nsrf) = ftsol(i,1)
281         ENDDO
282         ENDDO
283      ENDIF
284
285!c
286!c Lecture des temperatures du sol profond:
287!c
288      DO nsrf = 1, nbsrf
289        DO isoil=1, nsoilmx
290          IF (isoil.GT.99 .AND. nsrf.GT.99) THEN
291            PRINT*, "Trop de couches ou sous-mailles"
292            CALL abort
293          ENDIF
294          WRITE(str7,'(i2.2,"srf",i2.2)') isoil, nsrf
295         
296! L. Fita, LMD. November 2013. Removing adquisition of the variables
297!!          CALL get_field('Tsoil'//str7,tsoil(:,isoil,nsrf),found)
298          IF (.NOT. found) THEN
299            PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
300            PRINT*, "          Il prend donc la valeur de surface"
301            DO i=1, klon
302               tsoil(i,isoil,nsrf)=ftsol(i,nsrf)
303            ENDDO
304          ENDIF
305        ENDDO
306      ENDDO
307!c
308!c Lecture de l'humidite de l'air juste au dessus du sol:
309!c
310
311! L. Fita, LMD. November 2013. Removing adquisition of the variables
312!!      CALL get_field("QS",qsurf(:,1),found)
313      IF (.NOT. found) THEN
314         PRINT*, 'phyetat0: Le champ <QS> est absent'
315         PRINT*, '          Mais je vais essayer de lire QS**'
316         DO nsrf = 1, nbsrf
317           IF (nsrf.GT.99) THEN
318             PRINT*, "Trop de sous-mailles"
319             CALL abort
320           ENDIF
321           WRITE(str2,'(i2.2)') nsrf
322! L. Fita, LMD. November 2013. Removing adquisition of the variables
323!!           CALL get_field("QS"//str2,qsurf(:,nsrf))
324           xmin = 1.0E+20
325           xmax = -1.0E+20
326           DO i = 1, klon
327              xmin = MIN(qsurf(i,nsrf),xmin)
328              xmax = MAX(qsurf(i,nsrf),xmax)
329           ENDDO
330           PRINT*,'Humidite pres du sol QS**:', nsrf, xmin, xmax
331         ENDDO
332      ELSE
333         PRINT*, 'phyetat0: Le champ <QS> est present'
334         PRINT*, '          J ignore donc les autres humidites QS**'
335         xmin = 1.0E+20
336         xmax = -1.0E+20
337         DO i = 1, klon
338            xmin = MIN(qsurf(i,1),xmin)
339            xmax = MAX(qsurf(i,1),xmax)
340         ENDDO
341         PRINT*,'Humidite pres du sol <QS>', xmin, xmax
342         DO nsrf = 2, nbsrf
343           DO i = 1, klon
344             qsurf(i,nsrf) = qsurf(i,1)
345           ENDDO
346         ENDDO
347      ENDIF
348
349!C
350!C Eau dans le sol (pour le modele de sol "bucket")
351!C
352! L. Fita, LMD. November 2013. Removing adquisition of the variables
353!!      CALL get_field("QSOL",qsol,found)
354      IF (.NOT. found) THEN
355        PRINT*, 'phyetat0: Le champ <QSOL> est absent'
356        PRINT*, '          Valeur par defaut nulle'
357          qsol(:)=0.
358      ENDIF
359
360      xmin = 1.0E+20
361      xmax = -1.0E+20
362      DO i = 1, klon
363        xmin = MIN(qsol(i),xmin)
364        xmax = MAX(qsol(i),xmax)
365      ENDDO
366      PRINT*,'Eau dans le sol (mm) <QSOL>', xmin, xmax
367
368!c
369!c Lecture de neige au sol:
370!c
371
372! L. Fita, LMD. November 2013. Removing adquisition of the variables
373!!      CALL get_field("SNOW",snow(:,1),found)
374      IF (.NOT. found) THEN
375        PRINT*, 'phyetat0: Le champ <SNOW> est absent'
376        PRINT*, '          Mais je vais essayer de lire SNOW**'
377        DO nsrf = 1, nbsrf
378          IF (nsrf.GT.99) THEN
379            PRINT*, "Trop de sous-mailles"
380            CALL abort
381          ENDIF
382          WRITE(str2,'(i2.2)') nsrf
383! L. Fita, LMD. November 2013. Removing adquisition of the variables
384!!          CALL get_field( "SNOW"//str2,snow(:,nsrf))
385          xmin = 1.0E+20
386          xmax = -1.0E+20
387          DO i = 1, klon
388            xmin = MIN(snow(i,nsrf),xmin)
389            xmax = MAX(snow(i,nsrf),xmax)
390          ENDDO
391          PRINT*,'Neige du sol SNOW**:', nsrf, xmin, xmax
392        ENDDO
393      ELSE
394         PRINT*, 'phyetat0: Le champ <SNOW> est present'
395         PRINT*, '          J ignore donc les autres neiges SNOW**'
396         xmin = 1.0E+20
397         xmax = -1.0E+20
398         DO i = 1, klon
399            xmin = MIN(snow(i,1),xmin)
400            xmax = MAX(snow(i,1),xmax)
401         ENDDO
402         PRINT*,'Neige du sol <SNOW>', xmin, xmax
403         DO nsrf = 2, nbsrf
404         DO i = 1, klon
405            snow(i,nsrf) = snow(i,1)
406         ENDDO
407         ENDDO
408      ENDIF
409!c
410!c Lecture de albedo de l'interval visible au sol:
411!c
412! L. Fita, LMD. November 2013. Removing adquisition of the variables
413!!      CALL get_field("ALBE",falb1(:,1),found)
414      IF (.NOT. found) THEN
415         PRINT*, 'phyetat0: Le champ <ALBE> est absent'
416         PRINT*, '          Mais je vais essayer de lire ALBE**'
417         DO nsrf = 1, nbsrf
418           IF (nsrf.GT.99) THEN
419             PRINT*, "Trop de sous-mailles"
420             CALL abort
421           ENDIF
422           WRITE(str2,'(i2.2)') nsrf
423! L. Fita, LMD. November 2013. Removing adquisition of the variables
424!!           CALL get_field("ALBE"//str2,falb1(:,nsrf))
425           xmin = 1.0E+20
426           xmax = -1.0E+20
427           DO i = 1, klon
428              xmin = MIN(falb1(i,nsrf),xmin)
429              xmax = MAX(falb1(i,nsrf),xmax)
430           ENDDO
431           PRINT*,'Albedo du sol ALBE**:', nsrf, xmin, xmax
432         ENDDO
433      ELSE
434         PRINT*, 'phyetat0: Le champ <ALBE> est present'
435         PRINT*, '          J ignore donc les autres ALBE**'
436         xmin = 1.0E+20
437         xmax = -1.0E+20
438         DO i = 1, klon
439            xmin = MIN(falb1(i,1),xmin)
440            xmax = MAX(falb1(i,1),xmax)
441         ENDDO
442         PRINT*,'Neige du sol <ALBE>', xmin, xmax
443         DO nsrf = 2, nbsrf
444           DO i = 1, klon
445            falb1(i,nsrf) = falb1(i,1)
446           ENDDO
447         ENDDO
448      ENDIF
449
450!c
451!c Lecture de albedo au sol dans l'interval proche infra-rouge:
452!c
453! L. Fita, LMD. November 2013. Removing adquisition of the variables
454!!      CALL get_field("ALBLW",falb2(:,1),found)
455      IF (.NOT. found) THEN
456         PRINT*, 'phyetat0: Le champ <ALBLW> est absent'
457         PRINT*, '          Mais je vais prendre ALBE**'
458         DO nsrf = 1, nbsrf
459           DO i = 1, klon
460             falb2(i,nsrf) = falb1(i,nsrf)
461           ENDDO
462         ENDDO
463      ELSE
464         PRINT*, 'phyetat0: Le champ <ALBLW> est present'
465         PRINT*, '          J ignore donc les autres ALBLW**'
466         xmin = 1.0E+20
467         xmax = -1.0E+20
468         DO i = 1, klon
469            xmin = MIN(falb2(i,1),xmin)
470            xmax = MAX(falb2(i,1),xmax)
471         ENDDO
472         PRINT*,'Neige du sol <ALBLW>', xmin, xmax
473         DO nsrf = 2, nbsrf
474           DO i = 1, klon
475             falb2(i,nsrf) = falb2(i,1)
476           ENDDO
477         ENDDO
478      ENDIF
479!c
480!c Lecture de evaporation: 
481!c
482! L. Fita, LMD. November 2013. Removing adquisition of the variables
483!!      CALL get_field("EVAP",evap(:,1),found)
484      IF (.NOT. found) THEN
485         PRINT*, 'phyetat0: Le champ <EVAP> est absent'
486         PRINT*, '          Mais je vais essayer de lire EVAP**'
487         DO nsrf = 1, nbsrf
488           IF (nsrf.GT.99) THEN
489             PRINT*, "Trop de sous-mailles"
490             CALL abort
491           ENDIF
492           WRITE(str2,'(i2.2)') nsrf
493! L. Fita, LMD. November 2013. Removing adquisition of the variables
494!!           CALL get_field("EVAP"//str2, evap(:,nsrf))
495           xmin = 1.0E+20
496           xmax = -1.0E+20
497           DO i = 1, klon
498              xmin = MIN(evap(i,nsrf),xmin)
499              xmax = MAX(evap(i,nsrf),xmax)
500           ENDDO
501           PRINT*,'evap du sol EVAP**:', nsrf, xmin, xmax
502         ENDDO
503      ELSE
504         PRINT*, 'phyetat0: Le champ <EVAP> est present'
505         PRINT*, '          J ignore donc les autres EVAP**'
506         xmin = 1.0E+20
507         xmax = -1.0E+20
508         DO i = 1, klon
509            xmin = MIN(evap(i,1),xmin)
510            xmax = MAX(evap(i,1),xmax)
511         ENDDO
512         PRINT*,'Evap du sol <EVAP>', xmin, xmax
513         DO nsrf = 2, nbsrf
514         DO i = 1, klon
515            evap(i,nsrf) = evap(i,1)
516         ENDDO
517         ENDDO
518      ENDIF
519!c
520!c Lecture precipitation liquide:
521!c
522! L. Fita, LMD. November 2013. Removing adquisition of the variables
523!!      CALL get_field("rain_f",rain_fall)
524      xmin = 1.0E+20
525      xmax = -1.0E+20
526      DO i = 1, klon
527         xmin = MIN(rain_fall(i),xmin)
528         xmax = MAX(rain_fall(i),xmax)
529      ENDDO
530      PRINT*,'Precipitation liquide rain_f:', xmin, xmax
531!c
532!c Lecture precipitation solide:
533!c
534! L. Fita, LMD. November 2013. Removing adquisition of the variables
535!!      CALL get_field("snow_f",snow_fall)
536      xmin = 1.0E+20
537      xmax = -1.0E+20
538      DO i = 1, klon
539         xmin = MIN(snow_fall(i),xmin)
540         xmax = MAX(snow_fall(i),xmax)
541      ENDDO
542      PRINT*,'Precipitation solide snow_f:', xmin, xmax
543!c
544!c Lecture rayonnement solaire au sol:
545!c
546! L. Fita, LMD. November 2013. Removing adquisition of the variables
547!!      CALL get_field("solsw",solsw,found)
548      IF (.NOT. found) THEN
549         PRINT*, 'phyetat0: Le champ <solsw> est absent'
550         PRINT*, 'mis a zero'
551         solsw(:) = 0.
552      ENDIF
553      xmin = 1.0E+20
554      xmax = -1.0E+20
555      DO i = 1, klon
556         xmin = MIN(solsw(i),xmin)
557         xmax = MAX(solsw(i),xmax)
558      ENDDO
559      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax
560!c
561!c Lecture rayonnement IF au sol:
562!c
563! L. Fita, LMD. November 2013. Removing adquisition of the variables
564!!      CALL get_field("sollw",sollw,found)
565      IF (.NOT. found) THEN
566         PRINT*, 'phyetat0: Le champ <sollw> est absent'
567         PRINT*, 'mis a zero'
568         sollw = 0.
569      ENDIF
570      xmin = 1.0E+20
571      xmax = -1.0E+20
572      DO i = 1, klon
573         xmin = MIN(sollw(i),xmin)
574         xmax = MAX(sollw(i),xmax)
575      ENDDO
576      PRINT*,'Rayonnement IF au sol sollw:', xmin, xmax
577     
578!c
579!c Lecture derive des flux:
580!c
581! L. Fita, LMD. November 2013. Removing adquisition of the variables
582!!      CALL get_field("fder",fder,found)
583      IF (.NOT. found) THEN
584         PRINT*, 'phyetat0: Le champ <fder> est absent'
585         PRINT*, 'mis a zero'
586         fder = 0.
587      ENDIF
588      xmin = 1.0E+20
589      xmax = -1.0E+20
590      DO i = 1, klon
591         xmin = MIN(fder(i),xmin)
592         xmax = MAX(fder(i),xmax)
593      ENDDO
594      PRINT*,'Derive des flux fder:', xmin, xmax
595
596!c
597!c Lecture du rayonnement net au sol:
598!c
599! L. Fita, LMD. November 2013. Removing adquisition of the variables
600!!      CALL get_field("RADS",radsol)
601      xmin = 1.0E+20
602      xmax = -1.0E+20
603      DO i = 1, klon
604         xmin = MIN(radsol(i),xmin)
605         xmax = MAX(radsol(i),xmax)
606      ENDDO
607      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax
608!c
609!c Lecture de la longueur de rugosite
610!c
611!c
612! L. Fita, LMD. November 2013. Removing adquisition of the variables
613!!      CALL get_field("RUG",frugs(:,1),found)
614      IF (.NOT. found) THEN
615         PRINT*, 'phyetat0: Le champ <RUG> est absent'
616         PRINT*, '          Mais je vais essayer de lire RUG**'
617         DO nsrf = 1, nbsrf
618           IF (nsrf.GT.99) THEN
619             PRINT*, "Trop de sous-mailles"
620             CALL abort
621           ENDIF
622           WRITE(str2,'(i2.2)') nsrf
623! L. Fita, LMD. November 2013. Removing adquisition of the variables
624!!           CALL get_field("RUG"//str2,frugs(:,nsrf))
625           xmin = 1.0E+20
626           xmax = -1.0E+20
627           DO i = 1, klon
628              xmin = MIN(frugs(i,nsrf),xmin)
629              xmax = MAX(frugs(i,nsrf),xmax)
630           ENDDO
631           PRINT*,'rugosite du sol RUG**:', nsrf, xmin, xmax
632         ENDDO
633      ELSE
634         PRINT*, 'phyetat0: Le champ <RUG> est present'
635         PRINT*, '          J ignore donc les autres RUG**'
636         xmin = 1.0E+20
637         xmax = -1.0E+20
638         DO i = 1, klon
639            xmin = MIN(frugs(i,1),xmin)
640            xmax = MAX(frugs(i,1),xmax)
641         ENDDO
642         PRINT*,'rugosite <RUG>', xmin, xmax
643         DO nsrf = 2, nbsrf
644         DO i = 1, klon
645            frugs(i,nsrf) = frugs(i,1)
646         ENDDO
647         ENDDO
648      ENDIF
649
650!c
651!c Lecture de l'age de la neige:
652!c
653! L. Fita, LMD. November 2013. Removing adquisition of the variables
654!!      CALL get_field("AGESNO",agesno(:,1),found)
655      IF (.NOT. found) THEN
656         PRINT*, 'phyetat0: Le champ <AGESNO> est absent'
657         PRINT*, '          Mais je vais essayer de lire AGESNO**'
658         DO nsrf = 1, nbsrf
659           IF (nsrf.GT.99) THEN
660             PRINT*, "Trop de sous-mailles"
661             CALL abort
662           ENDIF
663           WRITE(str2,'(i2.2)') nsrf
664! L. Fita, LMD. November 2013. Removing adquisition of the variables
665!!           CALL get_field("AGESNO"//str2,agesno(:,nsrf),found)
666           IF (.NOT. found) THEN
667              PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
668              agesno = 50.0
669           ENDIF
670           xmin = 1.0E+20
671           xmax = -1.0E+20
672           DO i = 1, klon
673              xmin = MIN(agesno(i,nsrf),xmin)
674              xmax = MAX(agesno(i,nsrf),xmax)
675           ENDDO
676           PRINT*,'Age de la neige AGESNO**:', nsrf, xmin, xmax
677         ENDDO
678      ELSE
679         PRINT*, 'phyetat0: Le champ <AGESNO> est present'
680         PRINT*, '          J ignore donc les autres AGESNO**'
681         xmin = 1.0E+20
682         xmax = -1.0E+20
683         DO i = 1, klon
684            xmin = MIN(agesno(i,1),xmin)
685            xmax = MAX(agesno(i,1),xmax)
686         ENDDO
687         PRINT*,'Age de la neige <AGESNO>', xmin, xmax
688         DO nsrf = 2, nbsrf
689         DO i = 1, klon
690            agesno(i,nsrf) = agesno(i,1)
691         ENDDO
692         ENDDO
693      ENDIF
694
695!c
696! L. Fita, LMD. November 2013. Removing adquisition of the variables
697!!      CALL get_field("ZMEA", zmea)
698      xmin = 1.0E+20
699      xmax = -1.0E+20
700      DO i = 1, klon
701         xmin = MIN(zmea(i),xmin)
702         xmax = MAX(zmea(i),xmax)
703      ENDDO
704      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
705!c
706!c
707! L. Fita, LMD. November 2013. Removing adquisition of the variables
708!!      CALL get_field("ZSTD",zstd)
709      xmin = 1.0E+20
710      xmax = -1.0E+20
711      DO i = 1, klon
712         xmin = MIN(zstd(i),xmin)
713         xmax = MAX(zstd(i),xmax)
714      ENDDO
715      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
716!c
717!c
718! L. Fita, LMD. November 2013. Removing adquisition of the variables
719!!      CALL get_field("ZSIG",zsig)
720      xmin = 1.0E+20
721      xmax = -1.0E+20
722      DO i = 1, klon
723         xmin = MIN(zsig(i),xmin)
724         xmax = MAX(zsig(i),xmax)
725      ENDDO
726      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
727!c
728!c
729! L. Fita, LMD. November 2013. Removing adquisition of the variables
730!!      CALL get_field("ZGAM",zgam)
731      xmin = 1.0E+20
732      xmax = -1.0E+20
733      DO i = 1, klon
734         xmin = MIN(zgam(i),xmin)
735         xmax = MAX(zgam(i),xmax)
736      ENDDO
737      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
738!c
739!c
740! L. Fita, LMD. November 2013. Removing adquisition of the variables
741!!      CALL get_field("ZTHE",zthe)
742      xmin = 1.0E+20
743      xmax = -1.0E+20
744      DO i = 1, klon
745         xmin = MIN(zthe(i),xmin)
746         xmax = MAX(zthe(i),xmax)
747      ENDDO
748      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
749!c
750!c
751! L. Fita, LMD. November 2013. Removing adquisition of the variables
752!!      CALL get_field("ZPIC",zpic)
753      xmin = 1.0E+20
754      xmax = -1.0E+20
755      DO i = 1, klon
756         xmin = MIN(zpic(i),xmin)
757         xmax = MAX(zpic(i),xmax)
758      ENDDO
759      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
760!c
761! L. Fita, LMD. November 2013. Removing adquisition of the variables
762!!      CALL get_field("ZVAL",zval)
763      xmin = 1.0E+20
764      xmax = -1.0E+20
765      DO i = 1, klon
766         xmin = MIN(zval(i),xmin)
767         xmax = MAX(zval(i),xmax)
768      ENDDO
769      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
770!c
771!c
772! L. Fita, LMD. November 2013. Removing adquisition of the variables
773!!      CALL get_field("RUGSREL",rugoro)
774      xmin = 1.0E+20
775      xmax = -1.0E+20
776      DO i = 1, klon
777         xmin = MIN(rugoro(i),xmin)
778         xmax = MAX(rugoro(i),xmax)
779      ENDDO
780      PRINT*,'Rugosite relief (ecart-type) rugsrel:', xmin, xmax
781!c
782!c                                                                                   &
783       &!c
784      ancien_ok = .TRUE.
785
786! L. Fita, LMD. November 2013. Removing adquisition of the variables
787!!      CALL get_field("TANCIEN",t_ancien,found)
788      IF (.NOT. found) THEN
789         PRINT*, "phyetat0: Le champ <TANCIEN> est absent"
790         PRINT*, "Depart legerement fausse. Mais je continue"
791         ancien_ok = .FALSE.
792      ENDIF
793
794
795! L. Fita, LMD. November 2013. Removing adquisition of the variables
796!!      CALL get_field("QANCIEN",q_ancien,found)
797      IF (.NOT. found) THEN
798         PRINT*, "phyetat0: Le champ <QANCIEN> est absent"
799         PRINT*, "Depart legerement fausse. Mais je continue"
800         ancien_ok = .FALSE.
801      ENDIF
802
803! L. Fita, LMD. November 2013. Removing adquisition of the variables
804!!      CALL get_field("UANCIEN",u_ancien,found)
805      IF (.NOT. found) THEN
806         PRINT*, "phyetat0: Le champ <UANCIEN> est absent"
807         PRINT*, "Depart legerement fausse. Mais je continue"
808         ancien_ok = .FALSE.
809      ENDIF
810
811! L. Fita, LMD. November 2013. Removing adquisition of the variables
812!!      CALL get_field("VANCIEN",v_ancien,found)
813      IF (.NOT. found) THEN
814         PRINT*, "phyetat0: Le champ <VANCIEN> est absent"
815         PRINT*, "Depart legerement fausse. Mais je continue"
816         ancien_ok = .FALSE.
817      ENDIF
818
819! L. Fita, LMD. November 2013. Removing adquisition of the variables
820!      clwcon=0.
821!!      CALL get_field("CLWCON",clwcon,found)
822      IF (.NOT. found) THEN
823         PRINT*, "phyetat0: Le champ CLWCON est absent"
824         PRINT*, "Depart legerement fausse. Mais je continue"
825      ENDIF
826      xmin = 1.0E+20
827      xmax = -1.0E+20
828      xmin = MINval(clwcon)
829      xmax = MAXval(clwcon)
830      PRINT*,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
831!c
832! L. Fita, LMD. November 2013. Removing adquisition of the variables
833!      rnebcon = 0.
834!!      CALL get_field("RNEBCON",rnebcon,found)
835      IF (.NOT. found) THEN
836         PRINT*, "phyetat0: Le champ RNEBCON est absent"
837         PRINT*, "Depart legerement fausse. Mais je continue"
838      ENDIF
839      xmin = 1.0E+20
840      xmax = -1.0E+20
841      xmin = MINval(rnebcon)
842      xmax = MAXval(rnebcon)
843      PRINT*,'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
844
845!c
846!c Lecture ratqs
847!c
848! L. Fita, LMD. November 2013. Removing adquisition of the variables
849!      ratqs=0.
850!!      CALL get_field("RATQS",ratqs,found)
851      IF (.NOT. found) THEN
852         PRINT*, "phyetat0: Le champ <RATQS> est absent"
853         PRINT*, "Depart legerement fausse. Mais je continue"
854      ENDIF
855      xmin = 1.0E+20
856      xmax = -1.0E+20
857      xmin = MINval(ratqs)
858      xmax = MAXval(ratqs)
859      PRINT*,'(ecart-type) ratqs:', xmin, xmax
860!c
861!c Lecture run_off_lic_0
862!c
863! L. Fita, LMD. November 2013. Removing adquisition of the variables
864!!      CALL get_field("RUNOFFLIC0",run_off_lic_0,found)
865      IF (.NOT. found) THEN
866         PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"
867         PRINT*, "Depart legerement fausse. Mais je continue"
868         run_off_lic_0 = 0.
869      ENDIF
870      xmin = 1.0E+20
871      xmax = -1.0E+20
872      xmin = MINval(run_off_lic_0)
873      xmax = MAXval(run_off_lic_0)
874      PRINT*,'(ecart-type) run_off_lic_0:', xmin, xmax
875
876
877!c Lecture de l'energie cinetique turbulente
878!c
879
880      IF (iflag_pbl>1) then
881        DO nsrf = 1, nbsrf
882          IF (nsrf.GT.99) THEN
883            PRINT*, "Trop de sous-mailles"
884            CALL abort
885          ENDIF
886          WRITE(str2,'(i2.2)') nsrf
887! L. Fita, LMD. November 2013. Removing adquisition of the variables
888!!          CALL get_field("TKE"//str2,pbl_tke(:,1:klev+1,nsrf),found)
889          IF (.NOT. found) THEN
890            PRINT*, "phyetat0: <TKE"//str2//"> est absent"
891            pbl_tke(:,:,nsrf)=1.e-8
892          ENDIF
893          xmin = 1.0E+20
894          xmax = -1.0E+20
895          DO k = 1, klev+1
896            DO i = 1, klon
897              xmin = MIN(pbl_tke(i,k,nsrf),xmin)
898              xmax = MAX(pbl_tke(i,k,nsrf),xmax)
899            ENDDO
900          ENDDO
901          PRINT*,'Temperature du sol TKE**:', nsrf, xmin, xmax
902        ENDDO
903      ENDIF
904!c
905!c zmax0
906! L. Fita, LMD. November 2013. Removing adquisition of the variables
907!!      CALL get_field("ZMAX0",zmax0,found)
908      IF (.NOT. found) THEN
909        PRINT*, "phyetat0: Le champ <ZMAX0> est absent"
910        PRINT*, "Depart legerement fausse. Mais je continue"
911        zmax0=40.
912      ENDIF
913      xmin = 1.0E+20
914      xmax = -1.0E+20
915      xmin = MINval(zmax0)
916      xmax = MAXval(zmax0)
917      PRINT*,'(ecart-type) zmax0:', xmin, xmax
918!c
919!c           f0(ig)=1.e-5
920!c f0
921! L. Fita, LMD. November 2013. Removing adquisition of the variables
922!!      CALL get_field("F0",f0,found)
923      IF (.NOT. found) THEN
924         PRINT*, "phyetat0: Le champ <f0> est absent"
925         PRINT*, "Depart legerement fausse. Mais je continue"
926         f0=1.e-5
927      ENDIF
928      xmin = 1.0E+20
929      xmax = -1.0E+20
930      xmin = MINval(f0)
931      xmax = MAXval(f0)
932      PRINT*,'(ecart-type) f0:', xmin, xmax
933!c
934!c ema_work1
935!c
936! L. Fita, LMD. November 2013. Removing adquisition of the variables
937!!      CALL get_field("EMA_WORK1",ema_work1,found)
938      IF (.NOT. found) THEN
939        PRINT*, "phyetat0: Le champ <EMA_WORK1> est absent"
940        PRINT*, "Depart legerement fausse. Mais je continue"
941        ema_work1=0.
942      ELSE
943        xmin = 1.0E+20
944        xmax = -1.0E+20
945        DO k = 1, klev
946          DO i = 1, klon
947            xmin = MIN(ema_work1(i,k),xmin)
948            xmax = MAX(ema_work1(i,k),xmax)
949          ENDDO
950        ENDDO
951        PRINT*,'ema_work1:', xmin, xmax
952      ENDIF
953!c
954!c ema_work2
955!c
956! L. Fita, LMD. November 2013. Removing adquisition of the variables
957!!      CALL get_field("EMA_WORK2",ema_work2,found)
958      IF (.NOT. found) THEN
959        PRINT*, "phyetat0: Le champ <EMA_WORK2> est absent"
960        PRINT*, "Depart legerement fausse. Mais je continue"
961        ema_work2=0.
962      ELSE
963        xmin = 1.0E+20
964        xmax = -1.0E+20
965        DO k = 1, klev
966          DO i = 1, klon
967            xmin = MIN(ema_work2(i,k),xmin)
968            xmax = MAX(ema_work2(i,k),xmax)
969          ENDDO
970        ENDDO
971        PRINT*,'ema_work2:', xmin, xmax
972      ENDIF
973!c
974!c wake_deltat
975!c
976! L. Fita, LMD. November 2013. Removing adquisition of the variables
977!!      CALL get_field("WAKE_DELTAT",wake_deltat,found)
978      IF (.NOT. found) THEN
979        PRINT*, "phyetat0: Le champ <WAKE_DELTAT> est absent"
980        PRINT*, "Depart legerement fausse. Mais je continue"
981        wake_deltat=0.
982      ELSE
983        xmin = 1.0E+20
984        xmax = -1.0E+20
985        DO k = 1, klev
986          DO i = 1, klon
987            xmin = MIN(wake_deltat(i,k),xmin)
988            xmax = MAX(wake_deltat(i,k),xmax)
989          ENDDO
990        ENDDO
991        PRINT*,'wake_deltat:', xmin, xmax
992      ENDIF
993!c
994!c wake_deltaq
995!c   
996! L. Fita, LMD. November 2013. Removing adquisition of the variables
997!!      CALL get_field("WAKE_DELTAQ",wake_deltaq,found)
998      IF (.NOT. found) THEN
999        PRINT*, "phyetat0: Le champ <WAKE_DELTAQ> est absent"
1000        PRINT*, "Depart legerement fausse. Mais je continue"
1001        wake_deltaq=0.
1002      ELSE
1003        xmin = 1.0E+20
1004        xmax = -1.0E+20
1005        DO k = 1, klev
1006          DO i = 1, klon
1007            xmin = MIN(wake_deltaq(i,k),xmin)
1008            xmax = MAX(wake_deltaq(i,k),xmax)
1009          ENDDO
1010        ENDDO
1011        PRINT*,'wake_deltaq:', xmin, xmax
1012      ENDIF
1013!c
1014!c wake_s
1015!c
1016! L. Fita, LMD. November 2013. Removing adquisition of the variables
1017!!      CALL get_field("WAKE_S",wake_s,found)
1018      IF (.NOT. found) THEN
1019        PRINT*, "phyetat0: Le champ <WAKE_S> est absent"
1020        PRINT*, "Depart legerement fausse. Mais je continue"
1021        wake_s=0.
1022      ENDIF
1023      xmin = 1.0E+20
1024      xmax = -1.0E+20
1025      xmin = MINval(wake_s)
1026      xmax = MAXval(wake_s)
1027      PRINT*,'(ecart-type) wake_s:', xmin, xmax
1028!c
1029!c wake_cstar
1030!c
1031! L. Fita, LMD. November 2013. Removing adquisition of the variables
1032!!      CALL get_field("WAKE_CSTAR",wake_cstar,found)
1033      IF (.NOT. found) THEN
1034         PRINT*, "phyetat0: Le champ <WAKE_CSTAR> est absent"
1035         PRINT*, "Depart legerement fausse. Mais je continue"
1036         wake_cstar=0.
1037      ENDIF
1038      xmin = 1.0E+20
1039      xmax = -1.0E+20
1040      xmin = MINval(wake_cstar)
1041      xmax = MAXval(wake_cstar)
1042      PRINT*,'(ecart-type) wake_cstar:', xmin, xmax
1043!c
1044!c wake_pe
1045!c
1046! L. Fita, LMD. November 2013. Removing adquisition of the variables
1047!!      CALL get_field("WAKE_PE",wake_pe,found)
1048      IF (.NOT. found) THEN
1049         PRINT*, "phyetat0: Le champ <WAKE_PE> est absent"
1050         PRINT*, "Depart legerement fausse. Mais je continue"
1051         wake_pe=0.
1052      ENDIF
1053      xmin = 1.0E+20
1054      xmax = -1.0E+20
1055      xmin = MINval(wake_pe)
1056      xmax = MAXval(wake_pe)
1057      PRINT*,'(ecart-type) wake_pe:', xmin, xmax
1058!c
1059!c wake_fip
1060!c
1061! L. Fita, LMD. November 2013. Removing adquisition of the variables
1062!!      CALL get_field("WAKE_FIP",wake_fip,found)
1063      IF (.NOT. found) THEN
1064         PRINT*, "phyetat0: Le champ <WAKE_FIP> est absent"
1065         PRINT*, "Depart legerement fausse. Mais je continue"
1066         wake_fip=0.
1067      ENDIF
1068      xmin = 1.0E+20
1069      xmax = -1.0E+20
1070      xmin = MINval(wake_fip)
1071      xmax = MAXval(wake_fip)
1072      PRINT*,'(ecart-type) wake_fip:', xmin, xmax
1073!c
1074!c  thermiques
1075!c
1076! L. Fita, LMD. November 2013. Removing adquisition of the variables
1077!!      CALL get_field("FM_THERM",fm_therm,found)
1078      IF (.NOT. found) THEN
1079         PRINT*, "phyetat0: Le champ <fm_therm> est absent"
1080         PRINT*, "Depart legerement fausse. Mais je continue"
1081         fm_therm=0.
1082      ENDIF
1083      xmin = 1.0E+20
1084      xmax = -1.0E+20
1085      xmin = MINval(fm_therm)
1086      xmax = MAXval(fm_therm)
1087      PRINT*,'(ecart-type) fm_therm:', xmin, xmax
1088
1089! L. Fita, LMD. November 2013. Removing adquisition of the variables
1090!!      CALL get_field("ENTR_THERM",entr_therm,found)
1091      IF (.NOT. found) THEN
1092         PRINT*, "phyetat0: Le champ <entr_therm> est absent"
1093         PRINT*, "Depart legerement fausse. Mais je continue"
1094         entr_therm=0.
1095      ENDIF
1096      xmin = 1.0E+20
1097      xmax = -1.0E+20
1098      xmin = MINval(entr_therm)
1099      xmax = MAXval(entr_therm)
1100      PRINT*,'(ecart-type) entr_therm:', xmin, xmax
1101
1102! L. Fita, LMD. November 2013. Removing adquisition of the variables
1103!!      CALL get_field("DETR_THERM",detr_therm,found)
1104      IF (.NOT. found) THEN
1105         PRINT*, "phyetat0: Le champ <detr_therm> est absent"
1106         PRINT*, "Depart legerement fausse. Mais je continue"
1107         detr_therm=0.
1108      ENDIF
1109      xmin = 1.0E+20
1110      xmax = -1.0E+20
1111      xmin = MINval(detr_therm)
1112      xmax = MAXval(detr_therm)
1113      PRINT*,'(ecart-type) detr_therm:', xmin, xmax
1114
1115
1116
1117!c
1118!c Read and send field trs to traclmdz
1119!c
1120      IF (type_trac == 'lmdz') THEN
1121         DO it=1,nbtr
1122            iiq=niadv(it+2)
1123! L. Fita, LMD. November 2013. Removing adquisition of the variables
1124!!            CALL get_field("trs_"//tname(iiq),trs(:,it),found)
1125            IF (.NOT. found) THEN
1126               PRINT*,                                                               &
1127       &           "phyetat0: Le champ <trs_"//tname(iiq)//"> est absent"
1128               PRINT*, "Depart legerement fausse. Mais je continue"
1129               trs(:,it) = 0.
1130            ENDIF
1131            xmin = 1.0E+20
1132            xmax = -1.0E+20
1133            xmin = MINval(trs(:,it))
1134            xmax = MAXval(trs(:,it))
1135            PRINT*,"(ecart-type) trs_"//tname(iiq)//" :", xmin, xmax
1136
1137         END DO
1138         CALL traclmdz_from_restart(trs)
1139
1140         IF (carbon_cycle_cpl) THEN
1141            ALLOCATE(co2_send(klon), stat=ierr)
1142            IF (ierr /= 0) CALL abort_gcm                                            &
1143       &           ('phyetat0','pb allocation co2_send',1)
1144! L. Fita, LMD. November 2013. Removing adquisition of the variables
1145!!            CALL get_field("co2_send",co2_send,found)
1146            IF (.NOT. found) THEN
1147               PRINT*,"phyetat0: Le champ <co2_send> est absent"
1148               PRINT*,"Initialisation uniforme a co2_ppm=",co2_ppm
1149               co2_send(:) = co2_ppm
1150            END IF
1151         END IF
1152      END IF
1153
1154
1155!c on ferme le fichier
1156! L. Fita, LMD. November 2013. Removing adquisition of the variables
1157!      CALL close_startphy
1158      ELSE
1159        PRINT *,'  startphy not readed!'
1160
1161      END IF reading_file
1162
1163! L. Fita, LMD. Called inside the non-used if
1164!!
1165      trs=0.
1166      CALL traclmdz_from_restart(trs)
1167
1168      CALL init_iophy_new(rlat,rlon)
1169       
1170!c
1171!c Initialize module pbl_surface_mod
1172!c
1173! L. Fita, LMD. November 2013. Removing adquisition of the variables
1174!!      CALL pbl_surface_init(qsol, fder, snow, qsurf,                                 &
1175!!       &     evap, frugs, agesno, tsoil)
1176
1177!c Initialize module ocean_cpl_mod for the case of coupled ocean
1178      IF ( type_ocean == 'couple' ) THEN
1179         CALL ocean_cpl_init(dtime, rlon, rlat)
1180      ENDIF
1181!c
1182!c Initilialize module fonte_neige_mod     
1183!c
1184! L. Fita, LMD. November 2013. Removing adquisition of the variables
1185!!      CALL fonte_neige_init(run_off_lic_0)
1186
1187      RETURN
1188      END SUBROUTINE phyetat0
Note: See TracBrowser for help on using the repository browser.