source: lmdz_wrf/WRFV3/lmdz/phyetat0.F90 @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

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