/[lmdze]/trunk/phylmd/physiq.f
ViewVC logotype

Diff of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 12 by guez, Mon Jul 21 16:05:07 2008 UTC revision 47 by guez, Fri Jul 1 15:00:48 2011 UTC
# Line 1  Line 1 
1  module physiq_m  module physiq_m
2    
   ! This module is clean: no C preprocessor directive, no include line.  
   
3    IMPLICIT none    IMPLICIT none
4    
   private  
   public physiq  
   
5  contains  contains
6    
7    SUBROUTINE physiq(nq, firstcal, lafin, rdayvrai, gmtime, pdtphys, paprs, &    SUBROUTINE physiq(lafin, rdayvrai, time, dtphys, paprs, play, pphi, pphis, &
8         pplay, pphi, pphis, presnivs, clesphy0, u, v, t, qx, omega, d_u, d_v, &         u, v, t, qx, omega, d_u, d_v, d_t, d_qx, d_ps, dudyn, PVteta)
9         d_t, d_qx, d_ps, dudyn, PVteta)  
10        ! From phylmd/physiq.F, version 1.22 2006/02/20 09:38:28 (SVN revision 678)
11      ! From phylmd/physiq.F, v 1.22 2006/02/20 09:38:28      ! Author: Z.X. Li (LMD/CNRS) 1993
12    
13      ! Author : Z.X. Li (LMD/CNRS), date: 1993/08/18      ! Objet : moniteur général de la physique du modèle
14    
15      ! Objet: Moniteur general de la physique du modele      use abort_gcm_m, only: abort_gcm
16      !AA      Modifications quant aux traceurs :      USE calendar, only: ymds2ju
17      !AA                  -  uniformisation des parametrisations ds phytrac      use clesphys, only: ecrit_hf, ecrit_ins, ecrit_mth, cdmmax, cdhmax, &
18      !AA                  -  stockage des moyennes des champs necessaires           co2_ppm, ecrit_reg, ecrit_tra, ksta, ksta_ter, ok_kzmin
     !AA                     en mode traceur off-line  
   
     USE ioipsl, only: ymds2ju, histwrite, histsync  
     use dimens_m, only: jjm, iim, llm  
     use indicesol, only: nbsrf, is_ter, is_lic, is_sic, is_oce, &  
          clnsurf, epsfra  
     use dimphy, only: klon, nbtr  
     use conf_gcm_m, only: raz_date, offline, iphysiq  
     use dimsoil, only: nsoilmx  
     use temps, only: itau_phy, day_ref, annee_ref, itaufin  
     use clesphys, only: ecrit_hf, ecrit_hf2mth, &  
          ecrit_ins, ecrit_mth, ecrit_day, &  
          cdmmax, cdhmax, &  
          co2_ppm, ecrit_reg, ecrit_tra, ksta, ksta_ter, &  
          ok_kzmin  
19      use clesphys2, only: iflag_con, ok_orolf, ok_orodr, nbapp_rad, &      use clesphys2, only: iflag_con, ok_orolf, ok_orodr, nbapp_rad, &
20           cycle_diurne, new_oliq, soil_model           cycle_diurne, new_oliq, soil_model
21      use iniprint, only: prt_level      use clmain_m, only: clmain
     use abort_gcm_m, only: abort_gcm  
     use YOMCST, only: rcpd, rtt, rlvtt, rg, ra, rsigma, retv, romega  
22      use comgeomphy      use comgeomphy
23        use concvl_m, only: concvl
24        use conf_gcm_m, only: raz_date, offline
25        use conf_phys_m, only: conf_phys
26      use ctherm      use ctherm
27      use phytrac_m, only: phytrac      use dimens_m, only: jjm, iim, llm, nqmx
28        use dimphy, only: klon, nbtr
29        use dimsoil, only: nsoilmx
30        use hgardfou_m, only: hgardfou
31        USE histcom, only: histsync
32        USE histwrite_m, only: histwrite
33        use indicesol, only: nbsrf, is_ter, is_lic, is_sic, is_oce, clnsurf, epsfra
34        use ini_histhf_m, only: ini_histhf
35        use ini_histday_m, only: ini_histday
36        use ini_histins_m, only: ini_histins
37        use iniprint, only: prt_level
38      use oasis_m      use oasis_m
     use radepsi  
     use radopt  
     use yoethf  
     use ini_hist, only: ini_histhf, ini_histday, ini_histins  
39      use orbite_m, only: orbite, zenang      use orbite_m, only: orbite, zenang
40        use ozonecm_m, only: ozonecm
41      use phyetat0_m, only: phyetat0, rlat, rlon      use phyetat0_m, only: phyetat0, rlat, rlon
42      use hgardfou_m, only: hgardfou      use phyredem_m, only: phyredem
43      use conf_phys_m, only: conf_phys      use phystokenc_m, only: phystokenc
44        use phytrac_m, only: phytrac
45        use qcheck_m, only: qcheck
46        use radepsi
47        use radopt
48        use temps, only: itau_phy, day_ref, annee_ref
49        use yoethf_m
50        use SUPHEC_M, only: rcpd, rtt, rlvtt, rg, ra, rsigma, retv, romega
51    
52      ! Declaration des constantes et des fonctions thermodynamiques :      ! Declaration des constantes et des fonctions thermodynamiques :
53      use fcttre, only: thermcep, foeew, qsats, qsatl      use fcttre, only: thermcep, foeew, qsats, qsatl
54    
55      ! Variables argument:      ! Variables argument:
56    
57      INTEGER nq ! input nombre de traceurs (y compris vapeur d'eau)      REAL, intent(in):: rdayvrai
58      REAL, intent(in):: rdayvrai ! input numero du jour de l'experience      ! (elapsed time since January 1st 0h of the starting year, in days)
59      REAL, intent(in):: gmtime ! heure de la journée en fraction de jour  
60      REAL, intent(in):: pdtphys ! pas d'integration pour la physique (seconde)      REAL, intent(in):: time ! heure de la journée en fraction de jour
61      LOGICAL, intent(in):: firstcal ! first call to "calfis"      REAL, intent(in):: dtphys ! pas d'integration pour la physique (seconde)
62      logical, intent(in):: lafin ! dernier passage      logical, intent(in):: lafin ! dernier passage
63    
64      REAL, intent(in):: paprs(klon, llm+1)      REAL, intent(in):: paprs(klon, llm+1)
65      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
66        
67      REAL, intent(in):: pplay(klon, llm)      REAL, intent(in):: play(klon, llm)
68      ! (input pression pour le mileu de chaque couche (en Pa))      ! (input pression pour le mileu de chaque couche (en Pa))
69    
70      REAL pphi(klon, llm)        REAL, intent(in):: pphi(klon, llm)
71      ! (input geopotentiel de chaque couche (g z) (reference sol))      ! (input geopotentiel de chaque couche (g z) (reference sol))
72    
73      REAL pphis(klon) ! input geopotentiel du sol      REAL pphis(klon) ! input geopotentiel du sol
74    
75      REAL presnivs(llm)      REAL, intent(in):: u(klon, llm)
76      ! (input pressions approximat. des milieux couches ( en PA))      ! vitesse dans la direction X (de O a E) en m/s
77        
78        REAL, intent(in):: v(klon, llm) ! vitesse Y (de S a N) en m/s
79        REAL t(klon, llm) ! input temperature (K)
80    
81        REAL, intent(in):: qx(klon, llm, nqmx)
82        ! (humidité spécifique et fractions massiques des autres traceurs)
83    
84      REAL u(klon, llm)  ! input vitesse dans la direction X (de O a E) en m/s      REAL omega(klon, llm) ! input vitesse verticale en Pa/s
85      REAL v(klon, llm)  ! input vitesse Y (de S a N) en m/s      REAL, intent(out):: d_u(klon, llm) ! tendance physique de "u" (m/s/s)
86      REAL t(klon, llm)  ! input temperature (K)      REAL, intent(out):: d_v(klon, llm) ! tendance physique de "v" (m/s/s)
87        REAL d_t(klon, llm) ! output tendance physique de "t" (K/s)
88      REAL, intent(in):: qx(klon, llm, nq)      REAL d_qx(klon, llm, nqmx) ! output tendance physique de "qx" (kg/kg/s)
89      ! (humidite specifique (kg/kg) et fractions massiques des autres traceurs)      REAL d_ps(klon) ! output tendance physique de la pression au sol
90    
91      REAL omega(klon, llm)  ! input vitesse verticale en Pa/s      LOGICAL:: firstcal = .true.
     REAL d_u(klon, llm)  ! output tendance physique de "u" (m/s/s)  
     REAL d_v(klon, llm)  ! output tendance physique de "v" (m/s/s)  
     REAL d_t(klon, llm)  ! output tendance physique de "t" (K/s)  
     REAL d_qx(klon, llm, nq)  ! output tendance physique de "qx" (kg/kg/s)  
     REAL d_ps(klon)  ! output tendance physique de la pression au sol  
92    
93      INTEGER nbteta      INTEGER nbteta
94      PARAMETER(nbteta=3)      PARAMETER(nbteta=3)
# Line 100  contains Line 96  contains
96      REAL PVteta(klon, nbteta)      REAL PVteta(klon, nbteta)
97      ! (output vorticite potentielle a des thetas constantes)      ! (output vorticite potentielle a des thetas constantes)
98    
99      LOGICAL ok_cvl  ! pour activer le nouveau driver pour convection KE      LOGICAL ok_cvl ! pour activer le nouveau driver pour convection KE
100      PARAMETER (ok_cvl=.TRUE.)      PARAMETER (ok_cvl=.TRUE.)
101      LOGICAL ok_gust ! pour activer l'effet des gust sur flux surface      LOGICAL ok_gust ! pour activer l'effet des gust sur flux surface
102      PARAMETER (ok_gust=.FALSE.)      PARAMETER (ok_gust=.FALSE.)
# Line 122  contains Line 118  contains
118      SAVE ok_ocean      SAVE ok_ocean
119    
120      !IM "slab" ocean      !IM "slab" ocean
121      REAL tslab(klon)    !Temperature du slab-ocean      REAL tslab(klon) !Temperature du slab-ocean
122      SAVE tslab      SAVE tslab
123      REAL seaice(klon)   !glace de mer (kg/m2)      REAL seaice(klon) !glace de mer (kg/m2)
124      SAVE seaice      SAVE seaice
125      REAL fluxo(klon)    !flux turbulents ocean-glace de mer      REAL fluxo(klon) !flux turbulents ocean-glace de mer
126      REAL fluxg(klon)    !flux turbulents ocean-atmosphere      REAL fluxg(klon) !flux turbulents ocean-atmosphere
127    
128      ! Modele thermique du sol, a activer pour le cycle diurne:      ! Modele thermique du sol, a activer pour le cycle diurne:
129      logical ok_veget      logical, save:: ok_veget
130      save ok_veget      LOGICAL, save:: ok_journe ! sortir le fichier journalier
     LOGICAL ok_journe ! sortir le fichier journalier  
     save ok_journe  
131    
132      LOGICAL ok_mensuel ! sortir le fichier mensuel      LOGICAL ok_mensuel ! sortir le fichier mensuel
133    
# Line 143  contains Line 137  contains
137      LOGICAL ok_region ! sortir le fichier regional      LOGICAL ok_region ! sortir le fichier regional
138      PARAMETER (ok_region=.FALSE.)      PARAMETER (ok_region=.FALSE.)
139    
140      !     pour phsystoke avec thermiques      ! pour phsystoke avec thermiques
141      REAL fm_therm(klon, llm+1)      REAL fm_therm(klon, llm+1)
142      REAL entr_therm(klon, llm)      REAL entr_therm(klon, llm)
143      real q2(klon, llm+1, nbsrf)      real, save:: q2(klon, llm+1, nbsrf)
     save q2  
144    
145      INTEGER ivap          ! indice de traceurs pour vapeur d'eau      INTEGER ivap ! indice de traceurs pour vapeur d'eau
146      PARAMETER (ivap=1)      PARAMETER (ivap=1)
147      INTEGER iliq          ! indice de traceurs pour eau liquide      INTEGER iliq ! indice de traceurs pour eau liquide
148      PARAMETER (iliq=2)      PARAMETER (iliq=2)
149    
150      REAL t_ancien(klon, llm), q_ancien(klon, llm)      REAL t_ancien(klon, llm), q_ancien(klon, llm)
# Line 160  contains Line 153  contains
153      SAVE ancien_ok      SAVE ancien_ok
154    
155      REAL d_t_dyn(klon, llm) ! tendance dynamique pour "t" (K/s)      REAL d_t_dyn(klon, llm) ! tendance dynamique pour "t" (K/s)
156      REAL d_q_dyn(klon, llm)  ! tendance dynamique pour "q" (kg/kg/s)      REAL d_q_dyn(klon, llm) ! tendance dynamique pour "q" (kg/kg/s)
157    
158      real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)      real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
159    
# Line 180  contains Line 173  contains
173      REAL swup0(klon, klevp1), swup(klon, klevp1)      REAL swup0(klon, klevp1), swup(klon, klevp1)
174      SAVE swdn0, swdn, swup0, swup      SAVE swdn0, swdn, swup0, swup
175    
     REAL SWdn200clr(klon), SWdn200(klon)  
     REAL SWup200clr(klon), SWup200(klon)  
     SAVE SWdn200clr, SWdn200, SWup200clr, SWup200  
   
176      REAL lwdn0(klon, klevp1), lwdn(klon, klevp1)      REAL lwdn0(klon, klevp1), lwdn(klon, klevp1)
177      REAL lwup0(klon, klevp1), lwup(klon, klevp1)      REAL lwup0(klon, klevp1), lwup(klon, klevp1)
178      SAVE lwdn0, lwdn, lwup0, lwup      SAVE lwdn0, lwdn, lwup0, lwup
179    
     REAL LWdn200clr(klon), LWdn200(klon)  
     REAL LWup200clr(klon), LWup200(klon)  
     SAVE LWdn200clr, LWdn200, LWup200clr, LWup200  
   
180      !IM Amip2      !IM Amip2
181      ! variables a une pression donnee      ! variables a une pression donnee
182    
# Line 204  contains Line 189  contains
189      CHARACTER(LEN=4) clevSTD(nlevSTD)      CHARACTER(LEN=4) clevSTD(nlevSTD)
190      DATA clevSTD/'1000', '925 ', '850 ', '700 ', '600 ', &      DATA clevSTD/'1000', '925 ', '850 ', '700 ', '600 ', &
191           '500 ', '400 ', '300 ', '250 ', '200 ', '150 ', '100 ', &           '500 ', '400 ', '300 ', '250 ', '200 ', '150 ', '100 ', &
192           '70  ', '50  ', '30  ', '20  ', '10  '/           '70 ', '50 ', '30 ', '20 ', '10 '/
   
     real tlevSTD(klon, nlevSTD), qlevSTD(klon, nlevSTD)  
     real rhlevSTD(klon, nlevSTD), philevSTD(klon, nlevSTD)  
     real ulevSTD(klon, nlevSTD), vlevSTD(klon, nlevSTD)  
     real wlevSTD(klon, nlevSTD)  
   
     ! nout : niveau de output des variables a une pression donnee  
     INTEGER nout  
     PARAMETER(nout=3) !nout=1 : day; =2 : mth; =3 : NMC  
   
     REAL tsumSTD(klon, nlevSTD, nout)  
     REAL usumSTD(klon, nlevSTD, nout), vsumSTD(klon, nlevSTD, nout)  
     REAL wsumSTD(klon, nlevSTD, nout), phisumSTD(klon, nlevSTD, nout)  
     REAL qsumSTD(klon, nlevSTD, nout), rhsumSTD(klon, nlevSTD, nout)  
   
     SAVE tsumSTD, usumSTD, vsumSTD, wsumSTD, phisumSTD,  &  
          qsumSTD, rhsumSTD  
   
     logical oknondef(klon, nlevSTD, nout)  
     real tnondef(klon, nlevSTD, nout)  
     save tnondef  
   
     ! les produits uvSTD, vqSTD, .., T2STD sont calcules  
     ! a partir des valeurs instantannees toutes les 6 h  
     ! qui sont moyennees sur le mois  
   
     real uvSTD(klon, nlevSTD)  
     real vqSTD(klon, nlevSTD)  
     real vTSTD(klon, nlevSTD)  
     real wqSTD(klon, nlevSTD)  
   
     real uvsumSTD(klon, nlevSTD, nout)  
     real vqsumSTD(klon, nlevSTD, nout)  
     real vTsumSTD(klon, nlevSTD, nout)  
     real wqsumSTD(klon, nlevSTD, nout)  
   
     real vphiSTD(klon, nlevSTD)  
     real wTSTD(klon, nlevSTD)  
     real u2STD(klon, nlevSTD)  
     real v2STD(klon, nlevSTD)  
     real T2STD(klon, nlevSTD)  
   
     real vphisumSTD(klon, nlevSTD, nout)  
     real wTsumSTD(klon, nlevSTD, nout)  
     real u2sumSTD(klon, nlevSTD, nout)  
     real v2sumSTD(klon, nlevSTD, nout)  
     real T2sumSTD(klon, nlevSTD, nout)  
   
     SAVE uvsumSTD, vqsumSTD, vTsumSTD, wqsumSTD  
     SAVE vphisumSTD, wTsumSTD, u2sumSTD, v2sumSTD, T2sumSTD  
     !MI Amip2  
193    
194      ! prw: precipitable water      ! prw: precipitable water
195      real prw(klon)      real prw(klon)
# Line 265  contains Line 199  contains
199      REAL flwp(klon), fiwp(klon)      REAL flwp(klon), fiwp(klon)
200      REAL flwc(klon, llm), fiwc(klon, llm)      REAL flwc(klon, llm), fiwc(klon, llm)
201    
202      INTEGER l, kmax, lmax      INTEGER kmax, lmax
203      PARAMETER(kmax=8, lmax=8)      PARAMETER(kmax=8, lmax=8)
204      INTEGER kmaxm1, lmaxm1      INTEGER kmaxm1, lmaxm1
205      PARAMETER(kmaxm1=kmax-1, lmaxm1=lmax-1)      PARAMETER(kmaxm1=kmax-1, lmaxm1=lmax-1)
# Line 317  contains Line 251  contains
251      integer nid_hf, nid_hf3d      integer nid_hf, nid_hf3d
252      save nid_hf, nid_hf3d      save nid_hf, nid_hf3d
253    
     INTEGER        longcles  
     PARAMETER    ( longcles = 20 )  
     REAL, intent(in):: clesphy0( longcles      )  
   
254      ! Variables propres a la physique      ! Variables propres a la physique
255    
256      INTEGER, save:: radpas      INTEGER, save:: radpas
# Line 328  contains Line 258  contains
258      ! "physiq".)      ! "physiq".)
259    
260      REAL radsol(klon)      REAL radsol(klon)
261      SAVE radsol               ! bilan radiatif au sol calcule par code radiatif      SAVE radsol ! bilan radiatif au sol calcule par code radiatif
262    
263      INTEGER, SAVE:: itap ! number of calls to "physiq"      INTEGER, SAVE:: itap ! number of calls to "physiq"
264    
265      REAL ftsol(klon, nbsrf)      REAL ftsol(klon, nbsrf)
266      SAVE ftsol                  ! temperature du sol      SAVE ftsol ! temperature du sol
267    
268      REAL ftsoil(klon, nsoilmx, nbsrf)      REAL ftsoil(klon, nsoilmx, nbsrf)
269      SAVE ftsoil                 ! temperature dans le sol      SAVE ftsoil ! temperature dans le sol
270    
271      REAL fevap(klon, nbsrf)      REAL fevap(klon, nbsrf)
272      SAVE fevap                 ! evaporation      SAVE fevap ! evaporation
273      REAL fluxlat(klon, nbsrf)      REAL fluxlat(klon, nbsrf)
274      SAVE fluxlat      SAVE fluxlat
275    
276      REAL fqsurf(klon, nbsrf)      REAL fqsurf(klon, nbsrf)
277      SAVE fqsurf                 ! humidite de l'air au contact de la surface      SAVE fqsurf ! humidite de l'air au contact de la surface
278    
279      REAL qsol(klon)      REAL qsol(klon)
280      SAVE qsol                  ! hauteur d'eau dans le sol      SAVE qsol ! hauteur d'eau dans le sol
281    
282      REAL fsnow(klon, nbsrf)      REAL fsnow(klon, nbsrf)
283      SAVE fsnow                  ! epaisseur neigeuse      SAVE fsnow ! epaisseur neigeuse
284    
285      REAL falbe(klon, nbsrf)      REAL falbe(klon, nbsrf)
286      SAVE falbe                  ! albedo par type de surface      SAVE falbe ! albedo par type de surface
287      REAL falblw(klon, nbsrf)      REAL falblw(klon, nbsrf)
288      SAVE falblw                 ! albedo par type de surface      SAVE falblw ! albedo par type de surface
   
     !  Parametres de l'Orographie a l'Echelle Sous-Maille (OESM):  
   
     REAL zmea(klon)  
     SAVE zmea                   ! orographie moyenne  
   
     REAL zstd(klon)  
     SAVE zstd                   ! deviation standard de l'OESM  
   
     REAL zsig(klon)  
     SAVE zsig                   ! pente de l'OESM  
   
     REAL zgam(klon)  
     save zgam                   ! anisotropie de l'OESM  
   
     REAL zthe(klon)  
     SAVE zthe                   ! orientation de l'OESM  
   
     REAL zpic(klon)  
     SAVE zpic                   ! Maximum de l'OESM  
289    
290      REAL zval(klon)      ! Paramètres de l'orographie à l'échelle sous-maille (OESM) :
291      SAVE zval                   ! Minimum de l'OESM      REAL, save:: zmea(klon) ! orographie moyenne
292        REAL, save:: zstd(klon) ! deviation standard de l'OESM
293      REAL rugoro(klon)      REAL, save:: zsig(klon) ! pente de l'OESM
294      SAVE rugoro                 ! longueur de rugosite de l'OESM      REAL, save:: zgam(klon) ! anisotropie de l'OESM
295        REAL, save:: zthe(klon) ! orientation de l'OESM
296        REAL, save:: zpic(klon) ! Maximum de l'OESM
297        REAL, save:: zval(klon) ! Minimum de l'OESM
298        REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM
299    
300      REAL zulow(klon), zvlow(klon)      REAL zulow(klon), zvlow(klon)
301    
302      INTEGER igwd, idx(klon), itest(klon)      INTEGER igwd, idx(klon), itest(klon)
303    
304      REAL agesno(klon, nbsrf)      REAL agesno(klon, nbsrf)
305      SAVE agesno                 ! age de la neige      SAVE agesno ! age de la neige
306    
307      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
308      SAVE run_off_lic_0      SAVE run_off_lic_0
309      !KE43      !KE43
310      ! Variables liees a la convection de K. Emanuel (sb):      ! Variables liees a la convection de K. Emanuel (sb):
311    
312      REAL bas, top             ! cloud base and top levels      REAL bas, top ! cloud base and top levels
313      SAVE bas      SAVE bas
314      SAVE top      SAVE top
315    
316      REAL Ma(klon, llm)        ! undilute upward mass flux      REAL Ma(klon, llm) ! undilute upward mass flux
317      SAVE Ma      SAVE Ma
318      REAL qcondc(klon, llm)    ! in-cld water content from convect      REAL qcondc(klon, llm) ! in-cld water content from convect
319      SAVE qcondc      SAVE qcondc
320      REAL ema_work1(klon, llm), ema_work2(klon, llm)      REAL ema_work1(klon, llm), ema_work2(klon, llm)
321      SAVE ema_work1, ema_work2      SAVE ema_work1, ema_work2
322    
323      REAL wd(klon) ! sb      REAL wd(klon) ! sb
324      SAVE wd       ! sb      SAVE wd ! sb
325    
326      ! Variables locales pour la couche limite (al1):      ! Variables locales pour la couche limite (al1):
327    
# Line 416  contains Line 330  contains
330      REAL cdragh(klon) ! drag coefficient pour T and Q      REAL cdragh(klon) ! drag coefficient pour T and Q
331      REAL cdragm(klon) ! drag coefficient pour vent      REAL cdragm(klon) ! drag coefficient pour vent
332    
333      !AA  Pour phytrac      !AA Pour phytrac
334      REAL ycoefh(klon, llm)    ! coef d'echange pour phytrac      REAL ycoefh(klon, llm) ! coef d'echange pour phytrac
335      REAL yu1(klon)            ! vents dans la premiere couche U      REAL yu1(klon) ! vents dans la premiere couche U
336      REAL yv1(klon)            ! vents dans la premiere couche V      REAL yv1(klon) ! vents dans la premiere couche V
337      REAL ffonte(klon, nbsrf)    !Flux thermique utilise pour fondre la neige      REAL ffonte(klon, nbsrf) !Flux thermique utilise pour fondre la neige
338      REAL fqcalving(klon, nbsrf) !Flux d'eau "perdue" par la surface      REAL fqcalving(klon, nbsrf) !Flux d'eau "perdue" par la surface
339      !                               !et necessaire pour limiter la      ! !et necessaire pour limiter la
340      !                               !hauteur de neige, en kg/m2/s      ! !hauteur de neige, en kg/m2/s
341      REAL zxffonte(klon), zxfqcalving(klon)      REAL zxffonte(klon), zxfqcalving(klon)
342    
343      REAL pfrac_impa(klon, llm)! Produits des coefs lessivage impaction      REAL pfrac_impa(klon, llm)! Produits des coefs lessivage impaction
# Line 442  contains Line 356  contains
356      !IM cf FH pour Tiedtke 080604      !IM cf FH pour Tiedtke 080604
357      REAL rain_tiedtke(klon), snow_tiedtke(klon)      REAL rain_tiedtke(klon), snow_tiedtke(klon)
358    
     REAL total_rain(klon), nday_rain(klon)  
     save nday_rain  
   
359      REAL evap(klon), devap(klon) ! evaporation et sa derivee      REAL evap(klon), devap(klon) ! evaporation et sa derivee
360      REAL sens(klon), dsens(klon) ! chaleur sensible et sa derivee      REAL sens(klon), dsens(klon) ! chaleur sensible et sa derivee
361      REAL dlw(klon)    ! derivee infra rouge      REAL dlw(klon) ! derivee infra rouge
362      SAVE dlw      SAVE dlw
363      REAL bils(klon) ! bilan de chaleur au sol      REAL bils(klon) ! bilan de chaleur au sol
364      REAL fder(klon) ! Derive de flux (sensible et latente)      REAL fder(klon) ! Derive de flux (sensible et latente)
# Line 470  contains Line 381  contains
381      !IM      !IM
382      REAL pctsrf_new(klon, nbsrf) !pourcentage surfaces issus d'ORCHIDEE      REAL pctsrf_new(klon, nbsrf) !pourcentage surfaces issus d'ORCHIDEE
383    
384      SAVE pctsrf                 ! sous-fraction du sol      SAVE pctsrf ! sous-fraction du sol
385      REAL albsol(klon)      REAL albsol(klon)
386      SAVE albsol                 ! albedo du sol total      SAVE albsol ! albedo du sol total
387      REAL albsollw(klon)      REAL albsollw(klon)
388      SAVE albsollw                 ! albedo du sol total      SAVE albsollw ! albedo du sol total
389    
390      REAL, SAVE:: wo(klon, llm) ! ozone      REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU
391    
392      ! Declaration des procedures appelees      ! Declaration des procedures appelees
393    
394      EXTERNAL alboc     ! calculer l'albedo sur ocean      EXTERNAL alboc ! calculer l'albedo sur ocean
395      EXTERNAL ajsec     ! ajustement sec      EXTERNAL ajsec ! ajustement sec
     EXTERNAL clmain    ! couche limite  
396      !KE43      !KE43
397      EXTERNAL conema3  ! convect4.3      EXTERNAL conema3 ! convect4.3
398      EXTERNAL fisrtilp  ! schema de condensation a grande echelle (pluie)      EXTERNAL fisrtilp ! schema de condensation a grande echelle (pluie)
399      EXTERNAL nuage     ! calculer les proprietes radiatives      EXTERNAL nuage ! calculer les proprietes radiatives
400      EXTERNAL ozonecm   ! prescrire l'ozone      EXTERNAL radlwsw ! rayonnements solaire et infrarouge
401      EXTERNAL phyredem  ! ecrire l'etat de redemarrage de la physique      EXTERNAL transp ! transport total de l'eau et de l'energie
     EXTERNAL radlwsw   ! rayonnements solaire et infrarouge  
     EXTERNAL transp    ! transport total de l'eau et de l'energie  
   
     EXTERNAL ini_undefSTD  !initialise a 0 une variable a 1 niveau de pression  
   
     EXTERNAL undefSTD  
     ! (somme les valeurs definies d'1 var a 1 niveau de pression)  
402    
403      ! Variables locales      ! Variables locales
404    
# Line 504  contains Line 407  contains
407    
408      save rnebcon, clwcon      save rnebcon, clwcon
409    
410      REAL rhcl(klon, llm)    ! humiditi relative ciel clair      REAL rhcl(klon, llm) ! humiditi relative ciel clair
411      REAL dialiq(klon, llm)  ! eau liquide nuageuse      REAL dialiq(klon, llm) ! eau liquide nuageuse
412      REAL diafra(klon, llm)  ! fraction nuageuse      REAL diafra(klon, llm) ! fraction nuageuse
413      REAL cldliq(klon, llm)  ! eau liquide nuageuse      REAL cldliq(klon, llm) ! eau liquide nuageuse
414      REAL cldfra(klon, llm)  ! fraction nuageuse      REAL cldfra(klon, llm) ! fraction nuageuse
415      REAL cldtau(klon, llm)  ! epaisseur optique      REAL cldtau(klon, llm) ! epaisseur optique
416      REAL cldemi(klon, llm)  ! emissivite infrarouge      REAL cldemi(klon, llm) ! emissivite infrarouge
417    
418      REAL fluxq(klon, llm, nbsrf)   ! flux turbulent d'humidite      REAL fluxq(klon, llm, nbsrf) ! flux turbulent d'humidite
419      REAL fluxt(klon, llm, nbsrf)   ! flux turbulent de chaleur      REAL fluxt(klon, llm, nbsrf) ! flux turbulent de chaleur
420      REAL fluxu(klon, llm, nbsrf)   ! flux turbulent de vitesse u      REAL fluxu(klon, llm, nbsrf) ! flux turbulent de vitesse u
421      REAL fluxv(klon, llm, nbsrf)   ! flux turbulent de vitesse v      REAL fluxv(klon, llm, nbsrf) ! flux turbulent de vitesse v
422    
423      REAL zxfluxt(klon, llm)      REAL zxfluxt(klon, llm)
424      REAL zxfluxq(klon, llm)      REAL zxfluxq(klon, llm)
425      REAL zxfluxu(klon, llm)      REAL zxfluxu(klon, llm)
426      REAL zxfluxv(klon, llm)      REAL zxfluxv(klon, llm)
427    
428      REAL heat(klon, llm)    ! chauffage solaire      REAL heat(klon, llm) ! chauffage solaire
429      REAL heat0(klon, llm)   ! chauffage solaire ciel clair      REAL heat0(klon, llm) ! chauffage solaire ciel clair
430      REAL cool(klon, llm)    ! refroidissement infrarouge      REAL cool(klon, llm) ! refroidissement infrarouge
431      REAL cool0(klon, llm)   ! refroidissement infrarouge ciel clair      REAL cool0(klon, llm) ! refroidissement infrarouge ciel clair
432      REAL topsw(klon), toplw(klon), solsw(klon), sollw(klon)      REAL topsw(klon), toplw(klon), solsw(klon), sollw(klon)
433      real sollwdown(klon)    ! downward LW flux at surface      real sollwdown(klon) ! downward LW flux at surface
434      REAL topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)      REAL topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
435      REAL albpla(klon)      REAL albpla(klon)
436      REAL fsollw(klon, nbsrf)   ! bilan flux IR pour chaque sous surface      REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous surface
437      REAL fsolsw(klon, nbsrf)   ! flux solaire absorb. pour chaque sous surface      REAL fsolsw(klon, nbsrf) ! flux solaire absorb. pour chaque sous surface
438      ! Le rayonnement n'est pas calcule tous les pas, il faut donc      ! Le rayonnement n'est pas calcule tous les pas, il faut donc
439      !                      sauvegarder les sorties du rayonnement      ! sauvegarder les sorties du rayonnement
440      SAVE  heat, cool, albpla, topsw, toplw, solsw, sollw, sollwdown      SAVE heat, cool, albpla, topsw, toplw, solsw, sollw, sollwdown
441      SAVE  topsw0, toplw0, solsw0, sollw0, heat0, cool0      SAVE topsw0, toplw0, solsw0, sollw0, heat0, cool0
442    
443      INTEGER itaprad      INTEGER itaprad
444      SAVE itaprad      SAVE itaprad
# Line 566  contains Line 469  contains
469    
470      !IM cf. AM Variables locales pour la CLA (hbtm2)      !IM cf. AM Variables locales pour la CLA (hbtm2)
471    
472      REAL pblh(klon, nbsrf)           ! Hauteur de couche limite      REAL pblh(klon, nbsrf) ! Hauteur de couche limite
473      REAL plcl(klon, nbsrf)           ! Niveau de condensation de la CLA      REAL plcl(klon, nbsrf) ! Niveau de condensation de la CLA
474      REAL capCL(klon, nbsrf)          ! CAPE de couche limite      REAL capCL(klon, nbsrf) ! CAPE de couche limite
475      REAL oliqCL(klon, nbsrf)          ! eau_liqu integree de couche limite      REAL oliqCL(klon, nbsrf) ! eau_liqu integree de couche limite
476      REAL cteiCL(klon, nbsrf)          ! cloud top instab. crit. couche limite      REAL cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
477      REAL pblt(klon, nbsrf)          ! T a la Hauteur de couche limite      REAL pblt(klon, nbsrf) ! T a la Hauteur de couche limite
478      REAL therm(klon, nbsrf)      REAL therm(klon, nbsrf)
479      REAL trmb1(klon, nbsrf)          ! deep_cape      REAL trmb1(klon, nbsrf) ! deep_cape
480      REAL trmb2(klon, nbsrf)          ! inhibition      REAL trmb2(klon, nbsrf) ! inhibition
481      REAL trmb3(klon, nbsrf)          ! Point Omega      REAL trmb3(klon, nbsrf) ! Point Omega
482      ! Grdeurs de sorties      ! Grdeurs de sorties
483      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
484      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
# Line 584  contains Line 487  contains
487    
488      ! Variables locales pour la convection de K. Emanuel (sb):      ! Variables locales pour la convection de K. Emanuel (sb):
489    
490      REAL upwd(klon, llm)      ! saturated updraft mass flux      REAL upwd(klon, llm) ! saturated updraft mass flux
491      REAL dnwd(klon, llm)      ! saturated downdraft mass flux      REAL dnwd(klon, llm) ! saturated downdraft mass flux
492      REAL dnwd0(klon, llm)     ! unsaturated downdraft mass flux      REAL dnwd0(klon, llm) ! unsaturated downdraft mass flux
493      REAL tvp(klon, llm)       ! virtual temp of lifted parcel      REAL tvp(klon, llm) ! virtual temp of lifted parcel
494      REAL cape(klon)           ! CAPE      REAL cape(klon) ! CAPE
495      SAVE cape      SAVE cape
496    
497      REAL pbase(klon)          ! cloud base pressure      REAL pbase(klon) ! cloud base pressure
498      SAVE pbase      SAVE pbase
499      REAL bbase(klon)          ! cloud base buoyancy      REAL bbase(klon) ! cloud base buoyancy
500      SAVE bbase      SAVE bbase
501      REAL rflag(klon)          ! flag fonctionnement de convect      REAL rflag(klon) ! flag fonctionnement de convect
502      INTEGER iflagctrl(klon)          ! flag fonctionnement de convect      INTEGER iflagctrl(klon) ! flag fonctionnement de convect
503      ! -- convect43:      ! -- convect43:
504      INTEGER ntra              ! nb traceurs pour convect4.3      INTEGER ntra ! nb traceurs pour convect4.3
505      REAL dtvpdt1(klon, llm), dtvpdq1(klon, llm)      REAL dtvpdt1(klon, llm), dtvpdq1(klon, llm)
506      REAL dplcldt(klon), dplcldr(klon)      REAL dplcldt(klon), dplcldr(klon)
507    
# Line 644  contains Line 547  contains
547      save ratqsbas, ratqshaut, ratqs      save ratqsbas, ratqshaut, ratqs
548    
549      ! Parametres lies au nouveau schema de nuages (SB, PDF)      ! Parametres lies au nouveau schema de nuages (SB, PDF)
550      real fact_cldcon      real, save:: fact_cldcon
551      real facttemps      real, save:: facttemps
552      logical ok_newmicro      logical ok_newmicro
553      save ok_newmicro      save ok_newmicro
     save fact_cldcon, facttemps  
554      real facteur      real facteur
555    
556      integer iflag_cldcon      integer iflag_cldcon
# Line 656  contains Line 558  contains
558    
559      logical ptconv(klon, llm)      logical ptconv(klon, llm)
560    
     ! Variables liees a l'ecriture de la bande histoire physique  
   
     integer itau_w   ! pas de temps ecriture = itap + itau_phy  
   
561      ! Variables locales pour effectuer les appels en serie      ! Variables locales pour effectuer les appels en serie
562    
563      REAL t_seri(klon, llm), q_seri(klon, llm)      REAL t_seri(klon, llm), q_seri(klon, llm)
# Line 670  contains Line 568  contains
568      REAL d_tr(klon, llm, nbtr)      REAL d_tr(klon, llm, nbtr)
569    
570      REAL zx_rh(klon, llm)      REAL zx_rh(klon, llm)
     INTEGER ndex2d(iim*(jjm + 1)), ndex3d(iim*(jjm + 1)*llm)  
571    
572      REAL zustrdr(klon), zvstrdr(klon)      REAL zustrdr(klon), zvstrdr(klon)
573      REAL zustrli(klon), zvstrli(klon)      REAL zustrli(klon), zvstrli(klon)
# Line 679  contains Line 576  contains
576    
577      REAL dudyn(iim+1, jjm + 1, llm)      REAL dudyn(iim+1, jjm + 1, llm)
578    
579      REAL zx_tmp_fi2d(klon)      ! variable temporaire grille physique      REAL zx_tmp_fi2d(klon) ! variable temporaire grille physique
     REAL zx_tmp_fi3d(klon, llm) ! variable temporaire pour champs 3D  
   
580      REAL zx_tmp_2d(iim, jjm + 1), zx_tmp_3d(iim, jjm + 1, llm)      REAL zx_tmp_2d(iim, jjm + 1), zx_tmp_3d(iim, jjm + 1, llm)
581    
582      INTEGER nid_day, nid_ins      INTEGER, SAVE:: nid_day, nid_ins
     SAVE nid_day, nid_ins  
583    
584      REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert.      REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert.
585      REAL vq_lay(klon, llm) ! transport meri. de l'eau a chaque niveau vert.      REAL vq_lay(klon, llm) ! transport meri. de l'eau a chaque niveau vert.
# Line 699  contains Line 593  contains
593      logical ok_sync      logical ok_sync
594      real date0      real date0
595    
596      !     Variables liees au bilan d'energie et d'enthalpi      ! Variables liees au bilan d'energie et d'enthalpi
597      REAL ztsol(klon)      REAL ztsol(klon)
598      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec      REAL d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec
599      REAL      d_h_vcol_phy      REAL d_h_vcol_phy
600      REAL      fs_bound, fq_bound      REAL fs_bound, fq_bound
601      SAVE      d_h_vcol_phy      SAVE d_h_vcol_phy
602      REAL      zero_v(klon)      REAL zero_v(klon)
603      CHARACTER(LEN=15) ztit      CHARACTER(LEN=15) ztit
604      INTEGER   ip_ebil  ! PRINT level for energy conserv. diag.      INTEGER ip_ebil ! PRINT level for energy conserv. diag.
605      SAVE      ip_ebil      SAVE ip_ebil
606      DATA      ip_ebil/0/      DATA ip_ebil/0/
607      INTEGER   if_ebil ! level for energy conserv. dignostics      INTEGER, SAVE:: if_ebil ! level for energy conservation diagnostics
     SAVE      if_ebil  
608      !+jld ec_conser      !+jld ec_conser
609      REAL d_t_ec(klon, llm)    ! tendance du a la conersion Ec -> E thermique      REAL d_t_ec(klon, llm) ! tendance du a la conersion Ec -> E thermique
610      REAL ZRCPD      REAL ZRCPD
611      !-jld ec_conser      !-jld ec_conser
612      !IM: t2m, q2m, u10m, v10m      !IM: t2m, q2m, u10m, v10m
613      REAL t2m(klon, nbsrf), q2m(klon, nbsrf)   !temperature, humidite a 2m      REAL t2m(klon, nbsrf), q2m(klon, nbsrf) !temperature, humidite a 2m
614      REAL u10m(klon, nbsrf), v10m(klon, nbsrf) !vents a 10m      REAL u10m(klon, nbsrf), v10m(klon, nbsrf) !vents a 10m
615      REAL zt2m(klon), zq2m(klon)             !temp., hum. 2m moyenne s/ 1 maille      REAL zt2m(klon), zq2m(klon) !temp., hum. 2m moyenne s/ 1 maille
616      REAL zu10m(klon), zv10m(klon)           !vents a 10m moyennes s/1 maille      REAL zu10m(klon), zv10m(klon) !vents a 10m moyennes s/1 maille
617      !jq   Aerosol effects (Johannes Quaas, 27/11/2003)      !jq Aerosol effects (Johannes Quaas, 27/11/2003)
618      REAL sulfate(klon, llm) ! SO4 aerosol concentration [ug/m3]      REAL sulfate(klon, llm) ! SO4 aerosol concentration [ug/m3]
619    
620      REAL sulfate_pi(klon, llm)      REAL sulfate_pi(klon, llm)
# Line 731  contains Line 624  contains
624      REAL cldtaupi(klon, llm)      REAL cldtaupi(klon, llm)
625      ! (Cloud optical thickness for pre-industrial (pi) aerosols)      ! (Cloud optical thickness for pre-industrial (pi) aerosols)
626    
627      REAL re(klon, llm)       ! Cloud droplet effective radius      REAL re(klon, llm) ! Cloud droplet effective radius
628      REAL fl(klon, llm)  ! denominator of re      REAL fl(klon, llm) ! denominator of re
629    
630      ! Aerosol optical properties      ! Aerosol optical properties
631      REAL tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)      REAL tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)
# Line 743  contains Line 636  contains
636    
637      REAL topswai(klon), solswai(klon) ! Aerosol indirect effect.      REAL topswai(klon), solswai(klon) ! Aerosol indirect effect.
638      ! ok_aie=T ->      ! ok_aie=T ->
639      !        ok_ade=T -AIE=topswai-topswad      ! ok_ade=T -AIE=topswai-topswad
640      !        ok_ade=F -AIE=topswai-topsw      ! ok_ade=F -AIE=topswai-topsw
641    
642      REAL aerindex(klon)       ! POLDER aerosol index      REAL aerindex(klon) ! POLDER aerosol index
643    
644      ! Parameters      ! Parameters
645      LOGICAL ok_ade, ok_aie    ! Apply aerosol (in)direct effects or not      LOGICAL ok_ade, ok_aie ! Apply aerosol (in)direct effects or not
646      REAL bl95_b0, bl95_b1   ! Parameter in Boucher and Lohmann (1995)      REAL bl95_b0, bl95_b1 ! Parameter in Boucher and Lohmann (1995)
647    
648      SAVE ok_ade, ok_aie, bl95_b0, bl95_b1      SAVE ok_ade, ok_aie, bl95_b0, bl95_b1
649      SAVE u10m      SAVE u10m
# Line 783  contains Line 676  contains
676      SAVE trmb2      SAVE trmb2
677      SAVE trmb3      SAVE trmb3
678    
679        real zmasse(klon, llm)
680        ! (column-density of mass of air in a cell, in kg m-2)
681    
682        real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
683    
684      !----------------------------------------------------------------      !----------------------------------------------------------------
685    
686      modname = 'physiq'      modname = 'physiq'
# Line 792  contains Line 690  contains
690         END DO         END DO
691      END IF      END IF
692      ok_sync=.TRUE.      ok_sync=.TRUE.
693      IF (nq  <  2) THEN      IF (nqmx < 2) THEN
694         abort_message = 'eaux vapeur et liquide sont indispensables'         abort_message = 'eaux vapeur et liquide sont indispensables'
695         CALL abort_gcm (modname, abort_message, 1)         CALL abort_gcm(modname, abort_message, 1)
696      ENDIF      ENDIF
697    
698      test_firstcal: IF (firstcal) THEN      test_firstcal: IF (firstcal) THEN
699         !  initialiser         ! initialiser
700         u10m(:, :)=0.         u10m=0.
701         v10m(:, :)=0.         v10m=0.
702         t2m(:, :)=0.         t2m=0.
703         q2m(:, :)=0.         q2m=0.
704         ffonte(:, :)=0.         ffonte=0.
705         fqcalving(:, :)=0.         fqcalving=0.
706         piz_ae(:, :, :)=0.         piz_ae=0.
707         tau_ae(:, :, :)=0.         tau_ae=0.
708         cg_ae(:, :, :)=0.         cg_ae=0.
709         rain_con(:)=0.         rain_con(:)=0.
710         snow_con(:)=0.         snow_con(:)=0.
711         bl95_b0=0.         bl95_b0=0.
# Line 817  contains Line 715  contains
715         solswai(:)=0.         solswai(:)=0.
716         solswad(:)=0.         solswad(:)=0.
717    
718         d_u_con(:, :) = 0.0         d_u_con = 0.0
719         d_v_con(:, :) = 0.0         d_v_con = 0.0
720         rnebcon0(:, :) = 0.0         rnebcon0 = 0.0
721         clwcon0(:, :) = 0.0         clwcon0 = 0.0
722         rnebcon(:, :) = 0.0         rnebcon = 0.0
723         clwcon(:, :) = 0.0         clwcon = 0.0
724    
725         pblh(:, :)   =0.        ! Hauteur de couche limite         pblh =0. ! Hauteur de couche limite
726         plcl(:, :)   =0.        ! Niveau de condensation de la CLA         plcl =0. ! Niveau de condensation de la CLA
727         capCL(:, :)  =0.        ! CAPE de couche limite         capCL =0. ! CAPE de couche limite
728         oliqCL(:, :) =0.        ! eau_liqu integree de couche limite         oliqCL =0. ! eau_liqu integree de couche limite
729         cteiCL(:, :) =0.        ! cloud top instab. crit. couche limite         cteiCL =0. ! cloud top instab. crit. couche limite
730         pblt(:, :)   =0.        ! T a la Hauteur de couche limite         pblt =0. ! T a la Hauteur de couche limite
731         therm(:, :)  =0.         therm =0.
732         trmb1(:, :)  =0.        ! deep_cape         trmb1 =0. ! deep_cape
733         trmb2(:, :)  =0.        ! inhibition         trmb2 =0. ! inhibition
734         trmb3(:, :)  =0.        ! Point Omega         trmb3 =0. ! Point Omega
735    
736         IF (if_ebil >= 1) d_h_vcol_phy=0.         IF (if_ebil >= 1) d_h_vcol_phy=0.
737    
# Line 842  contains Line 740  contains
740         call conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, &         call conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, &
741              ok_instan, fact_cldcon, facttemps, ok_newmicro, &              ok_instan, fact_cldcon, facttemps, ok_newmicro, &
742              iflag_cldcon, ratqsbas, ratqshaut, if_ebil, &              iflag_cldcon, ratqsbas, ratqshaut, if_ebil, &
743              ok_ade, ok_aie,  &              ok_ade, ok_aie, &
744              bl95_b0, bl95_b1, &              bl95_b0, bl95_b1, &
745              iflag_thermals, nsplit_thermals)              iflag_thermals, nsplit_thermals)
746    
# Line 854  contains Line 752  contains
752         CALL phyetat0("startphy.nc", pctsrf, ftsol, ftsoil, ocean, tslab, &         CALL phyetat0("startphy.nc", pctsrf, ftsol, ftsoil, ocean, tslab, &
753              seaice, fqsurf, qsol, fsnow, &              seaice, fqsurf, qsol, fsnow, &
754              falbe, falblw, fevap, rain_fall, snow_fall, solsw, sollwdown, &              falbe, falblw, fevap, rain_fall, snow_fall, solsw, sollwdown, &
755              dlw, radsol, frugs, agesno, clesphy0, &              dlw, radsol, frugs, agesno, &
756              zmea, zstd, zsig, zgam, zthe, zpic, zval, rugoro, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, &
757              t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon,  &              t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &
758              run_off_lic_0)              run_off_lic_0)
759    
760         !   ATTENTION : il faudra a terme relire q2 dans l'etat initial         ! ATTENTION : il faudra a terme relire q2 dans l'etat initial
761         q2(:, :, :)=1.e-8         q2=1.e-8
762    
763         radpas = NINT( 86400. / pdtphys / nbapp_rad)         radpas = NINT( 86400. / dtphys / nbapp_rad)
764    
765         ! on remet le calendrier a zero         ! on remet le calendrier a zero
766           IF (raz_date) itau_phy = 0
        IF (raz_date == 1) THEN  
           itau_phy = 0  
        ENDIF  
767    
768         PRINT *, 'cycle_diurne = ', cycle_diurne         PRINT *, 'cycle_diurne = ', cycle_diurne
769    
# Line 879  contains Line 774  contains
774         CALL printflag(radpas, ok_ocean, ok_oasis, ok_journe, ok_instan, &         CALL printflag(radpas, ok_ocean, ok_oasis, ok_journe, ok_instan, &
775              ok_region)              ok_region)
776    
777         IF (pdtphys*REAL(radpas).GT.21600..AND.cycle_diurne) THEN         IF (dtphys*REAL(radpas).GT.21600..AND.cycle_diurne) THEN
778            print *,'Nbre d appels au rayonnement insuffisant'            print *,'Nbre d appels au rayonnement insuffisant'
779            print *,"Au minimum 4 appels par jour si cycle diurne"            print *,"Au minimum 4 appels par jour si cycle diurne"
780            abort_message='Nbre d appels au rayonnement insuffisant'            abort_message='Nbre d appels au rayonnement insuffisant'
# Line 892  contains Line 787  contains
787         ! Initialisation pour la convection de K.E. (sb):         ! Initialisation pour la convection de K.E. (sb):
788         IF (iflag_con >= 3) THEN         IF (iflag_con >= 3) THEN
789    
790            print *,"*** Convection de Kerry Emanuel 4.3  "            print *,"*** Convection de Kerry Emanuel 4.3 "
791    
792            !IM15/11/02 rajout initialisation ibas_con, itop_con cf. SB =>BEG            !IM15/11/02 rajout initialisation ibas_con, itop_con cf. SB =>BEG
793            DO i = 1, klon            DO i = 1, klon
# Line 904  contains Line 799  contains
799         ENDIF         ENDIF
800    
801         IF (ok_orodr) THEN         IF (ok_orodr) THEN
802            DO i=1, klon            rugoro = MAX(1e-5, zstd * zsig / 2)
803               rugoro(i) = MAX(1.0e-05, zstd(i)*zsig(i)/2.0)            CALL SUGWD(klon, llm, paprs, play)
804            ENDDO         else
805            CALL SUGWD(klon, llm, paprs, pplay)            rugoro = 0.
806         ENDIF         ENDIF
807    
808         lmt_pas = NINT(86400. / pdtphys)  ! tous les jours         lmt_pas = NINT(86400. / dtphys) ! tous les jours
809         print *, 'Number of time steps of "physics" per day: ', lmt_pas         print *, 'Number of time steps of "physics" per day: ', lmt_pas
810    
811         ecrit_ins = NINT(ecrit_ins/pdtphys)         ecrit_ins = NINT(ecrit_ins/dtphys)
812         ecrit_hf = NINT(ecrit_hf/pdtphys)         ecrit_hf = NINT(ecrit_hf/dtphys)
813         ecrit_day = NINT(ecrit_day/pdtphys)         ecrit_mth = NINT(ecrit_mth/dtphys)
814         ecrit_mth = NINT(ecrit_mth/pdtphys)         ecrit_tra = NINT(86400.*ecrit_tra/dtphys)
815         ecrit_tra = NINT(86400.*ecrit_tra/pdtphys)         ecrit_reg = NINT(ecrit_reg/dtphys)
        ecrit_reg = NINT(ecrit_reg/pdtphys)  
816    
817         ! Initialiser le couplage si necessaire         ! Initialiser le couplage si necessaire
818    
# Line 927  contains Line 821  contains
821    
822         print *,'AVANT HIST IFLAG_CON=', iflag_con         print *,'AVANT HIST IFLAG_CON=', iflag_con
823    
824         !   Initialisation des sorties         ! Initialisation des sorties
825    
826         call ini_histhf(pdtphys, presnivs, nid_hf, nid_hf3d)         call ini_histhf(dtphys, nid_hf, nid_hf3d)
827         call ini_histday(pdtphys, presnivs, ok_journe, nid_day)         call ini_histday(dtphys, ok_journe, nid_day, nqmx)
828         call ini_histins(pdtphys, presnivs, ok_instan, nid_ins)         call ini_histins(dtphys, ok_instan, nid_ins)
829         CALL ymds2ju(annee_ref, 1, int(day_ref), 0., date0)         CALL ymds2ju(annee_ref, 1, int(day_ref), 0., date0)
830         !XXXPB Positionner date0 pour initialisation de ORCHIDEE         !XXXPB Positionner date0 pour initialisation de ORCHIDEE
831         WRITE(*, *) 'physiq date0 : ', date0         WRITE(*, *) 'physiq date0 : ', date0
# Line 949  contains Line 843  contains
843            d_v(i, k) = 0.0            d_v(i, k) = 0.0
844         ENDDO         ENDDO
845      ENDDO      ENDDO
846      DO iq = 1, nq      DO iq = 1, nqmx
847         DO k = 1, llm         DO k = 1, llm
848            DO i = 1, klon            DO i = 1, klon
849               d_qx(i, k, iq) = 0.0               d_qx(i, k, iq) = 0.0
850            ENDDO            ENDDO
851         ENDDO         ENDDO
852      ENDDO      ENDDO
853      da(:, :)=0.      da=0.
854      mp(:, :)=0.      mp=0.
855      phi(:, :, :)=0.      phi=0.
856    
857      ! Ne pas affecter les valeurs entrees de u, v, h, et q      ! Ne pas affecter les valeurs entrees de u, v, h, et q
858    
859      DO k = 1, llm      DO k = 1, llm
860         DO i = 1, klon         DO i = 1, klon
861            t_seri(i, k)  = t(i, k)            t_seri(i, k) = t(i, k)
862            u_seri(i, k)  = u(i, k)            u_seri(i, k) = u(i, k)
863            v_seri(i, k)  = v(i, k)            v_seri(i, k) = v(i, k)
864            q_seri(i, k)  = qx(i, k, ivap)            q_seri(i, k) = qx(i, k, ivap)
865            ql_seri(i, k) = qx(i, k, iliq)            ql_seri(i, k) = qx(i, k, iliq)
866            qs_seri(i, k) = 0.            qs_seri(i, k) = 0.
867         ENDDO         ENDDO
868      ENDDO      ENDDO
869      IF (nq >= 3) THEN      IF (nqmx >= 3) THEN
870         tr_seri(:, :, :nq-2) = qx(:, :, 3:nq)         tr_seri(:, :, :nqmx-2) = qx(:, :, 3:nqmx)
871      ELSE      ELSE
872         tr_seri(:, :, 1) = 0.         tr_seri(:, :, 1) = 0.
873      ENDIF      ENDIF
# Line 989  contains Line 883  contains
883    
884      IF (if_ebil >= 1) THEN      IF (if_ebil >= 1) THEN
885         ztit='after dynamic'         ztit='after dynamic'
886         CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, dtphys, t_seri, q_seri, &
887              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
888              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
889         !     Comme les tendances de la physique sont ajoute dans la dynamique,         ! Comme les tendances de la physique sont ajoute dans la dynamique,
890         !     on devrait avoir que la variation d'entalpie par la dynamique         ! on devrait avoir que la variation d'entalpie par la dynamique
891         !     est egale a la variation de la physique au pas de temps precedent.         ! est egale a la variation de la physique au pas de temps precedent.
892         !     Donc la somme de ces 2 variations devrait etre nulle.         ! Donc la somme de ces 2 variations devrait etre nulle.
893         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
894              , zero_v, zero_v, zero_v, zero_v, zero_v &              zero_v, zero_v, zero_v, zero_v, ztsol, d_h_vcol+d_h_vcol_phy, &
895              , zero_v, zero_v, zero_v, ztsol &              d_qt, 0., fs_bound, fq_bound )
             , d_h_vcol+d_h_vcol_phy, d_qt, 0. &  
             , fs_bound, fq_bound )  
896      END IF      END IF
897    
898      ! Diagnostiquer la tendance dynamique      ! Diagnostiquer la tendance dynamique
# Line 1008  contains Line 900  contains
900      IF (ancien_ok) THEN      IF (ancien_ok) THEN
901         DO k = 1, llm         DO k = 1, llm
902            DO i = 1, klon            DO i = 1, klon
903               d_t_dyn(i, k) = (t_seri(i, k)-t_ancien(i, k))/pdtphys               d_t_dyn(i, k) = (t_seri(i, k)-t_ancien(i, k))/dtphys
904               d_q_dyn(i, k) = (q_seri(i, k)-q_ancien(i, k))/pdtphys               d_q_dyn(i, k) = (q_seri(i, k)-q_ancien(i, k))/dtphys
905            ENDDO            ENDDO
906         ENDDO         ENDDO
907      ELSE      ELSE
# Line 1040  contains Line 932  contains
932      julien = MOD(NINT(rdayvrai), 360)      julien = MOD(NINT(rdayvrai), 360)
933      if (julien == 0) julien = 360      if (julien == 0) julien = 360
934    
935        forall (k = 1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg
936    
937      ! Mettre en action les conditions aux limites (albedo, sst, etc.).      ! Mettre en action les conditions aux limites (albedo, sst, etc.).
938      ! Prescrire l'ozone et calculer l'albedo sur l'ocean.      ! Prescrire l'ozone et calculer l'albedo sur l'ocean.
939    
940      IF (MOD(itap - 1, lmt_pas) == 0) THEN      if (nqmx >= 5) then
941         CALL ozonecm(REAL(julien), rlat, paprs, wo)         wo = qx(:, :, 5) * zmasse / dobson_u / 1e3
942        else IF (MOD(itap - 1, lmt_pas) == 0) THEN
943           wo = ozonecm(REAL(julien), paprs)
944      ENDIF      ENDIF
945    
946      ! Re-evaporer l'eau liquide nuageuse      ! Re-evaporer l'eau liquide nuageuse
947    
948      DO k = 1, llm  ! re-evaporation de l'eau liquide nuageuse      DO k = 1, llm ! re-evaporation de l'eau liquide nuageuse
949         DO i = 1, klon         DO i = 1, klon
950            zlvdcp=RLVTT/RCPD/(1.0+RVTMP2*q_seri(i, k))            zlvdcp=RLVTT/RCPD/(1.0+RVTMP2*q_seri(i, k))
951            zlsdcp=RLVTT/RCPD/(1.0+RVTMP2*q_seri(i, k))            zlsdcp=RLVTT/RCPD/(1.0+RVTMP2*q_seri(i, k))
# Line 1065  contains Line 961  contains
961    
962      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
963         ztit='after reevap'         ztit='after reevap'
964         CALL diagetpq(airephy, ztit, ip_ebil, 2, 1, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 1, dtphys, t_seri, q_seri, &
965              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
966              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
967         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
968              , zero_v, zero_v, zero_v, zero_v, zero_v &              zero_v, zero_v, zero_v, zero_v, ztsol, d_h_vcol, d_qt, d_ec, &
969              , zero_v, zero_v, zero_v, ztsol &              fs_bound, fq_bound )
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
970    
971      END IF      END IF
972    
# Line 1096  contains Line 990  contains
990    
991      CALL orbite(REAL(julien), zlongi, dist)      CALL orbite(REAL(julien), zlongi, dist)
992      IF (cycle_diurne) THEN      IF (cycle_diurne) THEN
993         zdtime = pdtphys * REAL(radpas)         zdtime = dtphys * REAL(radpas)
994         CALL zenang(zlongi, gmtime, zdtime, rmu0, fract)         CALL zenang(zlongi, time, zdtime, rmu0, fract)
995      ELSE      ELSE
996         rmu0 = -999.999         rmu0 = -999.999
997      ENDIF      ENDIF
998    
999      !     Calcul de l'abedo moyen par maille      ! Calcul de l'abedo moyen par maille
1000      albsol(:)=0.      albsol(:)=0.
1001      albsollw(:)=0.      albsollw(:)=0.
1002      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
# Line 1112  contains Line 1006  contains
1006         ENDDO         ENDDO
1007      ENDDO      ENDDO
1008    
1009      !     Repartition sous maille des flux LW et SW      ! Repartition sous maille des flux LW et SW
1010      ! Repartition du longwave par sous-surface linearisee      ! Repartition du longwave par sous-surface linearisee
1011    
1012      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
# Line 1125  contains Line 1019  contains
1019    
1020      fder = dlw      fder = dlw
1021    
1022      CALL clmain(pdtphys, itap, date0, pctsrf, pctsrf_new, &      ! Couche limite:
1023           t_seri, q_seri, u_seri, v_seri, &  
1024           julien, rmu0, co2_ppm,  &      CALL clmain(dtphys, itap, date0, pctsrf, pctsrf_new, t_seri, q_seri, &
1025           ok_veget, ocean, npas, nexca, ftsol, &           u_seri, v_seri, julien, rmu0, co2_ppm, ok_veget, ocean, npas, nexca, &
1026           soil_model, cdmmax, cdhmax, &           ftsol, soil_model, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, &
1027           ksta, ksta_ter, ok_kzmin, ftsoil, qsol,  &           qsol, paprs, play, fsnow, fqsurf, fevap, falbe, falblw, fluxlat, &
1028           paprs, pplay, fsnow, fqsurf, fevap, falbe, falblw, &           rain_fall, snow_fall, fsolsw, fsollw, sollwdown, fder, rlon, rlat, &
1029           fluxlat, rain_fall, snow_fall, &           cuphy, cvphy, frugs, firstcal, lafin, agesno, rugoro, d_t_vdf, &
1030           fsolsw, fsollw, sollwdown, fder, &           d_q_vdf, d_u_vdf, d_v_vdf, d_ts, fluxt, fluxq, fluxu, fluxv, cdragh, &
1031           rlon, rlat, cuphy, cvphy, frugs, &           cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, u10m, v10m, &
1032           firstcal, lafin, agesno, rugoro, &           pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, plcl, &
1033           d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, &           fqcalving, ffonte, run_off_lic_0, fluxo, fluxg, tslab, seaice)
          fluxt, fluxq, fluxu, fluxv, cdragh, cdragm, &  
          q2, dsens, devap, &  
          ycoefh, yu1, yv1, t2m, q2m, u10m, v10m, &  
          pblh, capCL, oliqCL, cteiCL, pblT, &  
          therm, trmb1, trmb2, trmb3, plcl, &  
          fqcalving, ffonte, run_off_lic_0, &  
          fluxo, fluxg, tslab, seaice)  
1034    
1035      !XXX Incrementation des flux      ! Incrémentation des flux
1036    
1037      zxfluxt=0.      zxfluxt=0.
1038      zxfluxq=0.      zxfluxq=0.
# Line 1154  contains Line 1041  contains
1041      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
1042         DO k = 1, llm         DO k = 1, llm
1043            DO i = 1, klon            DO i = 1, klon
1044               zxfluxt(i, k) = zxfluxt(i, k) +  &               zxfluxt(i, k) = zxfluxt(i, k) + &
1045                    fluxt(i, k, nsrf) * pctsrf( i, nsrf)                    fluxt(i, k, nsrf) * pctsrf( i, nsrf)
1046               zxfluxq(i, k) = zxfluxq(i, k) +  &               zxfluxq(i, k) = zxfluxq(i, k) + &
1047                    fluxq(i, k, nsrf) * pctsrf( i, nsrf)                    fluxq(i, k, nsrf) * pctsrf( i, nsrf)
1048               zxfluxu(i, k) = zxfluxu(i, k) +  &               zxfluxu(i, k) = zxfluxu(i, k) + &
1049                    fluxu(i, k, nsrf) * pctsrf( i, nsrf)                    fluxu(i, k, nsrf) * pctsrf( i, nsrf)
1050               zxfluxv(i, k) = zxfluxv(i, k) +  &               zxfluxv(i, k) = zxfluxv(i, k) + &
1051                    fluxv(i, k, nsrf) * pctsrf( i, nsrf)                    fluxv(i, k, nsrf) * pctsrf( i, nsrf)
1052            END DO            END DO
1053         END DO         END DO
# Line 1182  contains Line 1069  contains
1069    
1070      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1071         ztit='after clmain'         ztit='after clmain'
1072         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1073              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1074              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1075         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
1076              , zero_v, zero_v, zero_v, zero_v, sens &              sens, evap, zero_v, zero_v, ztsol, d_h_vcol, d_qt, d_ec, &
1077              , evap, zero_v, zero_v, ztsol &              fs_bound, fq_bound )
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
1078      END IF      END IF
1079    
1080      ! Incrementer la temperature du sol      ! Incrementer la temperature du sol
# Line 1216  contains Line 1101  contains
1101         s_trmb2(i) = 0.0         s_trmb2(i) = 0.0
1102         s_trmb3(i) = 0.0         s_trmb3(i) = 0.0
1103    
1104         IF ( abs( pctsrf(i, is_ter) + pctsrf(i, is_lic) +  &         IF ( abs( pctsrf(i, is_ter) + pctsrf(i, is_lic) + &
1105              pctsrf(i, is_oce) + pctsrf(i, is_sic)  - 1.) .GT. EPSFRA)  &              pctsrf(i, is_oce) + pctsrf(i, is_sic) - 1.) .GT. EPSFRA) &
1106              THEN              THEN
1107            WRITE(*, *) 'physiq : pb sous surface au point ', i,  &            WRITE(*, *) 'physiq : pb sous surface au point ', i, &
1108                 pctsrf(i, 1 : nbsrf)                 pctsrf(i, 1 : nbsrf)
1109         ENDIF         ENDIF
1110      ENDDO      ENDDO
# Line 1234  contains Line 1119  contains
1119            zu10m(i) = zu10m(i) + u10m(i, nsrf)*pctsrf(i, nsrf)            zu10m(i) = zu10m(i) + u10m(i, nsrf)*pctsrf(i, nsrf)
1120            zv10m(i) = zv10m(i) + v10m(i, nsrf)*pctsrf(i, nsrf)            zv10m(i) = zv10m(i) + v10m(i, nsrf)*pctsrf(i, nsrf)
1121            zxffonte(i) = zxffonte(i) + ffonte(i, nsrf)*pctsrf(i, nsrf)            zxffonte(i) = zxffonte(i) + ffonte(i, nsrf)*pctsrf(i, nsrf)
1122            zxfqcalving(i) = zxfqcalving(i) +  &            zxfqcalving(i) = zxfqcalving(i) + &
1123                 fqcalving(i, nsrf)*pctsrf(i, nsrf)                 fqcalving(i, nsrf)*pctsrf(i, nsrf)
1124            s_pblh(i) = s_pblh(i) + pblh(i, nsrf)*pctsrf(i, nsrf)            s_pblh(i) = s_pblh(i) + pblh(i, nsrf)*pctsrf(i, nsrf)
1125            s_lcl(i) = s_lcl(i) + plcl(i, nsrf)*pctsrf(i, nsrf)            s_lcl(i) = s_lcl(i) + plcl(i, nsrf)*pctsrf(i, nsrf)
# Line 1253  contains Line 1138  contains
1138    
1139      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
1140         DO i = 1, klon         DO i = 1, klon
1141            IF (pctsrf(i, nsrf)  <  epsfra) ftsol(i, nsrf) = zxtsol(i)            IF (pctsrf(i, nsrf) < epsfra) ftsol(i, nsrf) = zxtsol(i)
1142    
1143            IF (pctsrf(i, nsrf)  <  epsfra) t2m(i, nsrf) = zt2m(i)            IF (pctsrf(i, nsrf) < epsfra) t2m(i, nsrf) = zt2m(i)
1144            IF (pctsrf(i, nsrf)  <  epsfra) q2m(i, nsrf) = zq2m(i)            IF (pctsrf(i, nsrf) < epsfra) q2m(i, nsrf) = zq2m(i)
1145            IF (pctsrf(i, nsrf)  <  epsfra) u10m(i, nsrf) = zu10m(i)            IF (pctsrf(i, nsrf) < epsfra) u10m(i, nsrf) = zu10m(i)
1146            IF (pctsrf(i, nsrf)  <  epsfra) v10m(i, nsrf) = zv10m(i)            IF (pctsrf(i, nsrf) < epsfra) v10m(i, nsrf) = zv10m(i)
1147            IF (pctsrf(i, nsrf)  <  epsfra) ffonte(i, nsrf) = zxffonte(i)            IF (pctsrf(i, nsrf) < epsfra) ffonte(i, nsrf) = zxffonte(i)
1148            IF (pctsrf(i, nsrf)  <  epsfra)  &            IF (pctsrf(i, nsrf) < epsfra) &
1149                 fqcalving(i, nsrf) = zxfqcalving(i)                 fqcalving(i, nsrf) = zxfqcalving(i)
1150            IF (pctsrf(i, nsrf)  <  epsfra) pblh(i, nsrf)=s_pblh(i)            IF (pctsrf(i, nsrf) < epsfra) pblh(i, nsrf)=s_pblh(i)
1151            IF (pctsrf(i, nsrf)  <  epsfra) plcl(i, nsrf)=s_lcl(i)            IF (pctsrf(i, nsrf) < epsfra) plcl(i, nsrf)=s_lcl(i)
1152            IF (pctsrf(i, nsrf)  <  epsfra) capCL(i, nsrf)=s_capCL(i)            IF (pctsrf(i, nsrf) < epsfra) capCL(i, nsrf)=s_capCL(i)
1153            IF (pctsrf(i, nsrf)  <  epsfra) oliqCL(i, nsrf)=s_oliqCL(i)            IF (pctsrf(i, nsrf) < epsfra) oliqCL(i, nsrf)=s_oliqCL(i)
1154            IF (pctsrf(i, nsrf)  <  epsfra) cteiCL(i, nsrf)=s_cteiCL(i)            IF (pctsrf(i, nsrf) < epsfra) cteiCL(i, nsrf)=s_cteiCL(i)
1155            IF (pctsrf(i, nsrf)  <  epsfra) pblT(i, nsrf)=s_pblT(i)            IF (pctsrf(i, nsrf) < epsfra) pblT(i, nsrf)=s_pblT(i)
1156            IF (pctsrf(i, nsrf)  <  epsfra) therm(i, nsrf)=s_therm(i)            IF (pctsrf(i, nsrf) < epsfra) therm(i, nsrf)=s_therm(i)
1157            IF (pctsrf(i, nsrf)  <  epsfra) trmb1(i, nsrf)=s_trmb1(i)            IF (pctsrf(i, nsrf) < epsfra) trmb1(i, nsrf)=s_trmb1(i)
1158            IF (pctsrf(i, nsrf)  <  epsfra) trmb2(i, nsrf)=s_trmb2(i)            IF (pctsrf(i, nsrf) < epsfra) trmb2(i, nsrf)=s_trmb2(i)
1159            IF (pctsrf(i, nsrf)  <  epsfra) trmb3(i, nsrf)=s_trmb3(i)            IF (pctsrf(i, nsrf) < epsfra) trmb3(i, nsrf)=s_trmb3(i)
1160         ENDDO         ENDDO
1161      ENDDO      ENDDO
1162    
# Line 1285  contains Line 1170  contains
1170    
1171      DO k = 1, llm      DO k = 1, llm
1172         DO i = 1, klon         DO i = 1, klon
1173            conv_q(i, k) = d_q_dyn(i, k)  &            conv_q(i, k) = d_q_dyn(i, k) &
1174                 + d_q_vdf(i, k)/pdtphys                 + d_q_vdf(i, k)/dtphys
1175            conv_t(i, k) = d_t_dyn(i, k)  &            conv_t(i, k) = d_t_dyn(i, k) &
1176                 + d_t_vdf(i, k)/pdtphys                 + d_t_vdf(i, k)/dtphys
1177         ENDDO         ENDDO
1178      ENDDO      ENDDO
1179      IF (check) THEN      IF (check) THEN
# Line 1304  contains Line 1189  contains
1189         DO k = 1, llm         DO k = 1, llm
1190            DO i = 1, klon            DO i = 1, klon
1191               z_avant(i) = z_avant(i) + (q_seri(i, k)+ql_seri(i, k)) &               z_avant(i) = z_avant(i) + (q_seri(i, k)+ql_seri(i, k)) &
1192                    *(paprs(i, k)-paprs(i, k+1))/RG                    *zmasse(i, k)
1193            ENDDO            ENDDO
1194         ENDDO         ENDDO
1195      ENDIF      ENDIF
1196      IF (iflag_con == 1) THEN      IF (iflag_con == 1) THEN
1197         stop 'reactiver le call conlmd dans physiq.F'         stop 'reactiver le call conlmd dans physiq.F'
1198      ELSE IF (iflag_con == 2) THEN      ELSE IF (iflag_con == 2) THEN
1199         CALL conflx(pdtphys, paprs, pplay, t_seri, q_seri, &         CALL conflx(dtphys, paprs, play, t_seri, q_seri, &
1200              conv_t, conv_q, zxfluxq(1, 1), omega, &              conv_t, conv_q, zxfluxq(1, 1), omega, &
1201              d_t_con, d_q_con, rain_con, snow_con, &              d_t_con, d_q_con, rain_con, snow_con, &
1202              pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &              pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &
# Line 1332  contains Line 1217  contains
1217         ! (driver commun aux versions 3 et 4)         ! (driver commun aux versions 3 et 4)
1218    
1219         IF (ok_cvl) THEN ! new driver for convectL         IF (ok_cvl) THEN ! new driver for convectL
1220              CALL concvl(iflag_con, dtphys, paprs, play, t_seri, q_seri, &
1221            CALL concvl (iflag_con, &                 u_seri, v_seri, tr_seri, ntra, ema_work1, ema_work2, d_t_con, &
1222                 pdtphys, paprs, pplay, t_seri, q_seri, &                 d_q_con, d_u_con, d_v_con, d_tr, rain_con, snow_con, ibas_con, &
1223                 u_seri, v_seri, tr_seri, ntra, &                 itop_con, upwd, dnwd, dnwd0, Ma, cape, tvp, iflagctrl, pbase, &
1224                 ema_work1, ema_work2, &                 bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr, qcondc, wd, pmflxr, &
1225                 d_t_con, d_q_con, d_u_con, d_v_con, d_tr, &                 pmflxs, da, phi, mp)
                rain_con, snow_con, ibas_con, itop_con, &  
                upwd, dnwd, dnwd0, &  
                Ma, cape, tvp, iflagctrl, &  
                pbase, bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr, qcondc, wd, &  
                pmflxr, pmflxs, &  
                da, phi, mp)  
1226    
1227            clwcon0=qcondc            clwcon0=qcondc
1228            pmfu(:, :)=upwd(:, :)+dnwd(:, :)            pmfu=upwd+dnwd
1229           ELSE
        ELSE ! ok_cvl  
1230            ! MAF conema3 ne contient pas les traceurs            ! MAF conema3 ne contient pas les traceurs
1231            CALL conema3 (pdtphys, &            CALL conema3 (dtphys, paprs, play, t_seri, q_seri, &
                paprs, pplay, t_seri, q_seri, &  
1232                 u_seri, v_seri, tr_seri, ntra, &                 u_seri, v_seri, tr_seri, ntra, &
1233                 ema_work1, ema_work2, &                 ema_work1, ema_work2, &
1234                 d_t_con, d_q_con, d_u_con, d_v_con, d_tr, &                 d_t_con, d_q_con, d_u_con, d_v_con, d_tr, &
# Line 1361  contains Line 1238  contains
1238                 pbase &                 pbase &
1239                 , bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr &                 , bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr &
1240                 , clwcon0)                 , clwcon0)
   
1241         ENDIF ! ok_cvl         ENDIF ! ok_cvl
1242    
1243         IF (.NOT. ok_gust) THEN         IF (.NOT. ok_gust) THEN
# Line 1377  contains Line 1253  contains
1253               zx_t = t_seri(i, k)               zx_t = t_seri(i, k)
1254               IF (thermcep) THEN               IF (thermcep) THEN
1255                  zdelta = MAX(0., SIGN(1., rtt-zx_t))                  zdelta = MAX(0., SIGN(1., rtt-zx_t))
1256                  zx_qs  = r2es * FOEEW(zx_t, zdelta)/pplay(i, k)                  zx_qs = r2es * FOEEW(zx_t, zdelta)/play(i, k)
1257                  zx_qs  = MIN(0.5, zx_qs)                  zx_qs = MIN(0.5, zx_qs)
1258                  zcor   = 1./(1.-retv*zx_qs)                  zcor = 1./(1.-retv*zx_qs)
1259                  zx_qs  = zx_qs*zcor                  zx_qs = zx_qs*zcor
1260               ELSE               ELSE
1261                  IF (zx_t < t_coup) THEN                  IF (zx_t < t_coup) THEN
1262                     zx_qs = qsats(zx_t)/pplay(i, k)                     zx_qs = qsats(zx_t)/play(i, k)
1263                  ELSE                  ELSE
1264                     zx_qs = qsatl(zx_t)/pplay(i, k)                     zx_qs = qsatl(zx_t)/play(i, k)
1265                  ENDIF                  ENDIF
1266               ENDIF               ENDIF
1267               zqsat(i, k)=zx_qs               zqsat(i, k)=zx_qs
1268            ENDDO            ENDDO
1269         ENDDO         ENDDO
1270    
1271         !   calcul des proprietes des nuages convectifs         ! calcul des proprietes des nuages convectifs
1272         clwcon0(:, :)=fact_cldcon*clwcon0(:, :)         clwcon0=fact_cldcon*clwcon0
1273         call clouds_gno &         call clouds_gno &
1274              (klon, llm, q_seri, zqsat, clwcon0, ptconv, ratqsc, rnebcon0)              (klon, llm, q_seri, zqsat, clwcon0, ptconv, ratqsc, rnebcon0)
1275      ELSE      ELSE
# Line 1412  contains Line 1288  contains
1288    
1289      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1290         ztit='after convect'         ztit='after convect'
1291         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1292              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1293              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1294         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
1295              , zero_v, zero_v, zero_v, zero_v, zero_v &              zero_v, zero_v, rain_con, snow_con, ztsol, d_h_vcol, d_qt, d_ec, &
1296              , zero_v, rain_con, snow_con, ztsol &              fs_bound, fq_bound )
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
1297      END IF      END IF
1298    
1299      IF (check) THEN      IF (check) THEN
# Line 1432  contains Line 1306  contains
1306            zx_t = zx_t + (rain_con(i)+ &            zx_t = zx_t + (rain_con(i)+ &
1307                 snow_con(i))*airephy(i)/REAL(klon)                 snow_con(i))*airephy(i)/REAL(klon)
1308         ENDDO         ENDDO
1309         zx_t = zx_t/za*pdtphys         zx_t = zx_t/za*dtphys
1310         print *,"Precip=", zx_t         print *,"Precip=", zx_t
1311      ENDIF      ENDIF
1312      IF (zx_ajustq) THEN      IF (zx_ajustq) THEN
# Line 1442  contains Line 1316  contains
1316         DO k = 1, llm         DO k = 1, llm
1317            DO i = 1, klon            DO i = 1, klon
1318               z_apres(i) = z_apres(i) + (q_seri(i, k)+ql_seri(i, k)) &               z_apres(i) = z_apres(i) + (q_seri(i, k)+ql_seri(i, k)) &
1319                    *(paprs(i, k)-paprs(i, k+1))/RG                    *zmasse(i, k)
1320            ENDDO            ENDDO
1321         ENDDO         ENDDO
1322         DO i = 1, klon         DO i = 1, klon
1323            z_factor(i) = (z_avant(i)-(rain_con(i)+snow_con(i))*pdtphys) &            z_factor(i) = (z_avant(i)-(rain_con(i)+snow_con(i))*dtphys) &
1324                 /z_apres(i)                 /z_apres(i)
1325         ENDDO         ENDDO
1326         DO k = 1, llm         DO k = 1, llm
# Line 1462  contains Line 1336  contains
1336    
1337      ! Convection seche (thermiques ou ajustement)      ! Convection seche (thermiques ou ajustement)
1338    
1339      d_t_ajs(:, :)=0.      d_t_ajs=0.
1340      d_u_ajs(:, :)=0.      d_u_ajs=0.
1341      d_v_ajs(:, :)=0.      d_v_ajs=0.
1342      d_q_ajs(:, :)=0.      d_q_ajs=0.
1343      fm_therm(:, :)=0.      fm_therm=0.
1344      entr_therm(:, :)=0.      entr_therm=0.
1345    
1346      IF(prt_level>9)print *, &      if (iflag_thermals == 0) then
1347           'AVANT LA CONVECTION SECHE, iflag_thermals=' &         ! Ajustement sec
1348           , iflag_thermals, '   nsplit_thermals=', nsplit_thermals         CALL ajsec(paprs, play, t_seri, q_seri, d_t_ajs, d_q_ajs)
1349      if(iflag_thermals < 0) then         t_seri = t_seri + d_t_ajs
1350         !  Rien         q_seri = q_seri + d_q_ajs
        IF(prt_level>9)print *,'pas de convection'  
     else if(iflag_thermals == 0) then  
        !  Ajustement sec  
        IF(prt_level>9)print *,'ajsec'  
        CALL ajsec(paprs, pplay, t_seri, q_seri, d_t_ajs, d_q_ajs)  
        t_seri(:, :) = t_seri(:, :) + d_t_ajs(:, :)  
        q_seri(:, :) = q_seri(:, :) + d_q_ajs(:, :)  
1351      else      else
1352         !  Thermiques         ! Thermiques
1353         IF(prt_level>9)print *,'JUSTE AVANT, iflag_thermals=' &         call calltherm(dtphys, play, paprs, pphi, u_seri, v_seri, t_seri, &
1354              , iflag_thermals, '   nsplit_thermals=', nsplit_thermals              q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
        call calltherm(pdtphys &  
             , pplay, paprs, pphi &  
             , u_seri, v_seri, t_seri, q_seri &  
             , d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs &  
             , fm_therm, entr_therm)  
1355      endif      endif
1356    
1357      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1358         ztit='after dry_adjust'         ztit='after dry_adjust'
1359         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1360              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1361              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1362      END IF      END IF
1363    
1364      !  Caclul des ratqs      ! Caclul des ratqs
1365    
1366      !   ratqs convectifs a l'ancienne en fonction de q(z=0)-q / q      ! ratqs convectifs a l'ancienne en fonction de q(z=0)-q / q
1367      !   on ecrase le tableau ratqsc calcule par clouds_gno      ! on ecrase le tableau ratqsc calcule par clouds_gno
1368      if (iflag_cldcon == 1) then      if (iflag_cldcon == 1) then
1369         do k=1, llm         do k=1, llm
1370            do i=1, klon            do i=1, klon
# Line 1516  contains Line 1378  contains
1378         enddo         enddo
1379      endif      endif
1380    
1381      !   ratqs stables      ! ratqs stables
1382      do k=1, llm      do k=1, llm
1383         do i=1, klon         do i=1, klon
1384            ratqss(i, k)=ratqsbas+(ratqshaut-ratqsbas)* &            ratqss(i, k)=ratqsbas+(ratqshaut-ratqsbas)* &
1385                 min((paprs(i, 1)-pplay(i, k))/(paprs(i, 1)-30000.), 1.)                 min((paprs(i, 1)-play(i, k))/(paprs(i, 1)-30000.), 1.)
1386         enddo         enddo
1387      enddo      enddo
1388    
1389      !  ratqs final      ! ratqs final
1390      if (iflag_cldcon == 1 .or.iflag_cldcon == 2) then      if (iflag_cldcon == 1 .or.iflag_cldcon == 2) then
1391         !   les ratqs sont une conbinaison de ratqss et ratqsc         ! les ratqs sont une conbinaison de ratqss et ratqsc
1392         !   ratqs final         ! ratqs final
1393         !   1e4 (en gros 3 heures), en dur pour le moment, est le temps de         ! 1e4 (en gros 3 heures), en dur pour le moment, est le temps de
1394         !   relaxation des ratqs         ! relaxation des ratqs
1395         facteur=exp(-pdtphys*facttemps)         facteur=exp(-dtphys*facttemps)
1396         ratqs(:, :)=max(ratqs(:, :)*facteur, ratqss(:, :))         ratqs=max(ratqs*facteur, ratqss)
1397         ratqs(:, :)=max(ratqs(:, :), ratqsc(:, :))         ratqs=max(ratqs, ratqsc)
1398      else      else
1399         !   on ne prend que le ratqs stable pour fisrtilp         ! on ne prend que le ratqs stable pour fisrtilp
1400         ratqs(:, :)=ratqss(:, :)         ratqs=ratqss
1401      endif      endif
1402    
1403      ! Appeler le processus de condensation a grande echelle      ! Appeler le processus de condensation a grande echelle
1404      ! et le processus de precipitation      ! et le processus de precipitation
1405      CALL fisrtilp(pdtphys, paprs, pplay, &      CALL fisrtilp(dtphys, paprs, play, &
1406           t_seri, q_seri, ptconv, ratqs, &           t_seri, q_seri, ptconv, ratqs, &
1407           d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, &           d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, &
1408           rain_lsc, snow_lsc, &           rain_lsc, snow_lsc, &
# Line 1569  contains Line 1431  contains
1431            zx_t = zx_t + (rain_lsc(i) &            zx_t = zx_t + (rain_lsc(i) &
1432                 + snow_lsc(i))*airephy(i)/REAL(klon)                 + snow_lsc(i))*airephy(i)/REAL(klon)
1433         ENDDO         ENDDO
1434         zx_t = zx_t/za*pdtphys         zx_t = zx_t/za*dtphys
1435         print *,"Precip=", zx_t         print *,"Precip=", zx_t
1436      ENDIF      ENDIF
1437    
1438      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1439         ztit='after fisrt'         ztit='after fisrt'
1440         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1441              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1442              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1443         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
1444              , zero_v, zero_v, zero_v, zero_v, zero_v &              zero_v, zero_v, rain_lsc, snow_lsc, ztsol, d_h_vcol, d_qt, d_ec, &
1445              , zero_v, rain_lsc, snow_lsc, ztsol &              fs_bound, fq_bound )
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
1446      END IF      END IF
1447    
1448      !  PRESCRIPTION DES NUAGES POUR LE RAYONNEMENT      ! PRESCRIPTION DES NUAGES POUR LE RAYONNEMENT
1449    
1450      ! 1. NUAGES CONVECTIFS      ! 1. NUAGES CONVECTIFS
1451    
# Line 1598  contains Line 1458  contains
1458            do k=1, llm            do k=1, llm
1459               do i=1, klon               do i=1, klon
1460                  if (d_q_con(i, k) < 0.) then                  if (d_q_con(i, k) < 0.) then
1461                     rain_tiedtke(i)=rain_tiedtke(i)-d_q_con(i, k)/pdtphys &                     rain_tiedtke(i)=rain_tiedtke(i)-d_q_con(i, k)/dtphys &
1462                          *(paprs(i, k)-paprs(i, k+1))/rg                          *zmasse(i, k)
1463                  endif                  endif
1464               enddo               enddo
1465            enddo            enddo
1466         endif         endif
1467    
1468         ! Nuages diagnostiques pour Tiedtke         ! Nuages diagnostiques pour Tiedtke
1469         CALL diagcld1(paprs, pplay, &         CALL diagcld1(paprs, play, &
1470              rain_tiedtke, snow_tiedtke, ibas_con, itop_con, &              rain_tiedtke, snow_tiedtke, ibas_con, itop_con, &
1471              diafra, dialiq)              diafra, dialiq)
1472         DO k = 1, llm         DO k = 1, llm
# Line 1622  contains Line 1482  contains
1482         ! On prend pour les nuages convectifs le max du calcul de la         ! On prend pour les nuages convectifs le max du calcul de la
1483         ! convection et du calcul du pas de temps précédent diminué d'un facteur         ! convection et du calcul du pas de temps précédent diminué d'un facteur
1484         ! facttemps         ! facttemps
1485         facteur = pdtphys *facttemps         facteur = dtphys *facttemps
1486         do k=1, llm         do k=1, llm
1487            do i=1, klon            do i=1, klon
1488               rnebcon(i, k)=rnebcon(i, k)*facteur               rnebcon(i, k)=rnebcon(i, k)*facteur
# Line 1634  contains Line 1494  contains
1494            enddo            enddo
1495         enddo         enddo
1496    
1497         !   On prend la somme des fractions nuageuses et des contenus en eau         ! On prend la somme des fractions nuageuses et des contenus en eau
1498         cldfra(:, :)=min(max(cldfra(:, :), rnebcon(:, :)), 1.)         cldfra=min(max(cldfra, rnebcon), 1.)
1499         cldliq(:, :)=cldliq(:, :)+rnebcon(:, :)*clwcon(:, :)         cldliq=cldliq+rnebcon*clwcon
1500    
1501      ENDIF      ENDIF
1502    
1503      ! 2. NUAGES STARTIFORMES      ! 2. NUAGES STARTIFORMES
1504    
1505      IF (ok_stratus) THEN      IF (ok_stratus) THEN
1506         CALL diagcld2(paprs, pplay, t_seri, q_seri, diafra, dialiq)         CALL diagcld2(paprs, play, t_seri, q_seri, diafra, dialiq)
1507         DO k = 1, llm         DO k = 1, llm
1508            DO i = 1, klon            DO i = 1, klon
1509               IF (diafra(i, k).GT.cldfra(i, k)) THEN               IF (diafra(i, k).GT.cldfra(i, k)) THEN
# Line 1663  contains Line 1523  contains
1523    
1524      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1525         ztit="after diagcld"         ztit="after diagcld"
1526         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1527              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1528              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1529      END IF      END IF
1530    
1531      ! Calculer l'humidite relative pour diagnostique      ! Calculer l'humidite relative pour diagnostique
# Line 1675  contains Line 1535  contains
1535            zx_t = t_seri(i, k)            zx_t = t_seri(i, k)
1536            IF (thermcep) THEN            IF (thermcep) THEN
1537               zdelta = MAX(0., SIGN(1., rtt-zx_t))               zdelta = MAX(0., SIGN(1., rtt-zx_t))
1538               zx_qs  = r2es * FOEEW(zx_t, zdelta)/pplay(i, k)               zx_qs = r2es * FOEEW(zx_t, zdelta)/play(i, k)
1539               zx_qs  = MIN(0.5, zx_qs)               zx_qs = MIN(0.5, zx_qs)
1540               zcor   = 1./(1.-retv*zx_qs)               zcor = 1./(1.-retv*zx_qs)
1541               zx_qs  = zx_qs*zcor               zx_qs = zx_qs*zcor
1542            ELSE            ELSE
1543               IF (zx_t < t_coup) THEN               IF (zx_t < t_coup) THEN
1544                  zx_qs = qsats(zx_t)/pplay(i, k)                  zx_qs = qsats(zx_t)/play(i, k)
1545               ELSE               ELSE
1546                  zx_qs = qsatl(zx_t)/pplay(i, k)                  zx_qs = qsatl(zx_t)/play(i, k)
1547               ENDIF               ENDIF
1548            ENDIF            ENDIF
1549            zx_rh(i, k) = q_seri(i, k)/zx_qs            zx_rh(i, k) = q_seri(i, k)/zx_qs
# Line 1698  contains Line 1558  contains
1558         CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi)         CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi)
1559    
1560         ! Calculate aerosol optical properties (Olivier Boucher)         ! Calculate aerosol optical properties (Olivier Boucher)
1561         CALL aeropt(pplay, paprs, t_seri, sulfate, rhcl, &         CALL aeropt(play, paprs, t_seri, sulfate, rhcl, &
1562              tau_ae, piz_ae, cg_ae, aerindex)              tau_ae, piz_ae, cg_ae, aerindex)
1563      ELSE      ELSE
1564         tau_ae(:, :, :)=0.0         tau_ae=0.0
1565         piz_ae(:, :, :)=0.0         piz_ae=0.0
1566         cg_ae(:, :, :)=0.0         cg_ae=0.0
1567      ENDIF      ENDIF
1568    
1569      ! Calculer les parametres optiques des nuages et quelques      ! Calculer les parametres optiques des nuages et quelques
1570      ! parametres pour diagnostiques:      ! parametres pour diagnostiques:
1571    
1572      if (ok_newmicro) then      if (ok_newmicro) then
1573         CALL newmicro (paprs, pplay, ok_newmicro, &         CALL newmicro (paprs, play, ok_newmicro, &
1574              t_seri, cldliq, cldfra, cldtau, cldemi, &              t_seri, cldliq, cldfra, cldtau, cldemi, &
1575              cldh, cldl, cldm, cldt, cldq, &              cldh, cldl, cldm, cldt, cldq, &
1576              flwp, fiwp, flwc, fiwc, &              flwp, fiwp, flwc, fiwc, &
# Line 1719  contains Line 1579  contains
1579              bl95_b0, bl95_b1, &              bl95_b0, bl95_b1, &
1580              cldtaupi, re, fl)              cldtaupi, re, fl)
1581      else      else
1582         CALL nuage (paprs, pplay, &         CALL nuage (paprs, play, &
1583              t_seri, cldliq, cldfra, cldtau, cldemi, &              t_seri, cldliq, cldfra, cldtau, cldemi, &
1584              cldh, cldl, cldm, cldt, cldq, &              cldh, cldl, cldm, cldt, cldq, &
1585              ok_aie, &              ok_aie, &
# Line 1743  contains Line 1603  contains
1603                 + falblw(i, is_sic) * pctsrf(i, is_sic)                 + falblw(i, is_sic) * pctsrf(i, is_sic)
1604         ENDDO         ENDDO
1605         ! nouveau rayonnement (compatible Arpege-IFS):         ! nouveau rayonnement (compatible Arpege-IFS):
1606         CALL radlwsw(dist, rmu0, fract,  &         CALL radlwsw(dist, rmu0, fract, paprs, play, zxtsol, albsol, &
1607              paprs, pplay, zxtsol, albsol, albsollw, t_seri, q_seri, &              albsollw, t_seri, q_seri, wo, cldfra, cldemi, cldtau, heat, &
1608              wo, &              heat0, cool, cool0, radsol, albpla, topsw, toplw, solsw, sollw, &
1609              cldfra, cldemi, cldtau, &              sollwdown, topsw0, toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, &
1610              heat, heat0, cool, cool0, radsol, albpla, &              lwup, swdn0, swdn, swup0, swup, ok_ade, ok_aie, tau_ae, piz_ae, &
1611              topsw, toplw, solsw, sollw, &              cg_ae, topswad, solswad, cldtaupi, topswai, solswai)
             sollwdown, &  
             topsw0, toplw0, solsw0, sollw0, &  
             lwdn0, lwdn, lwup0, lwup,  &  
             swdn0, swdn, swup0, swup, &  
             ok_ade, ok_aie, & ! new for aerosol radiative effects  
             tau_ae, piz_ae, cg_ae, &  
             topswad, solswad, &  
             cldtaupi, &  
             topswai, solswai)  
1612         itaprad = 0         itaprad = 0
1613      ENDIF      ENDIF
1614      itaprad = itaprad + 1      itaprad = itaprad + 1
# Line 1767  contains Line 1618  contains
1618      DO k = 1, llm      DO k = 1, llm
1619         DO i = 1, klon         DO i = 1, klon
1620            t_seri(i, k) = t_seri(i, k) &            t_seri(i, k) = t_seri(i, k) &
1621                 + (heat(i, k)-cool(i, k)) * pdtphys/86400.                 + (heat(i, k)-cool(i, k)) * dtphys/86400.
1622         ENDDO         ENDDO
1623      ENDDO      ENDDO
1624    
1625      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1626         ztit='after rad'         ztit='after rad'
1627         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1628              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1629              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1630         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, topsw, toplw, solsw, sollw, &
1631              , topsw, toplw, solsw, sollw, zero_v &              zero_v, zero_v, zero_v, zero_v, ztsol, d_h_vcol, d_qt, d_ec, &
1632              , zero_v, zero_v, zero_v, ztsol &              fs_bound, fq_bound )
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
1633      END IF      END IF
1634    
1635      ! Calculer l'hydrologie de la surface      ! Calculer l'hydrologie de la surface
# Line 1802  contains Line 1651  contains
1651         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
1652      ENDDO      ENDDO
1653    
1654      !moddeblott(jan95)      !mod deb lott(jan95)
1655      ! Appeler le programme de parametrisation de l'orographie      ! Appeler le programme de parametrisation de l'orographie
1656      ! a l'echelle sous-maille:      ! a l'echelle sous-maille:
1657    
1658      IF (ok_orodr) THEN      IF (ok_orodr) THEN
1659           ! selection des points pour lesquels le shema est actif:
        !  selection des points pour lesquels le shema est actif:  
1660         igwd=0         igwd=0
1661         DO i=1, klon         DO i=1, klon
1662            itest(i)=0            itest(i)=0
# Line 1819  contains Line 1667  contains
1667            ENDIF            ENDIF
1668         ENDDO         ENDDO
1669    
1670         CALL drag_noro(klon, llm, pdtphys, paprs, pplay, &         CALL drag_noro(klon, llm, dtphys, paprs, play, &
1671              zmea, zstd, zsig, zgam, zthe, zpic, zval, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, &
1672              igwd, idx, itest, &              igwd, idx, itest, &
1673              t_seri, u_seri, v_seri, &              t_seri, u_seri, v_seri, &
1674              zulow, zvlow, zustrdr, zvstrdr, &              zulow, zvlow, zustrdr, zvstrdr, &
1675              d_t_oro, d_u_oro, d_v_oro)              d_t_oro, d_u_oro, d_v_oro)
1676    
1677         !  ajout des tendances         ! ajout des tendances
1678         DO k = 1, llm         DO k = 1, llm
1679            DO i = 1, klon            DO i = 1, klon
1680               t_seri(i, k) = t_seri(i, k) + d_t_oro(i, k)               t_seri(i, k) = t_seri(i, k) + d_t_oro(i, k)
# Line 1834  contains Line 1682  contains
1682               v_seri(i, k) = v_seri(i, k) + d_v_oro(i, k)               v_seri(i, k) = v_seri(i, k) + d_v_oro(i, k)
1683            ENDDO            ENDDO
1684         ENDDO         ENDDO
1685        ENDIF
     ENDIF ! fin de test sur ok_orodr  
1686    
1687      IF (ok_orolf) THEN      IF (ok_orolf) THEN
1688    
1689         !  selection des points pour lesquels le shema est actif:         ! selection des points pour lesquels le shema est actif:
1690         igwd=0         igwd=0
1691         DO i=1, klon         DO i=1, klon
1692            itest(i)=0            itest(i)=0
# Line 1850  contains Line 1697  contains
1697            ENDIF            ENDIF
1698         ENDDO         ENDDO
1699    
1700         CALL lift_noro(klon, llm, pdtphys, paprs, pplay, &         CALL lift_noro(klon, llm, dtphys, paprs, play, rlat, zmea, zstd, zpic, &
1701              rlat, zmea, zstd, zpic, &              itest, t_seri, u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, &
             itest, &  
             t_seri, u_seri, v_seri, &  
             zulow, zvlow, zustrli, zvstrli, &  
1702              d_t_lif, d_u_lif, d_v_lif)              d_t_lif, d_u_lif, d_v_lif)
1703    
1704         !  ajout des tendances         ! ajout des tendances
1705         DO k = 1, llm         DO k = 1, llm
1706            DO i = 1, klon            DO i = 1, klon
1707               t_seri(i, k) = t_seri(i, k) + d_t_lif(i, k)               t_seri(i, k) = t_seri(i, k) + d_t_lif(i, k)
# Line 1876  contains Line 1720  contains
1720      ENDDO      ENDDO
1721      DO k = 1, llm      DO k = 1, llm
1722         DO i = 1, klon         DO i = 1, klon
1723            zustrph(i)=zustrph(i)+(u_seri(i, k)-u(i, k))/pdtphys* &            zustrph(i)=zustrph(i)+(u_seri(i, k)-u(i, k))/dtphys* zmasse(i, k)
1724                 (paprs(i, k)-paprs(i, k+1))/rg            zvstrph(i)=zvstrph(i)+(v_seri(i, k)-v(i, k))/dtphys* zmasse(i, k)
           zvstrph(i)=zvstrph(i)+(v_seri(i, k)-v(i, k))/pdtphys* &  
                (paprs(i, k)-paprs(i, k+1))/rg  
1725         ENDDO         ENDDO
1726      ENDDO      ENDDO
1727    
1728      !IM calcul composantes axiales du moment angulaire et couple des montagnes      !IM calcul composantes axiales du moment angulaire et couple des montagnes
1729    
1730      CALL aaam_bud (27, klon, llm, gmtime, &      CALL aaam_bud(27, klon, llm, time, ra, rg, romega, rlat, rlon, pphis, &
1731           ra, rg, romega, &           zustrdr, zustrli, zustrph, zvstrdr, zvstrli, zvstrph, paprs, u, v, &
          rlat, rlon, pphis, &  
          zustrdr, zustrli, zustrph, &  
          zvstrdr, zvstrli, zvstrph, &  
          paprs, u, v, &  
1732           aam, torsfc)           aam, torsfc)
1733    
1734      IF (if_ebil >= 2) THEN      IF (if_ebil >= 2) THEN
1735         ztit='after orography'         ztit='after orography'
1736         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1737              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1738              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1739      END IF      END IF
1740    
1741      !AA Installation de l'interface online-offline pour traceurs      ! Calcul des tendances traceurs
1742        call phytrac(rnpb, itap, lmt_pas, julien, time, firstcal, lafin, &
1743      !   Calcul  des tendances traceurs           nqmx-2, dtphys, u, t, paprs, play, pmfu, pmfd, pen_u, pde_u, &
1744             pen_d, pde_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, pctsrf, &
1745      call phytrac(rnpb, itap, lmt_pas, julien,  gmtime, firstcal, lafin, nq-2, &           frac_impa, frac_nucl, pphis, albsol, rhcl, cldfra, rneb, &
1746           pdtphys, u, v, t, paprs, pplay, pmfu,  pmfd,  pen_u,  pde_u,  pen_d, &           diafra, cldliq, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, &
1747           pde_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, pctsrf, &           tr_seri, zmasse)
          frac_impa,  frac_nucl, presnivs, pphis, pphi, albsol, rhcl, cldfra, &  
          rneb,  diafra,  cldliq, itop_con, ibas_con, pmflxr, pmflxs, prfl, &  
          psfl, da, phi, mp, upwd, dnwd, tr_seri)  
1748    
1749      IF (offline) THEN      IF (offline) THEN
1750           call phystokenc(dtphys, rlon, rlat, t, pmfu, pmfd, pen_u, pde_u, &
1751         print*, 'Attention on met a 0 les thermiques pour phystoke'              pen_d, pde_d, fm_therm, entr_therm, ycoefh, yu1, yv1, ftsol, &
1752         call phystokenc(pdtphys, rlon, rlat, &              pctsrf, frac_impa, frac_nucl, pphis, airephy, dtphys, itap)
             t, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &  
             fm_therm, entr_therm, &  
             ycoefh, yu1, yv1, ftsol, pctsrf, &  
             frac_impa, frac_nucl, &  
             pphis, airephy, pdtphys, itap)  
   
1753      ENDIF      ENDIF
1754    
1755      ! Calculer le transport de l'eau et de l'energie (diagnostique)      ! Calculer le transport de l'eau et de l'energie (diagnostique)
1756        CALL transp(paprs, zxtsol, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, &
1757             ue, uq)
1758    
1759      CALL transp (paprs, zxtsol, &      ! diag. bilKP
          t_seri, q_seri, u_seri, v_seri, zphi, &  
          ve, vq, ue, uq)  
1760    
1761      !IM diag. bilKP      CALL transp_lay (paprs, zxtsol, t_seri, q_seri, u_seri, v_seri, zphi, &
   
     CALL transp_lay (paprs, zxtsol, &  
          t_seri, q_seri, u_seri, v_seri, zphi, &  
1762           ve_lay, vq_lay, ue_lay, uq_lay)           ve_lay, vq_lay, ue_lay, uq_lay)
1763    
1764      ! Accumuler les variables a stocker dans les fichiers histoire:      ! Accumuler les variables a stocker dans les fichiers histoire:
# Line 1944  contains Line 1770  contains
1770            d_t_ec(i, k)=0.5/ZRCPD &            d_t_ec(i, k)=0.5/ZRCPD &
1771                 *(u(i, k)**2+v(i, k)**2-u_seri(i, k)**2-v_seri(i, k)**2)                 *(u(i, k)**2+v(i, k)**2-u_seri(i, k)**2-v_seri(i, k)**2)
1772            t_seri(i, k)=t_seri(i, k)+d_t_ec(i, k)            t_seri(i, k)=t_seri(i, k)+d_t_ec(i, k)
1773            d_t_ec(i, k) = d_t_ec(i, k)/pdtphys            d_t_ec(i, k) = d_t_ec(i, k)/dtphys
1774         END DO         END DO
1775      END DO      END DO
1776      !-jld ec_conser      !-jld ec_conser
1777      IF (if_ebil >= 1) THEN      IF (if_ebil >= 1) THEN
1778         ztit='after physic'         ztit='after physic'
1779         CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, pdtphys &         CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, dtphys, t_seri, q_seri, &
1780              , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &              ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1781              , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)              d_ql, d_qs, d_ec)
1782         !     Comme les tendances de la physique sont ajoute dans la dynamique,         ! Comme les tendances de la physique sont ajoute dans la dynamique,
1783         !     on devrait avoir que la variation d'entalpie par la dynamique         ! on devrait avoir que la variation d'entalpie par la dynamique
1784         !     est egale a la variation de la physique au pas de temps precedent.         ! est egale a la variation de la physique au pas de temps precedent.
1785         !     Donc la somme de ces 2 variations devrait etre nulle.         ! Donc la somme de ces 2 variations devrait etre nulle.
1786         call diagphy(airephy, ztit, ip_ebil &         call diagphy(airephy, ztit, ip_ebil, topsw, toplw, solsw, sollw, sens, &
1787              , topsw, toplw, solsw, sollw, sens &              evap, rain_fall, snow_fall, ztsol, d_h_vcol, d_qt, d_ec, &
1788              , evap, rain_fall, snow_fall, ztsol &              fs_bound, fq_bound )
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
1789    
1790         d_h_vcol_phy=d_h_vcol         d_h_vcol_phy=d_h_vcol
1791    
1792      END IF      END IF
1793    
1794      !   SORTIES      ! SORTIES
   
     !IM Interpolation sur les niveaux de pression du NMC  
     call calcul_STDlev  
1795    
1796      !cc prw = eau precipitable      !cc prw = eau precipitable
1797      DO i = 1, klon      DO i = 1, klon
1798         prw(i) = 0.         prw(i) = 0.
1799         DO k = 1, llm         DO k = 1, llm
1800            prw(i) = prw(i) + &            prw(i) = prw(i) + q_seri(i, k)*zmasse(i, k)
                q_seri(i, k)*(paprs(i, k)-paprs(i, k+1))/RG  
1801         ENDDO         ENDDO
1802      ENDDO      ENDDO
1803    
     !IM initialisation + calculs divers diag AMIP2  
     call calcul_divers  
   
1804      ! Convertir les incrementations en tendances      ! Convertir les incrementations en tendances
1805    
1806      DO k = 1, llm      DO k = 1, llm
1807         DO i = 1, klon         DO i = 1, klon
1808            d_u(i, k) = ( u_seri(i, k) - u(i, k) ) / pdtphys            d_u(i, k) = ( u_seri(i, k) - u(i, k) ) / dtphys
1809            d_v(i, k) = ( v_seri(i, k) - v(i, k) ) / pdtphys            d_v(i, k) = ( v_seri(i, k) - v(i, k) ) / dtphys
1810            d_t(i, k) = ( t_seri(i, k)-t(i, k) ) / pdtphys            d_t(i, k) = ( t_seri(i, k)-t(i, k) ) / dtphys
1811            d_qx(i, k, ivap) = ( q_seri(i, k) - qx(i, k, ivap) ) / pdtphys            d_qx(i, k, ivap) = ( q_seri(i, k) - qx(i, k, ivap) ) / dtphys
1812            d_qx(i, k, iliq) = ( ql_seri(i, k) - qx(i, k, iliq) ) / pdtphys            d_qx(i, k, iliq) = ( ql_seri(i, k) - qx(i, k, iliq) ) / dtphys
1813         ENDDO         ENDDO
1814      ENDDO      ENDDO
1815    
1816      IF (nq >= 3) THEN      IF (nqmx >= 3) THEN
1817         DO iq = 3, nq         DO iq = 3, nqmx
1818            DO  k = 1, llm            DO k = 1, llm
1819               DO  i = 1, klon               DO i = 1, klon
1820                  d_qx(i, k, iq) = ( tr_seri(i, k, iq-2) - qx(i, k, iq) ) / pdtphys                  d_qx(i, k, iq) = (tr_seri(i, k, iq-2) - qx(i, k, iq)) / dtphys
1821               ENDDO               ENDDO
1822            ENDDO            ENDDO
1823         ENDDO         ENDDO
1824      ENDIF      ENDIF
1825    
1826      ! Sauvegarder les valeurs de t et q a la fin de la physique:      ! Sauvegarder les valeurs de t et q a la fin de la physique:
   
1827      DO k = 1, llm      DO k = 1, llm
1828         DO i = 1, klon         DO i = 1, klon
1829            t_ancien(i, k) = t_seri(i, k)            t_ancien(i, k) = t_seri(i, k)
# Line 2015  contains Line 1831  contains
1831         ENDDO         ENDDO
1832      ENDDO      ENDDO
1833    
1834      !   Ecriture des sorties      ! Ecriture des sorties
   
1835      call write_histhf      call write_histhf
1836      call write_histday      call write_histday
1837      call write_histins      call write_histins
1838    
1839      ! Si c'est la fin, il faut conserver l'etat de redemarrage      ! Si c'est la fin, il faut conserver l'etat de redemarrage
   
1840      IF (lafin) THEN      IF (lafin) THEN
1841         itau_phy = itau_phy + itap         itau_phy = itau_phy + itap
1842         CALL phyredem ("restartphy.nc", radpas, rlat, rlon, pctsrf, ftsol, &         CALL phyredem("restartphy.nc", rlat, rlon, pctsrf, ftsol, &
1843              ftsoil, tslab, seaice, fqsurf, qsol, &              ftsoil, tslab, seaice, fqsurf, qsol, &
1844              fsnow, falbe, falblw, fevap, rain_fall, snow_fall, &              fsnow, falbe, falblw, fevap, rain_fall, snow_fall, &
1845              solsw, sollwdown, dlw, &              solsw, sollwdown, dlw, &
1846              radsol, frugs, agesno, &              radsol, frugs, agesno, &
1847              zmea, zstd, zsig, zgam, zthe, zpic, zval, rugoro, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, &
1848              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0)              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0)
1849      ENDIF      ENDIF
1850    
1851    contains      firstcal = .FALSE.
   
     subroutine calcul_STDlev  
   
       !     From phylmd/calcul_STDlev.h, v 1.1 2005/05/25 13:10:09  
   
       !IM on initialise les champs en debut du jour ou du mois  
   
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, tsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, usumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, vsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, wsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, phisumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, qsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, rhsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, uvsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, vqsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, vTsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, wqsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, vphisumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, wTsumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, u2sumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, v2sumSTD)  
       CALL ini_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, &  
            tnondef, T2sumSTD)  
   
       !IM on interpole sur les niveaux STD de pression a chaque pas de  
       !temps de la physique  
   
       DO k=1, nlevSTD  
   
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               t_seri, tlevSTD(:, k))  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               u_seri, ulevSTD(:, k))  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               v_seri, vlevSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=paprs(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., zx_tmp_fi3d, rlevSTD(k), &  
               omega, wlevSTD(:, k))  
   
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zphi/RG, philevSTD(:, k))  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               qx(:, :, ivap), qlevSTD(:, k))  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_rh*100., rhlevSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=u_seri(i, l)*v_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, uvSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=v_seri(i, l)*q_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, vqSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=v_seri(i, l)*t_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, vTSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=omega(i, l)*qx(i, l, ivap)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, wqSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=v_seri(i, l)*zphi(i, l)/RG  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, vphiSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=omega(i, l)*t_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, wTSTD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=u_seri(i, l)*u_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, u2STD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=v_seri(i, l)*v_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, v2STD(:, k))  
   
          DO l=1, llm  
             DO i=1, klon  
                zx_tmp_fi3d(i, l)=t_seri(i, l)*t_seri(i, l)  
             ENDDO !i  
          ENDDO !l  
          CALL plevel(klon, llm, .true., pplay, rlevSTD(k), &  
               zx_tmp_fi3d, T2STD(:, k))  
   
       ENDDO !k=1, nlevSTD  
   
       !IM on somme les valeurs definies a chaque pas de temps de la  
       ! physique ou toutes les 6 heures  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.TRUE.  
       CALL undefSTD(nlevSTD, itap, tlevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, tsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, ulevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, usumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, vlevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, vsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, wlevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, wsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, philevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, phisumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, qlevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, qsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, rhlevSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, rhsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, uvSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, uvsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, vqSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, vqsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, vTSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, vTsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, wqSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, wqsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, vphiSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, vphisumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, wTSTD, &  
            ecrit_hf, &  
            oknondef, tnondef, wTsumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, u2STD, &  
            ecrit_hf, &  
            oknondef, tnondef, u2sumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, v2STD, &  
            ecrit_hf, &  
            oknondef, tnondef, v2sumSTD)  
   
       oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE.  
       CALL undefSTD(nlevSTD, itap, T2STD, &  
            ecrit_hf, &  
            oknondef, tnondef, T2sumSTD)  
   
       !IM on moyenne a la fin du jour ou du mois  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, tsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, usumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, vsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, wsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, phisumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, qsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, rhsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, uvsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, vqsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, vTsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, wqsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, vphisumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, wTsumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, u2sumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, v2sumSTD)  
   
       CALL moy_undefSTD(nlevSTD, itap, &  
            ecrit_day, ecrit_mth, ecrit_hf2mth, &  
            tnondef, T2sumSTD)  
   
       !IM interpolation a chaque pas de temps du SWup(clr) et  
       !SWdn(clr) a 200 hPa  
   
       CALL plevel(klon, klevp1, .true., paprs, 20000., &  
            swdn0, SWdn200clr)  
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            swdn, SWdn200)  
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            swup0, SWup200clr)  
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            swup, SWup200)  
   
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            lwdn0, LWdn200clr)  
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            lwdn, LWdn200)  
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            lwup0, LWup200clr)  
       CALL plevel(klon, klevp1, .false., paprs, 20000., &  
            lwup, LWup200)  
   
     end SUBROUTINE calcul_STDlev  
   
     !****************************************************  
   
     SUBROUTINE calcul_divers  
   
       ! From phylmd/calcul_divers.h, v 1.1 2005/05/25 13:10:09  
   
       ! initialisations diverses au "debut" du mois  
   
       IF(MOD(itap, ecrit_mth) == 1) THEN  
          DO i=1, klon  
             nday_rain(i)=0.  
          ENDDO  
       ENDIF  
   
       IF(MOD(itap, ecrit_day) == 0) THEN  
          !IM calcul total_rain, nday_rain  
          DO i = 1, klon  
             total_rain(i)=rain_fall(i)+snow_fall(i)    
             IF(total_rain(i).GT.0.) nday_rain(i)=nday_rain(i)+1.  
          ENDDO  
       ENDIF  
   
     End SUBROUTINE calcul_divers  
1852    
1853      !***********************************************    contains
1854    
1855      subroutine write_histday      subroutine write_histday
1856    
1857        !     From phylmd/write_histday.h, v 1.3 2005/05/25 13:10:09        use gr_phy_write_3d_m, only: gr_phy_write_3d
1858          integer itau_w ! pas de temps ecriture
1859    
1860        if (ok_journe) THEN        !------------------------------------------------
   
          ndex2d = 0  
          ndex3d = 0  
   
          ! Champs 2D:  
1861    
1862          if (ok_journe) THEN
1863           itau_w = itau_phy + itap           itau_w = itau_phy + itap
1864             if (nqmx <= 4) then
1865           !   FIN ECRITURE DES CHAMPS 3D              call histwrite(nid_day, "Sigma_O3_Royer", itau_w, &
1866                     gr_phy_write_3d(wo) * 1e3)
1867                ! (convert "wo" from kDU to DU)
1868             end if
1869           if (ok_sync) then           if (ok_sync) then
1870              call histsync(nid_day)              call histsync(nid_day)
1871           endif           endif
   
1872        ENDIF        ENDIF
1873    
1874      End subroutine write_histday      End subroutine write_histday
# Line 2417  contains Line 1877  contains
1877    
1878      subroutine write_histhf      subroutine write_histhf
1879    
1880        ! From phylmd/write_histhf.h, v 1.5 2005/05/25 13:10:09        ! From phylmd/write_histhf.h, version 1.5 2005/05/25 13:10:09
1881    
1882        ndex2d = 0        !------------------------------------------------
       ndex3d = 0  
   
       itau_w = itau_phy + itap  
1883    
1884        call write_histhf3d        call write_histhf3d
1885    
# Line 2436  contains Line 1893  contains
1893    
1894      subroutine write_histins      subroutine write_histins
1895    
1896        ! From phylmd/write_histins.h, v 1.2 2005/05/25 13:10:09        ! From phylmd/write_histins.h, version 1.2 2005/05/25 13:10:09
1897    
1898        real zout        real zout
1899          integer itau_w ! pas de temps ecriture
1900    
1901        !--------------------------------------------------        !--------------------------------------------------
1902    
1903        IF (ok_instan) THEN        IF (ok_instan) THEN
   
          ndex2d = 0  
          ndex3d = 0  
   
1904           ! Champs 2D:           ! Champs 2D:
1905    
1906           zsto = pdtphys * ecrit_ins           zsto = dtphys * ecrit_ins
1907           zout = pdtphys * ecrit_ins           zout = dtphys * ecrit_ins
1908           itau_w = itau_phy + itap           itau_w = itau_phy + itap
1909    
1910           i = NINT(zout/zsto)           i = NINT(zout/zsto)
1911           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), pphis, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), pphis, zx_tmp_2d)
1912           CALL histwrite(nid_ins, "phis", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "phis", itau_w, zx_tmp_2d)
1913    
1914           i = NINT(zout/zsto)           i = NINT(zout/zsto)
1915           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), airephy, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), airephy, zx_tmp_2d)
1916           CALL histwrite(nid_ins, "aire", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "aire", itau_w, zx_tmp_2d)
1917    
1918           DO i = 1, klon           DO i = 1, klon
1919              zx_tmp_fi2d(i) = paprs(i, 1)              zx_tmp_fi2d(i) = paprs(i, 1)
1920           ENDDO           ENDDO
1921           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
1922           CALL histwrite(nid_ins, "psol", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "psol", itau_w, zx_tmp_2d)
1923    
1924           DO i = 1, klon           DO i = 1, klon
1925              zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)              zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
1926           ENDDO           ENDDO
1927           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
1928           CALL histwrite(nid_ins, "precip", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "precip", itau_w, zx_tmp_2d)
1929    
1930           DO i = 1, klon           DO i = 1, klon
1931              zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)              zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
1932           ENDDO           ENDDO
1933           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
1934           CALL histwrite(nid_ins, "plul", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "plul", itau_w, zx_tmp_2d)
1935    
1936           DO i = 1, klon           DO i = 1, klon
1937              zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)              zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
1938           ENDDO           ENDDO
1939           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
1940           CALL histwrite(nid_ins, "pluc", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "pluc", itau_w, zx_tmp_2d)
1941    
1942           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxtsol, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxtsol, zx_tmp_2d)
1943           CALL histwrite(nid_ins, "tsol", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "tsol", itau_w, zx_tmp_2d)
1944           !ccIM           !ccIM
1945           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zt2m, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zt2m, zx_tmp_2d)
1946           CALL histwrite(nid_ins, "t2m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "t2m", itau_w, zx_tmp_2d)
1947    
1948           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zq2m, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zq2m, zx_tmp_2d)
1949           CALL histwrite(nid_ins, "q2m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "q2m", itau_w, zx_tmp_2d)
1950    
1951           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zu10m, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zu10m, zx_tmp_2d)
1952           CALL histwrite(nid_ins, "u10m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "u10m", itau_w, zx_tmp_2d)
1953    
1954           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zv10m, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zv10m, zx_tmp_2d)
1955           CALL histwrite(nid_ins, "v10m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "v10m", itau_w, zx_tmp_2d)
1956    
1957           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), snow_fall, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), snow_fall, zx_tmp_2d)
1958           CALL histwrite(nid_ins, "snow", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "snow", itau_w, zx_tmp_2d)
1959    
1960           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragm, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragm, zx_tmp_2d)
1961           CALL histwrite(nid_ins, "cdrm", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "cdrm", itau_w, zx_tmp_2d)
1962    
1963           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragh, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragh, zx_tmp_2d)
1964           CALL histwrite(nid_ins, "cdrh", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "cdrh", itau_w, zx_tmp_2d)
1965    
1966           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), toplw, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), toplw, zx_tmp_2d)
1967           CALL histwrite(nid_ins, "topl", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "topl", itau_w, zx_tmp_2d)
1968    
1969           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), evap, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), evap, zx_tmp_2d)
1970           CALL histwrite(nid_ins, "evap", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "evap", itau_w, zx_tmp_2d)
1971    
1972           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), solsw, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), solsw, zx_tmp_2d)
1973           CALL histwrite(nid_ins, "sols", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "sols", itau_w, zx_tmp_2d)
1974    
1975           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollw, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollw, zx_tmp_2d)
1976           CALL histwrite(nid_ins, "soll", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "soll", itau_w, zx_tmp_2d)
1977    
1978           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollwdown, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollwdown, zx_tmp_2d)
1979           CALL histwrite(nid_ins, "solldown", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "solldown", itau_w, zx_tmp_2d)
               ndex2d)  
1980    
1981           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), bils, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), bils, zx_tmp_2d)
1982           CALL histwrite(nid_ins, "bils", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "bils", itau_w, zx_tmp_2d)
1983    
1984           zx_tmp_fi2d(1:klon)=-1*sens(1:klon)           zx_tmp_fi2d(1:klon)=-1*sens(1:klon)
1985           !     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sens, zx_tmp_2d)           ! CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sens, zx_tmp_2d)
1986           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
1987           CALL histwrite(nid_ins, "sens", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "sens", itau_w, zx_tmp_2d)
1988    
1989           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), fder, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), fder, zx_tmp_2d)
1990           CALL histwrite(nid_ins, "fder", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "fder", itau_w, zx_tmp_2d)
1991    
1992           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_oce), zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_oce), zx_tmp_2d)
1993           CALL histwrite(nid_ins, "dtsvdfo", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "dtsvdfo", itau_w, zx_tmp_2d)
               ndex2d)  
1994    
1995           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_ter), zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_ter), zx_tmp_2d)
1996           CALL histwrite(nid_ins, "dtsvdft", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "dtsvdft", itau_w, zx_tmp_2d)
               ndex2d)  
1997    
1998           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_lic), zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_lic), zx_tmp_2d)
1999           CALL histwrite(nid_ins, "dtsvdfg", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "dtsvdfg", itau_w, zx_tmp_2d)
               ndex2d)  
2000    
2001           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_sic), zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_sic), zx_tmp_2d)
2002           CALL histwrite(nid_ins, "dtsvdfi", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "dtsvdfi", itau_w, zx_tmp_2d)
               ndex2d)  
2003    
2004           DO nsrf = 1, nbsrf           DO nsrf = 1, nbsrf
2005              !XXX              !XXX
2006              zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.              zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.
2007              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2008              CALL histwrite(nid_ins, "pourc_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "pourc_"//clnsurf(nsrf), itau_w, &
2009                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2010    
2011              zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)              zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)
2012              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2013              CALL histwrite(nid_ins, "fract_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "fract_"//clnsurf(nsrf), itau_w, &
2014                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2015    
2016              zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)              zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)
2017              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2018              CALL histwrite(nid_ins, "sens_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "sens_"//clnsurf(nsrf), itau_w, &
2019                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2020    
2021              zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)              zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)
2022              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2023              CALL histwrite(nid_ins, "lat_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "lat_"//clnsurf(nsrf), itau_w, &
2024                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2025    
2026              zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)              zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)
2027              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2028              CALL histwrite(nid_ins, "tsol_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "tsol_"//clnsurf(nsrf), itau_w, &
2029                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2030    
2031              zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)              zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)
2032              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2033              CALL histwrite(nid_ins, "taux_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "taux_"//clnsurf(nsrf), itau_w, &
2034                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2035    
2036              zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)              zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)
2037              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2038              CALL histwrite(nid_ins, "tauy_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "tauy_"//clnsurf(nsrf), itau_w, &
2039                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2040    
2041              zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf)              zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf)
2042              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2043              CALL histwrite(nid_ins, "rugs_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "rugs_"//clnsurf(nsrf), itau_w, &
2044                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2045    
2046              zx_tmp_fi2d(1 : klon) = falbe( 1 : klon, nsrf)              zx_tmp_fi2d(1 : klon) = falbe( 1 : klon, nsrf)
2047              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)
2048              CALL histwrite(nid_ins, "albe_"//clnsurf(nsrf), itau_w, &              CALL histwrite(nid_ins, "albe_"//clnsurf(nsrf), itau_w, &
2049                   zx_tmp_2d, iim*(jjm + 1), ndex2d)                   zx_tmp_2d)
2050    
2051           END DO           END DO
2052           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsol, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsol, zx_tmp_2d)
2053           CALL histwrite(nid_ins, "albs", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "albs", itau_w, zx_tmp_2d)
2054           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsollw, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsollw, zx_tmp_2d)
2055           CALL histwrite(nid_ins, "albslw", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "albslw", itau_w, zx_tmp_2d)
2056    
2057           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxrugs, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxrugs, zx_tmp_2d)
2058           CALL histwrite(nid_ins, "rugs", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "rugs", itau_w, zx_tmp_2d)
2059    
2060           !IM cf. AM 081204 BEG           !IM cf. AM 081204 BEG
2061    
2062           !HBTM2           !HBTM2
2063    
2064           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblh, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblh, zx_tmp_2d)
2065           CALL histwrite(nid_ins, "s_pblh", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "s_pblh", itau_w, zx_tmp_2d)
2066    
2067           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblt, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblt, zx_tmp_2d)
2068           CALL histwrite(nid_ins, "s_pblt", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "s_pblt", itau_w, zx_tmp_2d)
2069    
2070           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_lcl, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_lcl, zx_tmp_2d)
2071           CALL histwrite(nid_ins, "s_lcl", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)           CALL histwrite(nid_ins, "s_lcl", itau_w, zx_tmp_2d)
2072    
2073           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_capCL, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_capCL, zx_tmp_2d)
2074           CALL histwrite(nid_ins, "s_capCL", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_capCL", itau_w, zx_tmp_2d)
               ndex2d)  
2075    
2076           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_oliqCL, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_oliqCL, zx_tmp_2d)
2077           CALL histwrite(nid_ins, "s_oliqCL", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_oliqCL", itau_w, zx_tmp_2d)
               ndex2d)  
2078    
2079           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_cteiCL, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_cteiCL, zx_tmp_2d)
2080           CALL histwrite(nid_ins, "s_cteiCL", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_cteiCL", itau_w, zx_tmp_2d)
               ndex2d)  
2081    
2082           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_therm, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_therm, zx_tmp_2d)
2083           CALL histwrite(nid_ins, "s_therm", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_therm", itau_w, zx_tmp_2d)
               ndex2d)  
2084    
2085           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb1, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb1, zx_tmp_2d)
2086           CALL histwrite(nid_ins, "s_trmb1", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_trmb1", itau_w, zx_tmp_2d)
               ndex2d)  
2087    
2088           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb2, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb2, zx_tmp_2d)
2089           CALL histwrite(nid_ins, "s_trmb2", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_trmb2", itau_w, zx_tmp_2d)
               ndex2d)  
2090    
2091           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb3, zx_tmp_2d)           CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb3, zx_tmp_2d)
2092           CALL histwrite(nid_ins, "s_trmb3", itau_w, zx_tmp_2d, iim*(jjm + 1), &           CALL histwrite(nid_ins, "s_trmb3", itau_w, zx_tmp_2d)
               ndex2d)  
2093    
2094           !IM cf. AM 081204 END           !IM cf. AM 081204 END
2095    
2096           ! Champs 3D:           ! Champs 3D:
2097    
2098           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d)
2099           CALL histwrite(nid_ins, "temp", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "temp", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2100    
2101           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d)
2102           CALL histwrite(nid_ins, "vitu", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "vitu", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2103    
2104           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d)
2105           CALL histwrite(nid_ins, "vitv", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "vitv", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2106    
2107           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), zphi, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), zphi, zx_tmp_3d)
2108           CALL histwrite(nid_ins, "geop", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "geop", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2109    
2110           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), pplay, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), play, zx_tmp_3d)
2111           CALL histwrite(nid_ins, "pres", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "pres", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2112    
2113           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_t_vdf, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_t_vdf, zx_tmp_3d)
2114           CALL histwrite(nid_ins, "dtvdf", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "dtvdf", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2115    
2116           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_q_vdf, zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_q_vdf, zx_tmp_3d)
2117           CALL histwrite(nid_ins, "dqvdf", itau_w, zx_tmp_3d, &           CALL histwrite(nid_ins, "dqvdf", itau_w, zx_tmp_3d)
               iim*(jjm + 1)*llm, ndex3d)  
2118    
2119           if (ok_sync) then           if (ok_sync) then
2120              call histsync(nid_ins)              call histsync(nid_ins)
# Line 2692  contains Line 2127  contains
2127    
2128      subroutine write_histhf3d      subroutine write_histhf3d
2129    
2130        ! From phylmd/write_histhf3d.h, v 1.2 2005/05/25 13:10:09        ! From phylmd/write_histhf3d.h, version 1.2 2005/05/25 13:10:09
2131    
2132        ndex2d = 0        integer itau_w ! pas de temps ecriture
2133        ndex3d = 0  
2134          !-------------------------------------------------------
2135    
2136        itau_w = itau_phy + itap        itau_w = itau_phy + itap
2137    
2138        ! Champs 3D:        ! Champs 3D:
2139    
2140        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d)        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d)
2141        CALL histwrite(nid_hf3d, "temp", itau_w, zx_tmp_3d, &        CALL histwrite(nid_hf3d, "temp", itau_w, zx_tmp_3d)
            iim*(jjm + 1)*llm, ndex3d)  
2142    
2143        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), qx(1, 1, ivap), zx_tmp_3d)        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), qx(1, 1, ivap), zx_tmp_3d)
2144        CALL histwrite(nid_hf3d, "ovap", itau_w, zx_tmp_3d, &        CALL histwrite(nid_hf3d, "ovap", itau_w, zx_tmp_3d)
            iim*(jjm + 1)*llm, ndex3d)  
2145    
2146        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d)        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d)
2147        CALL histwrite(nid_hf3d, "vitu", itau_w, zx_tmp_3d, &        CALL histwrite(nid_hf3d, "vitu", itau_w, zx_tmp_3d)
            iim*(jjm + 1)*llm, ndex3d)  
2148    
2149        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d)        CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d)
2150        CALL histwrite(nid_hf3d, "vitv", itau_w, zx_tmp_3d, &        CALL histwrite(nid_hf3d, "vitv", itau_w, zx_tmp_3d)
            iim*(jjm + 1)*llm, ndex3d)  
2151    
2152        if (nbtr >= 3) then        if (nbtr >= 3) then
2153           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), tr_seri(1, 1, 3), &           CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), tr_seri(1, 1, 3), &
2154                zx_tmp_3d)                zx_tmp_3d)
2155           CALL histwrite(nid_hf3d, "O3", itau_w, zx_tmp_3d, iim*(jjm + 1)*llm, &           CALL histwrite(nid_hf3d, "O3", itau_w, zx_tmp_3d)
               ndex3d)  
2156        end if        end if
2157    
2158        if (ok_sync) then        if (ok_sync) then
# Line 2732  contains Line 2163  contains
2163    
2164    END SUBROUTINE physiq    END SUBROUTINE physiq
2165    
   !****************************************************  
   
   FUNCTION qcheck(klon, klev, paprs, q, ql, aire)  
   
     ! From phylmd/physiq.F, v 1.22 2006/02/20 09:38:28  
   
     use YOMCST  
     IMPLICIT none  
   
     ! Calculer et imprimer l'eau totale. A utiliser pour verifier  
     ! la conservation de l'eau  
   
     INTEGER klon, klev  
     REAL, intent(in):: paprs(klon, klev+1)  
     real q(klon, klev), ql(klon, klev)  
     REAL aire(klon)  
     REAL qtotal, zx, qcheck  
     INTEGER i, k  
   
     zx = 0.0  
     DO i = 1, klon  
        zx = zx + aire(i)  
     ENDDO  
     qtotal = 0.0  
     DO k = 1, klev  
        DO i = 1, klon  
           qtotal = qtotal + (q(i, k)+ql(i, k)) * aire(i) &  
                *(paprs(i, k)-paprs(i, k+1))/RG  
        ENDDO  
     ENDDO  
   
     qcheck = qtotal/zx  
   
   END FUNCTION qcheck  
   
2166  end module physiq_m  end module physiq_m

Legend:
Removed from v.12  
changed lines
  Added in v.47

  ViewVC Help
Powered by ViewVC 1.1.21