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

Diff of /trunk/Sources/phylmd/physiq.f

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

trunk/libf/phylmd/physiq.f90 revision 10 by guez, Fri Apr 18 14:45:53 2008 UTC trunk/Sources/phylmd/physiq.f revision 206 by guez, Tue Aug 30 12:52:46 2016 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, dayvrai, time, paprs, play, pphi, pphis, u, v, t, &
8         pplay, pphi, pphis, presnivs, clesphy0, u, v, t, qx, omega, d_u, d_v, &         qx, omega, d_u, d_v, d_t, d_qx)
        d_t, d_qx, d_ps, dudyn, PVteta)  
   
     ! From phylmd/physiq.F, v 1.22 2006/02/20 09:38:28  
   
     ! Author : Z.X. Li (LMD/CNRS), date: 1993/08/18  
   
     ! Objet: Moniteur general de la physique du modele  
     !AA      Modifications quant aux traceurs :  
     !AA                  -  uniformisation des parametrisations ds phytrac  
     !AA                  -  stockage des moyennes des champs necessaires  
     !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, iflag_con, ok_orolf, ok_orodr, ecrit_mth, ecrit_day, &  
          nbapp_rad, cycle_diurne, cdmmax, cdhmax, &  
          co2_ppm, ecrit_reg, ecrit_tra, ksta, ksta_ter, new_oliq, &  
          ok_kzmin, soil_model  
     use iniprint, only: lunout, prt_level  
     use abort_gcm_m, only: abort_gcm  
     use YOMCST, only: rcpd, rtt, rlvtt, rg, ra, rsigma, retv, romega  
     use comgeomphy  
     use ctherm  
     use phytrac_m, only: phytrac  
     use oasis_m  
     use radepsi  
     use radopt  
     use yoethf  
     use ini_hist, only: ini_histhf, ini_histday, ini_histins  
     use orbite_m, only: orbite, zenang  
     use phyetat0_m, only: phyetat0, rlat, rlon  
     use hgardfou_m, only: hgardfou  
     use conf_phys_m, only: conf_phys  
   
     ! Declaration des constantes et des fonctions thermodynamiques :  
     use fcttre, only: thermcep, foeew, qsats, qsatl  
   
     ! Variables argument:  
   
     INTEGER nq ! input nombre de traceurs (y compris vapeur d'eau)  
     REAL, intent(in):: rdayvrai ! input numero du jour de l'experience  
     REAL, intent(in):: gmtime ! heure de la journée en fraction de jour  
     REAL pdtphys ! input pas d'integration pour la physique (seconde)  
     LOGICAL, intent(in):: firstcal ! first call to "calfis"  
     logical, intent(in):: lafin ! dernier passage  
   
     REAL, intent(in):: paprs(klon, llm+1)  
     ! (pression pour chaque inter-couche, en Pa)  
       
     REAL, intent(in):: pplay(klon, llm)  
     ! (input pression pour le mileu de chaque couche (en Pa))  
   
     REAL pphi(klon, llm)    
     ! (input geopotentiel de chaque couche (g z) (reference sol))  
   
     REAL pphis(klon) ! input geopotentiel du sol  
   
     REAL presnivs(llm)  
     ! (input pressions approximat. des milieux couches ( en PA))  
   
     REAL u(klon, llm)  ! input vitesse dans la direction X (de O a E) en m/s  
     REAL v(klon, llm)  ! input vitesse Y (de S a N) en m/s  
     REAL t(klon, llm)  ! input temperature (K)  
   
     REAL qx(klon, llm, nq)  
     ! (input humidite specifique (kg/kg) et d'autres traceurs)  
   
     REAL omega(klon, llm)  ! input vitesse verticale en Pa/s  
     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  
   
     INTEGER nbteta  
     PARAMETER(nbteta=3)  
   
     REAL PVteta(klon, nbteta)  
     ! (output vorticite potentielle a des thetas constantes)  
   
     LOGICAL ok_cvl  ! pour activer le nouveau driver pour convection KE  
     PARAMETER (ok_cvl=.TRUE.)  
     LOGICAL ok_gust ! pour activer l'effet des gust sur flux surface  
     PARAMETER (ok_gust=.FALSE.)  
   
     LOGICAL check ! Verifier la conservation du modele en eau  
     PARAMETER (check=.FALSE.)  
     LOGICAL ok_stratus ! Ajouter artificiellement les stratus  
     PARAMETER (ok_stratus=.FALSE.)  
   
     ! Parametres lies au coupleur OASIS:  
     INTEGER, SAVE :: npas, nexca  
     logical rnpb  
     parameter(rnpb=.true.)  
     !      ocean = type de modele ocean a utiliser: force, slab, couple  
     character(len=6) ocean  
     SAVE ocean  
   
     logical ok_ocean  
     SAVE ok_ocean  
   
     !IM "slab" ocean  
     REAL tslab(klon)    !Temperature du slab-ocean  
     SAVE tslab  
     REAL seaice(klon)   !glace de mer (kg/m2)  
     SAVE seaice  
     REAL fluxo(klon)    !flux turbulents ocean-glace de mer  
     REAL fluxg(klon)    !flux turbulents ocean-atmosphere  
   
     ! Modele thermique du sol, a activer pour le cycle diurne:  
     logical ok_veget  
     save ok_veget  
     LOGICAL ok_journe ! sortir le fichier journalier  
     save ok_journe  
   
     LOGICAL ok_mensuel ! sortir le fichier mensuel  
9    
10      LOGICAL ok_instan ! sortir le fichier instantane      ! From phylmd/physiq.F, version 1.22 2006/02/20 09:38:28
11      save ok_instan      ! (subversion revision 678)
12    
13      LOGICAL ok_region ! sortir le fichier regional      ! Author: Z. X. Li (LMD/CNRS) 1993
     PARAMETER (ok_region=.FALSE.)  
14    
15      !     pour phsystoke avec thermiques      ! This is the main procedure for the "physics" part of the program.
16      REAL fm_therm(klon, llm+1)  
17      REAL entr_therm(klon, llm)      use aaam_bud_m, only: aaam_bud
18      real q2(klon, llm+1, nbsrf)      USE abort_gcm_m, ONLY: abort_gcm
19      save q2      use ajsec_m, only: ajsec
20        use calltherm_m, only: calltherm
21      INTEGER ivap          ! indice de traceurs pour vapeur d'eau      USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, ksta, ksta_ter, ok_kzmin, &
22      PARAMETER (ivap=1)           ok_instan
23      INTEGER iliq          ! indice de traceurs pour eau liquide      USE clesphys2, ONLY: cycle_diurne, conv_emanuel, nbapp_rad, new_oliq, &
24      PARAMETER (iliq=2)           ok_orodr, ok_orolf
25        USE clmain_m, ONLY: clmain
26      REAL t_ancien(klon, llm), q_ancien(klon, llm)      use clouds_gno_m, only: clouds_gno
27      SAVE t_ancien, q_ancien      use comconst, only: dtphys
28      LOGICAL ancien_ok      USE comgeomphy, ONLY: airephy
29      SAVE ancien_ok      USE concvl_m, ONLY: concvl
30        USE conf_gcm_m, ONLY: offline, day_step, iphysiq, lmt_pas
31        USE conf_phys_m, ONLY: conf_phys
32        use conflx_m, only: conflx
33        USE ctherm, ONLY: iflag_thermals, nsplit_thermals
34        use diagcld2_m, only: diagcld2
35        USE dimens_m, ONLY: llm, nqmx
36        USE dimphy, ONLY: klon
37        USE dimsoil, ONLY: nsoilmx
38        use drag_noro_m, only: drag_noro
39        use dynetat0_m, only: day_ref, annee_ref
40        USE fcttre, ONLY: foeew, qsatl, qsats, thermcep
41        use fisrtilp_m, only: fisrtilp
42        USE hgardfou_m, ONLY: hgardfou
43        USE histsync_m, ONLY: histsync
44        USE histwrite_phy_m, ONLY: histwrite_phy
45        USE indicesol, ONLY: clnsurf, epsfra, is_lic, is_oce, is_sic, is_ter, &
46             nbsrf
47        USE ini_histins_m, ONLY: ini_histins, nid_ins
48        use netcdf95, only: NF95_CLOSE
49        use newmicro_m, only: newmicro
50        use nr_util, only: assert
51        use nuage_m, only: nuage
52        USE orbite_m, ONLY: orbite
53        USE ozonecm_m, ONLY: ozonecm
54        USE phyetat0_m, ONLY: phyetat0, rlat, rlon
55        USE phyredem_m, ONLY: phyredem
56        USE phyredem0_m, ONLY: phyredem0
57        USE phystokenc_m, ONLY: phystokenc
58        USE phytrac_m, ONLY: phytrac
59        use radlwsw_m, only: radlwsw
60        use yoegwd, only: sugwd
61        USE suphec_m, ONLY: rcpd, retv, rg, rlvtt, romega, rsigma, rtt
62        use time_phylmdz, only: itap, increment_itap
63        use transp_m, only: transp
64        use transp_lay_m, only: transp_lay
65        use unit_nml_m, only: unit_nml
66        USE ymds2ju_m, ONLY: ymds2ju
67        USE yoethf_m, ONLY: r2es, rvtmp2
68        use zenang_m, only: zenang
69    
70      REAL d_t_dyn(klon, llm) ! tendance dynamique pour "t" (K/s)      logical, intent(in):: lafin ! dernier passage
     REAL d_q_dyn(klon, llm)  ! tendance dynamique pour "q" (kg/kg/s)  
   
     real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)  
71    
72      !IM Amip2 PV a theta constante      integer, intent(in):: dayvrai
73        ! current day number, based at value 1 on January 1st of annee_ref
74    
75      CHARACTER(LEN=3) ctetaSTD(nbteta)      REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour
     DATA ctetaSTD/'350', '380', '405'/  
     REAL rtetaSTD(nbteta)  
     DATA rtetaSTD/350., 380., 405./  
   
     !MI Amip2 PV a theta constante  
   
     INTEGER klevp1  
     PARAMETER(klevp1=llm+1)  
   
     REAL swdn0(klon, klevp1), swdn(klon, klevp1)  
     REAL swup0(klon, klevp1), swup(klon, klevp1)  
     SAVE swdn0, swdn, swup0, swup  
   
     REAL SWdn200clr(klon), SWdn200(klon)  
     REAL SWup200clr(klon), SWup200(klon)  
     SAVE SWdn200clr, SWdn200, SWup200clr, SWup200  
   
     REAL lwdn0(klon, klevp1), lwdn(klon, klevp1)  
     REAL lwup0(klon, klevp1), lwup(klon, klevp1)  
     SAVE lwdn0, lwdn, lwup0, lwup  
   
     REAL LWdn200clr(klon), LWdn200(klon)  
     REAL LWup200clr(klon), LWup200(klon)  
     SAVE LWdn200clr, LWdn200, LWup200clr, LWup200  
   
     !IM Amip2  
     ! variables a une pression donnee  
   
     integer nlevSTD  
     PARAMETER(nlevSTD=17)  
     real rlevSTD(nlevSTD)  
     DATA rlevSTD/100000., 92500., 85000., 70000., &  
          60000., 50000., 40000., 30000., 25000., 20000., &  
          15000., 10000., 7000., 5000., 3000., 2000., 1000./  
     CHARACTER(LEN=4) clevSTD(nlevSTD)  
     DATA clevSTD/'1000', '925 ', '850 ', '700 ', '600 ', &  
          '500 ', '400 ', '300 ', '250 ', '200 ', '150 ', '100 ', &  
          '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  
76    
77      ! prw: precipitable water      REAL, intent(in):: paprs(:, :) ! (klon, llm + 1)
78      real prw(klon)      ! pression pour chaque inter-couche, en Pa
79    
80      ! flwp, fiwp = Liquid Water Path & Ice Water Path (kg/m2)      REAL, intent(in):: play(:, :) ! (klon, llm)
81      ! flwc, fiwc = Liquid Water Content & Ice Water Content (kg/kg)      ! pression pour le mileu de chaque couche (en Pa)
     REAL flwp(klon), fiwp(klon)  
     REAL flwc(klon, llm), fiwc(klon, llm)  
82    
83      INTEGER l, kmax, lmax      REAL, intent(in):: pphi(:, :) ! (klon, llm)
84      PARAMETER(kmax=8, lmax=8)      ! géopotentiel de chaque couche (référence sol)
     INTEGER kmaxm1, lmaxm1  
     PARAMETER(kmaxm1=kmax-1, lmaxm1=lmax-1)  
   
     REAL zx_tau(kmaxm1), zx_pc(lmaxm1)  
     DATA zx_tau/0.0, 0.3, 1.3, 3.6, 9.4, 23., 60./  
     DATA zx_pc/50., 180., 310., 440., 560., 680., 800./  
   
     ! cldtopres pression au sommet des nuages  
     REAL cldtopres(lmaxm1)  
     DATA cldtopres/50., 180., 310., 440., 560., 680., 800./  
   
     ! taulev: numero du niveau de tau dans les sorties ISCCP  
     CHARACTER(LEN=4) taulev(kmaxm1)  
   
     DATA taulev/'tau0', 'tau1', 'tau2', 'tau3', 'tau4', 'tau5', 'tau6'/  
     CHARACTER(LEN=3) pclev(lmaxm1)  
     DATA pclev/'pc1', 'pc2', 'pc3', 'pc4', 'pc5', 'pc6', 'pc7'/  
   
     CHARACTER(LEN=28) cnameisccp(lmaxm1, kmaxm1)  
     DATA cnameisccp/'pc< 50hPa, tau< 0.3', 'pc= 50-180hPa, tau< 0.3', &  
          'pc= 180-310hPa, tau< 0.3', 'pc= 310-440hPa, tau< 0.3', &  
          'pc= 440-560hPa, tau< 0.3', 'pc= 560-680hPa, tau< 0.3', &  
          'pc= 680-800hPa, tau< 0.3', 'pc< 50hPa, tau= 0.3-1.3', &  
          'pc= 50-180hPa, tau= 0.3-1.3', 'pc= 180-310hPa, tau= 0.3-1.3', &  
          'pc= 310-440hPa, tau= 0.3-1.3', 'pc= 440-560hPa, tau= 0.3-1.3', &  
          'pc= 560-680hPa, tau= 0.3-1.3', 'pc= 680-800hPa, tau= 0.3-1.3', &  
          'pc< 50hPa, tau= 1.3-3.6', 'pc= 50-180hPa, tau= 1.3-3.6', &  
          'pc= 180-310hPa, tau= 1.3-3.6', 'pc= 310-440hPa, tau= 1.3-3.6', &  
          'pc= 440-560hPa, tau= 1.3-3.6', 'pc= 560-680hPa, tau= 1.3-3.6', &  
          'pc= 680-800hPa, tau= 1.3-3.6', 'pc< 50hPa, tau= 3.6-9.4', &  
          'pc= 50-180hPa, tau= 3.6-9.4', 'pc= 180-310hPa, tau= 3.6-9.4', &  
          'pc= 310-440hPa, tau= 3.6-9.4', 'pc= 440-560hPa, tau= 3.6-9.4', &  
          'pc= 560-680hPa, tau= 3.6-9.4', 'pc= 680-800hPa, tau= 3.6-9.4', &  
          'pc< 50hPa, tau= 9.4-23', 'pc= 50-180hPa, tau= 9.4-23', &  
          'pc= 180-310hPa, tau= 9.4-23', 'pc= 310-440hPa, tau= 9.4-23', &  
          'pc= 440-560hPa, tau= 9.4-23', 'pc= 560-680hPa, tau= 9.4-23', &  
          'pc= 680-800hPa, tau= 9.4-23', 'pc< 50hPa, tau= 23-60', &  
          'pc= 50-180hPa, tau= 23-60', 'pc= 180-310hPa, tau= 23-60', &  
          'pc= 310-440hPa, tau= 23-60', 'pc= 440-560hPa, tau= 23-60', &  
          'pc= 560-680hPa, tau= 23-60', 'pc= 680-800hPa, tau= 23-60', &  
          'pc< 50hPa, tau> 60.', 'pc= 50-180hPa, tau> 60.', &  
          'pc= 180-310hPa, tau> 60.', 'pc= 310-440hPa, tau> 60.', &  
          'pc= 440-560hPa, tau> 60.', 'pc= 560-680hPa, tau> 60.', &  
          'pc= 680-800hPa, tau> 60.'/  
   
     !IM ISCCP simulator v3.4  
   
     integer nid_hf, nid_hf3d  
     save nid_hf, nid_hf3d  
   
     INTEGER        longcles  
     PARAMETER    ( longcles = 20 )  
     REAL clesphy0( longcles      )  
85    
86      ! Variables propres a la physique      REAL, intent(in):: pphis(:) ! (klon) géopotentiel du sol
87    
88      REAL, SAVE:: dtime ! pas temporel de la physique (s)      REAL, intent(in):: u(:, :) ! (klon, llm)
89        ! vitesse dans la direction X (de O a E) en m / s
90    
91      INTEGER, save:: radpas      REAL, intent(in):: v(:, :) ! (klon, llm) vitesse Y (de S a N) en m / s
92      ! (Radiative transfer computations are made every "radpas" call to      REAL, intent(in):: t(:, :) ! (klon, llm) temperature (K)
     ! "physiq".)  
93    
94      REAL radsol(klon)      REAL, intent(in):: qx(:, :, :) ! (klon, llm, nqmx)
95      SAVE radsol               ! bilan radiatif au sol calcule par code radiatif      ! (humidit\'e sp\'ecifique et fractions massiques des autres traceurs)
96    
97      INTEGER, SAVE:: itap ! number of calls to "physiq"      REAL, intent(in):: omega(:, :) ! (klon, llm) vitesse verticale en Pa / s
98      REAL co2_ppm_etat0      REAL, intent(out):: d_u(:, :) ! (klon, llm) tendance physique de "u" (m s-2)
99      REAL solaire_etat0      REAL, intent(out):: d_v(:, :) ! (klon, llm) tendance physique de "v" (m s-2)
100        REAL, intent(out):: d_t(:, :) ! (klon, llm) tendance physique de "t" (K / s)
101    
102      REAL ftsol(klon, nbsrf)      REAL, intent(out):: d_qx(:, :, :) ! (klon, llm, nqmx)
103      SAVE ftsol                  ! temperature du sol      ! tendance physique de "qx" (s-1)
104    
105      REAL ftsoil(klon, nsoilmx, nbsrf)      ! Local:
     SAVE ftsoil                 ! temperature dans le sol  
106    
107      REAL fevap(klon, nbsrf)      LOGICAL:: firstcal = .true.
     SAVE fevap                 ! evaporation  
     REAL fluxlat(klon, nbsrf)  
     SAVE fluxlat  
108    
109      REAL fqsurf(klon, nbsrf)      LOGICAL, PARAMETER:: ok_stratus = .FALSE.
110      SAVE fqsurf                 ! humidite de l'air au contact de la surface      ! Ajouter artificiellement les stratus
111    
112      REAL qsol(klon)      ! pour phystoke avec thermiques
113      SAVE qsol                  ! hauteur d'eau dans le sol      REAL fm_therm(klon, llm + 1)
114        REAL entr_therm(klon, llm)
115        real, save:: q2(klon, llm + 1, nbsrf)
116    
117      REAL fsnow(klon, nbsrf)      INTEGER, PARAMETER:: ivap = 1 ! indice de traceur pour vapeur d'eau
118      SAVE fsnow                  ! epaisseur neigeuse      INTEGER, PARAMETER:: iliq = 2 ! indice de traceur pour eau liquide
119    
120      REAL falbe(klon, nbsrf)      REAL, save:: t_ancien(klon, llm), q_ancien(klon, llm)
121      SAVE falbe                  ! albedo par type de surface      LOGICAL, save:: ancien_ok
     REAL falblw(klon, nbsrf)  
     SAVE falblw                 ! albedo par type de surface  
122    
123      !  Parametres de l'Orographie a l'Echelle Sous-Maille (OESM):      REAL d_t_dyn(klon, llm) ! tendance dynamique pour "t" (K / s)
124        REAL d_q_dyn(klon, llm) ! tendance dynamique pour "q" (kg / kg / s)
125    
126      REAL zmea(klon)      real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
     SAVE zmea                   ! orographie moyenne  
127    
128      REAL zstd(klon)      REAL, save:: swdn0(klon, llm + 1), swdn(klon, llm + 1)
129      SAVE zstd                   ! deviation standard de l'OESM      REAL, save:: swup0(klon, llm + 1), swup(klon, llm + 1)
130    
131      REAL zsig(klon)      REAL, save:: lwdn0(klon, llm + 1), lwdn(klon, llm + 1)
132      SAVE zsig                   ! pente de l'OESM      REAL, save:: lwup0(klon, llm + 1), lwup(klon, llm + 1)
133    
134      REAL zgam(klon)      ! prw: precipitable water
135      save zgam                   ! anisotropie de l'OESM      real prw(klon)
136    
137      REAL zthe(klon)      ! flwp, fiwp = Liquid Water Path & Ice Water Path (kg / m2)
138      SAVE zthe                   ! orientation de l'OESM      ! flwc, fiwc = Liquid Water Content & Ice Water Content (kg / kg)
139        REAL flwp(klon), fiwp(klon)
140        REAL flwc(klon, llm), fiwc(klon, llm)
141    
142      REAL zpic(klon)      ! Variables propres a la physique
     SAVE zpic                   ! Maximum de l'OESM  
143    
144      REAL zval(klon)      INTEGER, save:: radpas
145      SAVE zval                   ! Minimum de l'OESM      ! Radiative transfer computations are made every "radpas" call to
146        ! "physiq".
147    
148      REAL rugoro(klon)      REAL, save:: radsol(klon) ! bilan radiatif au sol calcule par code radiatif
     SAVE rugoro                 ! longueur de rugosite de l'OESM  
149    
150      REAL zulow(klon), zvlow(klon)      REAL, save:: ftsol(klon, nbsrf) ! skin temperature of surface fraction
151    
152      INTEGER igwd, idx(klon), itest(klon)      REAL, save:: ftsoil(klon, nsoilmx, nbsrf)
153        ! soil temperature of surface fraction
154    
155      REAL agesno(klon, nbsrf)      REAL, save:: fevap(klon, nbsrf) ! evaporation
156      SAVE agesno                 ! age de la neige      REAL, save:: fluxlat(klon, nbsrf)
157    
158      REAL run_off_lic_0(klon)      REAL, save:: fqsurf(klon, nbsrf)
159      SAVE run_off_lic_0      ! humidite de l'air au contact de la surface
     !KE43  
     ! Variables liees a la convection de K. Emanuel (sb):  
160    
161      REAL bas, top             ! cloud base and top levels      REAL, save:: qsol(klon)
162      SAVE bas      ! column-density of water in soil, in kg m-2
     SAVE top  
163    
164      REAL Ma(klon, llm)        ! undilute upward mass flux      REAL, save:: fsnow(klon, nbsrf) ! epaisseur neigeuse
165      SAVE Ma      REAL, save:: falbe(klon, nbsrf) ! albedo visible par type de surface
     REAL qcondc(klon, llm)    ! in-cld water content from convect  
     SAVE qcondc  
     REAL ema_work1(klon, llm), ema_work2(klon, llm)  
     SAVE ema_work1, ema_work2  
166    
167      REAL wd(klon) ! sb      ! Param\`etres de l'orographie \`a l'\'echelle sous-maille (OESM) :
168      SAVE wd       ! sb      REAL, save:: zmea(klon) ! orographie moyenne
169        REAL, save:: zstd(klon) ! deviation standard de l'OESM
170        REAL, save:: zsig(klon) ! pente de l'OESM
171        REAL, save:: zgam(klon) ! anisotropie de l'OESM
172        REAL, save:: zthe(klon) ! orientation de l'OESM
173        REAL, save:: zpic(klon) ! Maximum de l'OESM
174        REAL, save:: zval(klon) ! Minimum de l'OESM
175        REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM
176        REAL zulow(klon), zvlow(klon)
177        INTEGER igwd, itest(klon)
178    
179      ! Variables locales pour la couche limite (al1):      REAL, save:: agesno(klon, nbsrf) ! age de la neige
180        REAL, save:: run_off_lic_0(klon)
181    
182      ! Variables locales:      ! Variables li\'ees \`a la convection d'Emanuel :
183        REAL, save:: Ma(klon, llm) ! undilute upward mass flux
184        REAL, save:: qcondc(klon, llm) ! in-cld water content from convect
185        REAL, save:: sig1(klon, llm), w01(klon, llm)
186    
187        ! Variables pour la couche limite (Alain Lahellec) :
188      REAL cdragh(klon) ! drag coefficient pour T and Q      REAL cdragh(klon) ! drag coefficient pour T and Q
189      REAL cdragm(klon) ! drag coefficient pour vent      REAL cdragm(klon) ! drag coefficient pour vent
190    
191      !AA  Pour phytrac      ! Pour phytrac :
192      REAL ycoefh(klon, llm)    ! coef d'echange pour phytrac      REAL ycoefh(klon, llm) ! coef d'echange pour phytrac
193      REAL yu1(klon)            ! vents dans la premiere couche U      REAL yu1(klon) ! vents dans la premiere couche U
194      REAL yv1(klon)            ! vents dans la premiere couche V      REAL yv1(klon) ! vents dans la premiere couche V
195      REAL ffonte(klon, nbsrf)    !Flux thermique utilise pour fondre la neige  
196      REAL fqcalving(klon, nbsrf) !Flux d'eau "perdue" par la surface      REAL, save:: ffonte(klon, nbsrf)
197      !                               !et necessaire pour limiter la      ! flux thermique utilise pour fondre la neige
198      !                               !hauteur de neige, en kg/m2/s  
199        REAL, save:: fqcalving(klon, nbsrf)
200        ! flux d'eau "perdue" par la surface et necessaire pour limiter la
201        ! hauteur de neige, en kg / m2 / s
202    
203      REAL zxffonte(klon), zxfqcalving(klon)      REAL zxffonte(klon), zxfqcalving(klon)
204    
205      REAL pfrac_impa(klon, llm)! Produits des coefs lessivage impaction      REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction
206      save pfrac_impa      REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation
207      REAL pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation  
208      save pfrac_nucl      REAL, save:: pfrac_1nucl(klon, llm)
209      REAL pfrac_1nucl(klon, llm)! Produits des coefs lessi nucl (alpha = 1)      ! Produits des coefs lessi nucl (alpha = 1)
210      save pfrac_1nucl  
211      REAL frac_impa(klon, llm) ! fractions d'aerosols lessivees (impaction)      REAL frac_impa(klon, llm) ! fractions d'aerosols lessivees (impaction)
212      REAL frac_nucl(klon, llm) ! idem (nucleation)      REAL frac_nucl(klon, llm) ! idem (nucleation)
213    
214      !AA      REAL, save:: rain_fall(klon)
215      REAL rain_fall(klon) ! pluie      ! liquid water mass flux (kg / m2 / s), positive down
216      REAL snow_fall(klon) ! neige  
217      save snow_fall, rain_fall      REAL, save:: snow_fall(klon)
218      !IM cf FH pour Tiedtke 080604      ! solid water mass flux (kg / m2 / s), positive down
     REAL rain_tiedtke(klon), snow_tiedtke(klon)  
219    
220      REAL total_rain(klon), nday_rain(klon)      REAL rain_tiedtke(klon), snow_tiedtke(klon)
     save nday_rain  
221    
222      REAL evap(klon), devap(klon) ! evaporation et sa derivee      REAL evap(klon) ! flux d'\'evaporation au sol
223      REAL sens(klon), dsens(klon) ! chaleur sensible et sa derivee      real devap(klon) ! derivative of the evaporation flux at the surface
224      REAL dlw(klon)    ! derivee infra rouge      REAL sens(klon) ! flux de chaleur sensible au sol
225      SAVE dlw      real dsens(klon) ! derivee du flux de chaleur sensible au sol
226        REAL, save:: dlw(klon) ! derivee infra rouge
227      REAL bils(klon) ! bilan de chaleur au sol      REAL bils(klon) ! bilan de chaleur au sol
228      REAL fder(klon) ! Derive de flux (sensible et latente)      REAL, save:: fder(klon) ! Derive de flux (sensible et latente)
     save fder  
229      REAL ve(klon) ! integr. verticale du transport meri. de l'energie      REAL ve(klon) ! integr. verticale du transport meri. de l'energie
230      REAL vq(klon) ! integr. verticale du transport meri. de l'eau      REAL vq(klon) ! integr. verticale du transport meri. de l'eau
231      REAL ue(klon) ! integr. verticale du transport zonal de l'energie      REAL ue(klon) ! integr. verticale du transport zonal de l'energie
232      REAL uq(klon) ! integr. verticale du transport zonal de l'eau      REAL uq(klon) ! integr. verticale du transport zonal de l'eau
233    
234      REAL frugs(klon, nbsrf) ! longueur de rugosite      REAL, save:: frugs(klon, nbsrf) ! longueur de rugosite
     save frugs  
235      REAL zxrugs(klon) ! longueur de rugosite      REAL zxrugs(klon) ! longueur de rugosite
236    
237      ! Conditions aux limites      ! Conditions aux limites
238    
239      INTEGER julien      INTEGER julien
240        REAL, save:: pctsrf(klon, nbsrf) ! percentage of surface
241        REAL, save:: albsol(klon) ! albedo du sol total visible
242        REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU
243    
244        real, save:: clwcon(klon, llm), rnebcon(klon, llm)
245        real, save:: clwcon0(klon, llm), rnebcon0(klon, llm)
246    
247        REAL rhcl(klon, llm) ! humiditi relative ciel clair
248        REAL dialiq(klon, llm) ! eau liquide nuageuse
249        REAL diafra(klon, llm) ! fraction nuageuse
250        REAL cldliq(klon, llm) ! eau liquide nuageuse
251        REAL cldfra(klon, llm) ! fraction nuageuse
252        REAL cldtau(klon, llm) ! epaisseur optique
253        REAL cldemi(klon, llm) ! emissivite infrarouge
254    
255        REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface
256        REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface
257        REAL flux_u(klon, nbsrf) ! flux turbulent de vitesse u à la surface
258        REAL flux_v(klon, nbsrf) ! flux turbulent de vitesse v à la surface
259    
260        ! Le rayonnement n'est pas calcul\'e tous les pas, il faut donc que
261        ! les variables soient r\'emanentes.
262        REAL, save:: heat(klon, llm) ! chauffage solaire
263        REAL, save:: heat0(klon, llm) ! chauffage solaire ciel clair
264        REAL, save:: cool(klon, llm) ! refroidissement infrarouge
265        REAL, save:: cool0(klon, llm) ! refroidissement infrarouge ciel clair
266        REAL, save:: topsw(klon), toplw(klon), solsw(klon)
267        REAL, save:: sollw(klon) ! rayonnement infrarouge montant \`a la surface
268        real, save:: sollwdown(klon) ! downward LW flux at surface
269        REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
270        REAL, save:: albpla(klon)
271        REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous-surface
272        REAL fsolsw(klon, nbsrf) ! flux solaire absorb\'e pour chaque sous-surface
273    
274        REAL conv_q(klon, llm) ! convergence de l'humidite (kg / kg / s)
275        REAL conv_t(klon, llm) ! convergence of temperature (K / s)
276    
277      INTEGER, SAVE:: lmt_pas ! number of time steps of "physics" per day      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut
278      REAL pctsrf(klon, nbsrf)      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree
     !IM  
     REAL pctsrf_new(klon, nbsrf) !pourcentage surfaces issus d'ORCHIDEE  
   
     SAVE pctsrf                 ! sous-fraction du sol  
     REAL albsol(klon)  
     SAVE albsol                 ! albedo du sol total  
     REAL albsollw(klon)  
     SAVE albsollw                 ! albedo du sol total  
   
     REAL, SAVE:: wo(klon, llm) ! ozone  
   
     ! Declaration des procedures appelees  
   
     EXTERNAL alboc     ! calculer l'albedo sur ocean  
     EXTERNAL ajsec     ! ajustement sec  
     EXTERNAL clmain    ! couche limite  
     !KE43  
     EXTERNAL conema3  ! convect4.3  
     EXTERNAL fisrtilp  ! schema de condensation a grande echelle (pluie)  
     EXTERNAL nuage     ! calculer les proprietes radiatives  
     EXTERNAL ozonecm   ! prescrire l'ozone  
     EXTERNAL phyredem  ! ecrire l'etat de redemarrage de la physique  
     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)  
   
     ! Variables locales  
   
     real clwcon(klon, llm), rnebcon(klon, llm)  
     real clwcon0(klon, llm), rnebcon0(klon, llm)  
   
     save rnebcon, clwcon  
   
     REAL rhcl(klon, llm)    ! humiditi relative ciel clair  
     REAL dialiq(klon, llm)  ! eau liquide nuageuse  
     REAL diafra(klon, llm)  ! fraction nuageuse  
     REAL cldliq(klon, llm)  ! eau liquide nuageuse  
     REAL cldfra(klon, llm)  ! fraction nuageuse  
     REAL cldtau(klon, llm)  ! epaisseur optique  
     REAL cldemi(klon, llm)  ! emissivite infrarouge  
   
     REAL fluxq(klon, llm, nbsrf)   ! flux turbulent d'humidite  
     REAL fluxt(klon, llm, nbsrf)   ! flux turbulent de chaleur  
     REAL fluxu(klon, llm, nbsrf)   ! flux turbulent de vitesse u  
     REAL fluxv(klon, llm, nbsrf)   ! flux turbulent de vitesse v  
   
     REAL zxfluxt(klon, llm)  
     REAL zxfluxq(klon, llm)  
     REAL zxfluxu(klon, llm)  
     REAL zxfluxv(klon, llm)  
   
     REAL heat(klon, llm)    ! chauffage solaire  
     REAL heat0(klon, llm)   ! chauffage solaire ciel clair  
     REAL cool(klon, llm)    ! refroidissement infrarouge  
     REAL cool0(klon, llm)   ! refroidissement infrarouge ciel clair  
     REAL topsw(klon), toplw(klon), solsw(klon), sollw(klon)  
     real sollwdown(klon)    ! downward LW flux at surface  
     REAL topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)  
     REAL albpla(klon)  
     REAL fsollw(klon, nbsrf)   ! bilan flux IR pour chaque sous surface  
     REAL fsolsw(klon, nbsrf)   ! flux solaire absorb. pour chaque sous surface  
     ! Le rayonnement n'est pas calcule tous les pas, il faut donc  
     !                      sauvegarder les sorties du rayonnement  
     SAVE  heat, cool, albpla, topsw, toplw, solsw, sollw, sollwdown  
     SAVE  topsw0, toplw0, solsw0, sollw0, heat0, cool0  
   
     INTEGER itaprad  
     SAVE itaprad  
   
     REAL conv_q(klon, llm) ! convergence de l'humidite (kg/kg/s)  
     REAL conv_t(klon, llm) ! convergence de la temperature(K/s)  
   
     REAL cldl(klon), cldm(klon), cldh(klon) !nuages bas, moyen et haut  
     REAL cldt(klon), cldq(klon) !nuage total, eau liquide integree  
   
     REAL zxtsol(klon), zxqsurf(klon), zxsnow(klon), zxfluxlat(klon)  
   
     REAL dist, rmu0(klon), fract(klon)  
     REAL zdtime ! pas de temps du rayonnement (s)  
     real zlongi  
279    
280      REAL z_avant(klon), z_apres(klon), z_factor(klon)      REAL zxqsurf(klon), zxsnow(klon), zxfluxlat(klon)
     LOGICAL zx_ajustq  
281    
282      REAL za, zb      REAL dist, mu0(klon), fract(klon)
283      REAL zx_t, zx_qs, zdelta, zcor, zlvdcp, zlsdcp      real longi
284        REAL z_avant(klon), z_apres(klon), z_factor(klon)
285        REAL zb
286        REAL zx_t, zx_qs, zcor
287      real zqsat(klon, llm)      real zqsat(klon, llm)
288      INTEGER i, k, iq, nsrf      INTEGER i, k, iq, nsrf
289      REAL t_coup      REAL, PARAMETER:: t_coup = 234.
     PARAMETER (t_coup=234.0)  
   
290      REAL zphi(klon, llm)      REAL zphi(klon, llm)
291    
292      !IM cf. AM Variables locales pour la CLA (hbtm2)      ! cf. Anne Mathieu, variables pour la couche limite atmosphérique (hbtm)
293    
294      REAL pblh(klon, nbsrf)           ! Hauteur de couche limite      REAL, SAVE:: pblh(klon, nbsrf) ! Hauteur de couche limite
295      REAL plcl(klon, nbsrf)           ! Niveau de condensation de la CLA      REAL, SAVE:: plcl(klon, nbsrf) ! Niveau de condensation de la CLA
296      REAL capCL(klon, nbsrf)          ! CAPE de couche limite      REAL, SAVE:: capCL(klon, nbsrf) ! CAPE de couche limite
297      REAL oliqCL(klon, nbsrf)          ! eau_liqu integree de couche limite      REAL, SAVE:: oliqCL(klon, nbsrf) ! eau_liqu integree de couche limite
298      REAL cteiCL(klon, nbsrf)          ! cloud top instab. crit. couche limite      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
299      REAL pblt(klon, nbsrf)          ! T a la Hauteur de couche limite      REAL, SAVE:: pblt(klon, nbsrf) ! T a la Hauteur de couche limite
300      REAL therm(klon, nbsrf)      REAL, SAVE:: therm(klon, nbsrf)
301      REAL trmb1(klon, nbsrf)          ! deep_cape      REAL, SAVE:: trmb1(klon, nbsrf) ! deep_cape
302      REAL trmb2(klon, nbsrf)          ! inhibition      REAL, SAVE:: trmb2(klon, nbsrf) ! inhibition
303      REAL trmb3(klon, nbsrf)          ! Point Omega      REAL, SAVE:: trmb3(klon, nbsrf) ! Point Omega
304      ! Grdeurs de sorties      ! Grandeurs de sorties
305      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
306      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
307      REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)      REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)
308      REAL s_trmb3(klon)      REAL s_trmb3(klon)
309    
310      ! Variables locales pour la convection de K. Emanuel (sb):      ! Variables pour la convection de K. Emanuel :
311    
312      REAL upwd(klon, llm)      ! saturated updraft mass flux      REAL upwd(klon, llm) ! saturated updraft mass flux
313      REAL dnwd(klon, llm)      ! saturated downdraft mass flux      REAL dnwd(klon, llm) ! saturated downdraft mass flux
314      REAL dnwd0(klon, llm)     ! unsaturated downdraft mass flux      REAL, save:: cape(klon)
315      REAL tvp(klon, llm)       ! virtual temp of lifted parcel  
316      REAL cape(klon)           ! CAPE      INTEGER iflagctrl(klon) ! flag fonctionnement de convect
     SAVE cape  
   
     REAL pbase(klon)          ! cloud base pressure  
     SAVE pbase  
     REAL bbase(klon)          ! cloud base buoyancy  
     SAVE bbase  
     REAL rflag(klon)          ! flag fonctionnement de convect  
     INTEGER iflagctrl(klon)          ! flag fonctionnement de convect  
     ! -- convect43:  
     INTEGER ntra              ! nb traceurs pour convect4.3  
     REAL dtvpdt1(klon, llm), dtvpdq1(klon, llm)  
     REAL dplcldt(klon), dplcldr(klon)  
317    
318      ! Variables du changement      ! Variables du changement
319    
320      ! con: convection      ! con: convection
321      ! lsc: condensation a grande echelle (Large-Scale-Condensation)      ! lsc: large scale condensation
322      ! ajs: ajustement sec      ! ajs: ajustement sec
323      ! eva: evaporation de l'eau liquide nuageuse      ! eva: \'evaporation de l'eau liquide nuageuse
324      ! vdf: couche limite (Vertical DiFfusion)      ! vdf: vertical diffusion in boundary layer
325      REAL d_t_con(klon, llm), d_q_con(klon, llm)      REAL d_t_con(klon, llm), d_q_con(klon, llm)
326      REAL d_u_con(klon, llm), d_v_con(klon, llm)      REAL, save:: d_u_con(klon, llm), d_v_con(klon, llm)
327      REAL d_t_lsc(klon, llm), d_q_lsc(klon, llm), d_ql_lsc(klon, llm)      REAL d_t_lsc(klon, llm), d_q_lsc(klon, llm), d_ql_lsc(klon, llm)
328      REAL d_t_ajs(klon, llm), d_q_ajs(klon, llm)      REAL d_t_ajs(klon, llm), d_q_ajs(klon, llm)
329      REAL d_u_ajs(klon, llm), d_v_ajs(klon, llm)      REAL d_u_ajs(klon, llm), d_v_ajs(klon, llm)
330      REAL rneb(klon, llm)      REAL rneb(klon, llm)
331    
332      REAL pmfu(klon, llm), pmfd(klon, llm)      REAL mfu(klon, llm), mfd(klon, llm)
333      REAL pen_u(klon, llm), pen_d(klon, llm)      REAL pen_u(klon, llm), pen_d(klon, llm)
334      REAL pde_u(klon, llm), pde_d(klon, llm)      REAL pde_u(klon, llm), pde_d(klon, llm)
335      INTEGER kcbot(klon), kctop(klon), kdtop(klon)      INTEGER kcbot(klon), kctop(klon), kdtop(klon)
336      REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)      REAL pmflxr(klon, llm + 1), pmflxs(klon, llm + 1)
337      REAL prfl(klon, llm+1), psfl(klon, llm+1)      REAL prfl(klon, llm + 1), psfl(klon, llm + 1)
   
     INTEGER ibas_con(klon), itop_con(klon)  
338    
339      SAVE ibas_con, itop_con      INTEGER, save:: ibas_con(klon), itop_con(klon)
340        real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa
341    
342      REAL rain_con(klon), rain_lsc(klon)      REAL, save:: rain_con(klon)
343      REAL snow_con(klon), snow_lsc(klon)      real rain_lsc(klon)
344        REAL, save:: snow_con(klon) ! neige (mm / s)
345        real snow_lsc(klon)
346      REAL d_ts(klon, nbsrf)      REAL d_ts(klon, nbsrf)
347    
348      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
# Line 641  contains Line 353  contains
353      REAL d_u_lif(klon, llm), d_v_lif(klon, llm)      REAL d_u_lif(klon, llm), d_v_lif(klon, llm)
354      REAL d_t_lif(klon, llm)      REAL d_t_lif(klon, llm)
355    
356      REAL ratqs(klon, llm), ratqss(klon, llm), ratqsc(klon, llm)      REAL, save:: ratqs(klon, llm)
357      real ratqsbas, ratqshaut      real ratqss(klon, llm), ratqsc(klon, llm)
358      save ratqsbas, ratqshaut, ratqs      real:: ratqsbas = 0.01, ratqshaut = 0.3
359    
360      ! Parametres lies au nouveau schema de nuages (SB, PDF)      ! Parametres lies au nouveau schema de nuages (SB, PDF)
361      real fact_cldcon      real:: fact_cldcon = 0.375
362      real facttemps      real:: facttemps = 1.e-4
363      logical ok_newmicro      logical:: ok_newmicro = .true.
     save ok_newmicro  
     save fact_cldcon, facttemps  
364      real facteur      real facteur
365    
366      integer iflag_cldcon      integer:: iflag_cldcon = 1
     save iflag_cldcon  
   
367      logical ptconv(klon, llm)      logical ptconv(klon, llm)
368    
369      ! Variables liees a l'ecriture de la bande histoire physique      ! Variables pour effectuer les appels en s\'erie :
   
     integer itau_w   ! pas de temps ecriture = itap + itau_phy  
   
     ! Variables locales pour effectuer les appels en serie  
370    
371      REAL t_seri(klon, llm), q_seri(klon, llm)      REAL t_seri(klon, llm), q_seri(klon, llm)
372      REAL ql_seri(klon, llm), qs_seri(klon, llm)      REAL ql_seri(klon, llm)
373      REAL u_seri(klon, llm), v_seri(klon, llm)      REAL u_seri(klon, llm), v_seri(klon, llm)
374        REAL tr_seri(klon, llm, nqmx - 2)
     REAL tr_seri(klon, llm, nbtr)  
     REAL d_tr(klon, llm, nbtr)  
375    
376      REAL zx_rh(klon, llm)      REAL zx_rh(klon, llm)
377    
     INTEGER        length  
     PARAMETER    ( length = 100 )  
     REAL tabcntr0( length       )  
   
     INTEGER ndex2d(iim*(jjm + 1)), ndex3d(iim*(jjm + 1)*llm)  
   
378      REAL zustrdr(klon), zvstrdr(klon)      REAL zustrdr(klon), zvstrdr(klon)
379      REAL zustrli(klon), zvstrli(klon)      REAL zustrli(klon), zvstrli(klon)
380      REAL zustrph(klon), zvstrph(klon)      REAL zustrph(klon), zvstrph(klon)
381      REAL aam, torsfc      REAL aam, torsfc
382    
     REAL dudyn(iim+1, jjm + 1, llm)  
   
     REAL zx_tmp_fi2d(klon)      ! variable temporaire grille physique  
     REAL zx_tmp_fi3d(klon, llm) ! variable temporaire pour champs 3D  
   
     REAL zx_tmp_2d(iim, jjm + 1), zx_tmp_3d(iim, jjm + 1, llm)  
   
     INTEGER nid_day, nid_ins  
     SAVE nid_day, nid_ins  
   
383      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.
384      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.
385      REAL ue_lay(klon, llm) ! transport zonal de l'energie a chaque niveau vert.      REAL ue_lay(klon, llm) ! transport zonal de l'energie a chaque niveau vert.
386      REAL uq_lay(klon, llm) ! transport zonal de l'eau a chaque niveau vert.      REAL uq_lay(klon, llm) ! transport zonal de l'eau a chaque niveau vert.
387    
     REAL zsto  
   
     character(len=20) modname  
     character(len=80) abort_message  
     logical ok_sync  
388      real date0      real date0
   
     !     Variables liees au bilan d'energie et d'enthalpi  
389      REAL ztsol(klon)      REAL ztsol(klon)
     REAL      d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec  
     REAL      d_h_vcol_phy  
     REAL      fs_bound, fq_bound  
     SAVE      d_h_vcol_phy  
     REAL      zero_v(klon)  
     CHARACTER(LEN=15) ztit  
     INTEGER   ip_ebil  ! PRINT level for energy conserv. diag.  
     SAVE      ip_ebil  
     DATA      ip_ebil/0/  
     INTEGER   if_ebil ! level for energy conserv. dignostics  
     SAVE      if_ebil  
     !+jld ec_conser  
     REAL d_t_ec(klon, llm)    ! tendance du a la conersion Ec -> E thermique  
     REAL ZRCPD  
     !-jld ec_conser  
     !IM: t2m, q2m, u10m, v10m  
     REAL t2m(klon, nbsrf), q2m(klon, nbsrf)   !temperature, humidite a 2m  
     REAL u10m(klon, nbsrf), v10m(klon, nbsrf) !vents a 10m  
     REAL zt2m(klon), zq2m(klon)             !temp., hum. 2m moyenne s/ 1 maille  
     REAL zu10m(klon), zv10m(klon)           !vents a 10m moyennes s/1 maille  
     !jq   Aerosol effects (Johannes Quaas, 27/11/2003)  
     REAL sulfate(klon, llm) ! SO4 aerosol concentration [ug/m3]  
   
     REAL sulfate_pi(klon, llm)  
     ! (SO4 aerosol concentration [ug/m3] (pre-industrial value))  
     SAVE sulfate_pi  
390    
391      REAL cldtaupi(klon, llm)      REAL d_t_ec(klon, llm)
392      ! (Cloud optical thickness for pre-industrial (pi) aerosols)      ! tendance due \`a la conversion Ec en énergie thermique
393    
394      REAL re(klon, llm)       ! Cloud droplet effective radius      REAL ZRCPD
     REAL fl(klon, llm)  ! denominator of re  
395    
396      ! Aerosol optical properties      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)
397      REAL tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)      ! temperature and humidity at 2 m
     REAL cg_ae(klon, llm, 2)  
398    
399      REAL topswad(klon), solswad(klon) ! Aerosol direct effect.      REAL, save:: u10m(klon, nbsrf), v10m(klon, nbsrf) ! vents a 10 m
400      ! ok_ade=T -ADE=topswad-topsw      REAL zt2m(klon), zq2m(klon) ! temp., hum. 2 m moyenne s/ 1 maille
401        REAL zu10m(klon), zv10m(klon) ! vents a 10 m moyennes s/1 maille
402    
403      REAL topswai(klon), solswai(klon) ! Aerosol indirect effect.      ! Aerosol effects:
     ! ok_aie=T ->  
     !        ok_ade=T -AIE=topswai-topswad  
     !        ok_ade=F -AIE=topswai-topsw  
   
     REAL aerindex(klon)       ! POLDER aerosol index  
   
     ! Parameters  
     LOGICAL ok_ade, ok_aie    ! Apply aerosol (in)direct effects or not  
     REAL bl95_b0, bl95_b1   ! Parameter in Boucher and Lohmann (1995)  
   
     SAVE ok_ade, ok_aie, bl95_b0, bl95_b1  
     SAVE u10m  
     SAVE v10m  
     SAVE t2m  
     SAVE q2m  
     SAVE ffonte  
     SAVE fqcalving  
     SAVE piz_ae  
     SAVE tau_ae  
     SAVE cg_ae  
     SAVE rain_con  
     SAVE snow_con  
     SAVE topswai  
     SAVE topswad  
     SAVE solswai  
     SAVE solswad  
     SAVE d_u_con  
     SAVE d_v_con  
     SAVE rnebcon0  
     SAVE clwcon0  
     SAVE pblh  
     SAVE plcl  
     SAVE capCL  
     SAVE oliqCL  
     SAVE cteiCL  
     SAVE pblt  
     SAVE therm  
     SAVE trmb1  
     SAVE trmb2  
     SAVE trmb3  
404    
405      !----------------------------------------------------------------      REAL sulfate(klon, llm) ! SO4 aerosol concentration (micro g / m3)
406    
407      modname = 'physiq'      REAL, save:: sulfate_pi(klon, llm)
408      IF (if_ebil >= 1) THEN      ! SO4 aerosol concentration, in \mu g / m3, pre-industrial value
        DO i=1, klon  
           zero_v(i)=0.  
        END DO  
     END IF  
     ok_sync=.TRUE.  
     IF (nq  <  2) THEN  
        abort_message = 'eaux vapeur et liquide sont indispensables'  
        CALL abort_gcm (modname, abort_message, 1)  
     ENDIF  
409    
410      test_firstcal: IF (firstcal) THEN      REAL cldtaupi(klon, llm)
411         !  initialiser      ! cloud optical thickness for pre-industrial aerosols
        u10m(:, :)=0.  
        v10m(:, :)=0.  
        t2m(:, :)=0.  
        q2m(:, :)=0.  
        ffonte(:, :)=0.  
        fqcalving(:, :)=0.  
        piz_ae(:, :, :)=0.  
        tau_ae(:, :, :)=0.  
        cg_ae(:, :, :)=0.  
        rain_con(:)=0.  
        snow_con(:)=0.  
        bl95_b0=0.  
        bl95_b1=0.  
        topswai(:)=0.  
        topswad(:)=0.  
        solswai(:)=0.  
        solswad(:)=0.  
   
        d_u_con(:, :) = 0.0  
        d_v_con(:, :) = 0.0  
        rnebcon0(:, :) = 0.0  
        clwcon0(:, :) = 0.0  
        rnebcon(:, :) = 0.0  
        clwcon(:, :) = 0.0  
   
        pblh(:, :)   =0.        ! Hauteur de couche limite  
        plcl(:, :)   =0.        ! Niveau de condensation de la CLA  
        capCL(:, :)  =0.        ! CAPE de couche limite  
        oliqCL(:, :) =0.        ! eau_liqu integree de couche limite  
        cteiCL(:, :) =0.        ! cloud top instab. crit. couche limite  
        pblt(:, :)   =0.        ! T a la Hauteur de couche limite  
        therm(:, :)  =0.  
        trmb1(:, :)  =0.        ! deep_cape  
        trmb2(:, :)  =0.        ! inhibition  
        trmb3(:, :)  =0.        ! Point Omega  
   
        IF (if_ebil >= 1) d_h_vcol_phy=0.  
   
        ! appel a la lecture du run.def physique  
   
        call conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, &  
             ok_instan, fact_cldcon, facttemps, ok_newmicro, &  
             iflag_cldcon, ratqsbas, ratqshaut, if_ebil, &  
             ok_ade, ok_aie,  &  
             bl95_b0, bl95_b1, &  
             iflag_thermals, nsplit_thermals)  
412    
413         ! Initialiser les compteurs:      REAL re(klon, llm) ! Cloud droplet effective radius
414        REAL fl(klon, llm) ! denominator of re
415    
416         frugs = 0.      ! Aerosol optical properties
417         itap = 0      REAL, save:: tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)
418         itaprad = 0      REAL, save:: cg_ae(klon, llm, 2)
        CALL phyetat0("startphy.nc", dtime, co2_ppm_etat0, solaire_etat0, &  
             pctsrf, ftsol, ftsoil, &  
             ocean, tslab, seaice, & !IM "slab" ocean  
             fqsurf, qsol, fsnow, &  
             falbe, falblw, fevap, rain_fall, snow_fall, solsw, sollwdown, &  
             dlw, radsol, frugs, agesno, clesphy0, &  
             zmea, zstd, zsig, zgam, zthe, zpic, zval, rugoro, tabcntr0, &  
             t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon,  &  
             run_off_lic_0)  
   
        !   ATTENTION : il faudra a terme relire q2 dans l'etat initial  
        q2(:, :, :)=1.e-8  
419    
420         radpas = NINT( 86400. / dtime / nbapp_rad)      REAL, save:: topswad(klon), solswad(klon) ! aerosol direct effect
421        REAL, save:: topswai(klon), solswai(klon) ! aerosol indirect effect
422    
423         ! on remet le calendrier a zero      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect
424        LOGICAL:: ok_aie = .false. ! apply aerosol indirect effect
425    
426         IF (raz_date == 1) THEN      REAL:: bl95_b0 = 2., bl95_b1 = 0.2
427            itau_phy = 0      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus
428         ENDIF      ! B). They link cloud droplet number concentration to aerosol mass
429        ! concentration.
430    
431         PRINT*, 'cycle_diurne =', cycle_diurne      real zmasse(klon, llm)
432        ! (column-density of mass of air in a cell, in kg m-2)
433    
434         IF(ocean.NE.'force ') THEN      integer, save:: ncid_startphy
           ok_ocean=.TRUE.  
        ENDIF  
435    
436         CALL printflag( tabcntr0, radpas, ok_ocean, ok_oasis, ok_journe, &      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &
437              ok_instan, ok_region )           ratqsbas, ratqshaut, ok_ade, ok_aie, bl95_b0, bl95_b1, &
438             iflag_thermals, nsplit_thermals
439    
440         IF (ABS(dtime-pdtphys).GT.0.001) THEN      !----------------------------------------------------------------
           WRITE(lunout, *) 'Pas physique n est pas correct', dtime, &  
                pdtphys  
           abort_message='Pas physique n est pas correct '  
           call abort_gcm(modname, abort_message, 1)  
        ENDIF  
441    
442         IF (dtime*REAL(radpas).GT.21600..AND.cycle_diurne) THEN      IF (nqmx < 2) CALL abort_gcm('physiq', &
443            WRITE(lunout, *)'Nbre d appels au rayonnement insuffisant'           'eaux vapeur et liquide sont indispensables')
           WRITE(lunout, *)"Au minimum 4 appels par jour si cycle diurne"  
           abort_message='Nbre d appels au rayonnement insuffisant'  
           call abort_gcm(modname, abort_message, 1)  
        ENDIF  
        WRITE(lunout, *)"Clef pour la convection, iflag_con=", iflag_con  
        WRITE(lunout, *)"Clef pour le driver de la convection, ok_cvl=", &  
             ok_cvl  
444    
445         ! Initialisation pour la convection de K.E. (sb):      test_firstcal: IF (firstcal) THEN
446         IF (iflag_con >= 3) THEN         ! initialiser
447           u10m = 0.
448           v10m = 0.
449           t2m = 0.
450           q2m = 0.
451           ffonte = 0.
452           fqcalving = 0.
453           piz_ae = 0.
454           tau_ae = 0.
455           cg_ae = 0.
456           rain_con = 0.
457           snow_con = 0.
458           topswai = 0.
459           topswad = 0.
460           solswai = 0.
461           solswad = 0.
462    
463           d_u_con = 0.
464           d_v_con = 0.
465           rnebcon0 = 0.
466           clwcon0 = 0.
467           rnebcon = 0.
468           clwcon = 0.
469    
470           pblh =0. ! Hauteur de couche limite
471           plcl =0. ! Niveau de condensation de la CLA
472           capCL =0. ! CAPE de couche limite
473           oliqCL =0. ! eau_liqu integree de couche limite
474           cteiCL =0. ! cloud top instab. crit. couche limite
475           pblt =0. ! T a la Hauteur de couche limite
476           therm =0.
477           trmb1 =0. ! deep_cape
478           trmb2 =0. ! inhibition
479           trmb3 =0. ! Point Omega
480    
481           iflag_thermals = 0
482           nsplit_thermals = 1
483           print *, "Enter namelist 'physiq_nml'."
484           read(unit=*, nml=physiq_nml)
485           write(unit_nml, nml=physiq_nml)
486    
487            WRITE(lunout, *)"*** Convection de Kerry Emanuel 4.3  "         call conf_phys
488    
489            !IM15/11/02 rajout initialisation ibas_con, itop_con cf. SB =>BEG         ! Initialiser les compteurs:
           DO i = 1, klon  
              ibas_con(i) = 1  
              itop_con(i) = 1  
           ENDDO  
           !IM15/11/02 rajout initialisation ibas_con, itop_con cf. SB =>END  
490    
491           frugs = 0.
492           CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
493                fevap, rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, &
494                agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
495                q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &
496                w01, ncid_startphy)
497    
498           ! ATTENTION : il faudra a terme relire q2 dans l'etat initial
499           q2 = 1e-8
500    
501           radpas = lmt_pas / nbapp_rad
502           print *, "radpas = ", radpas
503    
504           ! Initialisation pour le sch\'ema de convection d'Emanuel :
505           IF (conv_emanuel) THEN
506              ibas_con = 1
507              itop_con = 1
508         ENDIF         ENDIF
509    
510         IF (ok_orodr) THEN         IF (ok_orodr) THEN
511            DO i=1, klon            rugoro = MAX(1e-5, zstd * zsig / 2)
512               rugoro(i) = MAX(1.0e-05, zstd(i)*zsig(i)/2.0)            CALL SUGWD(paprs, play)
513            ENDDO         else
514            CALL SUGWD(klon, llm, paprs, pplay)            rugoro = 0.
515         ENDIF         ENDIF
516    
517         lmt_pas = NINT(86400. / dtime)  ! tous les jours         ecrit_ins = NINT(ecrit_ins / dtphys)
        print *, 'Number of time steps of "physics" per day: ', lmt_pas  
   
        ecrit_ins = NINT(ecrit_ins/dtime)  
        ecrit_hf = NINT(ecrit_hf/dtime)  
        ecrit_day = NINT(ecrit_day/dtime)  
        ecrit_mth = NINT(ecrit_mth/dtime)  
        ecrit_tra = NINT(86400.*ecrit_tra/dtime)  
        ecrit_reg = NINT(ecrit_reg/dtime)  
   
        ! Initialiser le couplage si necessaire  
   
        npas = 0  
        nexca = 0  
        if (ocean == 'couple') then  
           npas = itaufin/ iphysiq  
           nexca = 86400 / int(dtime)  
           write(lunout, *)' Ocean couple'  
           write(lunout, *)' Valeurs des pas de temps'  
           write(lunout, *)' npas = ', npas  
           write(lunout, *)' nexca = ', nexca  
        endif  
   
        write(lunout, *)'AVANT HIST IFLAG_CON=', iflag_con  
518    
519         !   Initialisation des sorties         ! Initialisation des sorties
520    
521         call ini_histhf(dtime, presnivs, nid_hf, nid_hf3d)         call ini_histins(dtphys)
522         call ini_histday(dtime, presnivs, ok_journe, nid_day)         CALL ymds2ju(annee_ref, 1, day_ref, 0., date0)
523         call ini_histins(dtime, presnivs, ok_instan, nid_ins)         ! Positionner date0 pour initialisation de ORCHIDEE
524         CALL ymds2ju(annee_ref, 1, int(day_ref), 0., date0)         print *, 'physiq date0: ', date0
525         !XXXPB Positionner date0 pour initialisation de ORCHIDEE         CALL phyredem0
        WRITE(*, *) 'physiq date0 : ', date0  
526      ENDIF test_firstcal      ENDIF test_firstcal
527    
528      ! Mettre a zero des variables de sortie (pour securite)      ! We will modify variables *_seri and we will not touch variables
529        ! u, v, t, qx:
530      DO i = 1, klon      t_seri = t
531         d_ps(i) = 0.0      u_seri = u
532      ENDDO      v_seri = v
533      DO k = 1, llm      q_seri = qx(:, :, ivap)
534         DO i = 1, klon      ql_seri = qx(:, :, iliq)
535            d_t(i, k) = 0.0      tr_seri = qx(:, :, 3:nqmx)
           d_u(i, k) = 0.0  
           d_v(i, k) = 0.0  
        ENDDO  
     ENDDO  
     DO iq = 1, nq  
        DO k = 1, llm  
           DO i = 1, klon  
              d_qx(i, k, iq) = 0.0  
           ENDDO  
        ENDDO  
     ENDDO  
     da(:, :)=0.  
     mp(:, :)=0.  
     phi(:, :, :)=0.  
   
     ! Ne pas affecter les valeurs entrees de u, v, h, et q  
   
     DO k = 1, llm  
        DO i = 1, klon  
           t_seri(i, k)  = t(i, k)  
           u_seri(i, k)  = u(i, k)  
           v_seri(i, k)  = v(i, k)  
           q_seri(i, k)  = qx(i, k, ivap)  
           ql_seri(i, k) = qx(i, k, iliq)  
           qs_seri(i, k) = 0.  
        ENDDO  
     ENDDO  
     IF (nq >= 3) THEN  
        tr_seri(:, :, :nq-2) = qx(:, :, 3:nq)  
     ELSE  
        tr_seri(:, :, 1) = 0.  
     ENDIF  
   
     DO i = 1, klon  
        ztsol(i) = 0.  
     ENDDO  
     DO nsrf = 1, nbsrf  
        DO i = 1, klon  
           ztsol(i) = ztsol(i) + ftsol(i, nsrf)*pctsrf(i, nsrf)  
        ENDDO  
     ENDDO  
   
     IF (if_ebil >= 1) THEN  
        ztit='after dynamic'  
        CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        !     Comme les tendances de la physique sont ajoute dans la dynamique,  
        !     on devrait avoir que la variation d'entalpie par la dynamique  
        !     est egale a la variation de la physique au pas de temps precedent.  
        !     Donc la somme de ces 2 variations devrait etre nulle.  
        call diagphy(airephy, ztit, ip_ebil &  
             , zero_v, zero_v, zero_v, zero_v, zero_v &  
             , zero_v, zero_v, zero_v, ztsol &  
             , d_h_vcol+d_h_vcol_phy, d_qt, 0. &  
             , fs_bound, fq_bound )  
     END IF  
536    
537      ! Diagnostiquer la tendance dynamique      ztsol = sum(ftsol * pctsrf, dim = 2)
538    
539        ! Diagnostic de la tendance dynamique :
540      IF (ancien_ok) THEN      IF (ancien_ok) THEN
541         DO k = 1, llm         DO k = 1, llm
542            DO i = 1, klon            DO i = 1, klon
543               d_t_dyn(i, k) = (t_seri(i, k)-t_ancien(i, k))/dtime               d_t_dyn(i, k) = (t_seri(i, k) - t_ancien(i, k)) / dtphys
544               d_q_dyn(i, k) = (q_seri(i, k)-q_ancien(i, k))/dtime               d_q_dyn(i, k) = (q_seri(i, k) - q_ancien(i, k)) / dtphys
545            ENDDO            ENDDO
546         ENDDO         ENDDO
547      ELSE      ELSE
548         DO k = 1, llm         DO k = 1, llm
549            DO i = 1, klon            DO i = 1, klon
550               d_t_dyn(i, k) = 0.0               d_t_dyn(i, k) = 0.
551               d_q_dyn(i, k) = 0.0               d_q_dyn(i, k) = 0.
552            ENDDO            ENDDO
553         ENDDO         ENDDO
554         ancien_ok = .TRUE.         ancien_ok = .TRUE.
555      ENDIF      ENDIF
556    
557      ! Ajouter le geopotentiel du sol:      ! Ajouter le geopotentiel du sol:
   
558      DO k = 1, llm      DO k = 1, llm
559         DO i = 1, klon         DO i = 1, klon
560            zphi(i, k) = pphi(i, k) + pphis(i)            zphi(i, k) = pphi(i, k) + pphis(i)
561         ENDDO         ENDDO
562      ENDDO      ENDDO
563    
564      ! Verifier les temperatures      ! Check temperatures:
   
565      CALL hgardfou(t_seri, ftsol)      CALL hgardfou(t_seri, ftsol)
566    
567      ! Incrementer le compteur de la physique      call increment_itap
568        julien = MOD(dayvrai, 360)
     itap = itap + 1  
     julien = MOD(NINT(rdayvrai), 360)  
569      if (julien == 0) julien = 360      if (julien == 0) julien = 360
570    
571      ! Mettre en action les conditions aux limites (albedo, sst, etc.).      forall (k = 1: llm) zmasse(:, k) = (paprs(:, k) - paprs(:, k + 1)) / rg
     ! Prescrire l'ozone et calculer l'albedo sur l'ocean.  
572    
573      IF (MOD(itap - 1, lmt_pas) == 0) THEN      ! Prescrire l'ozone :
574         CALL ozonecm(REAL(julien), rlat, paprs, wo)      wo = ozonecm(REAL(julien), paprs)
     ENDIF  
   
     ! Re-evaporer l'eau liquide nuageuse  
575    
576      DO k = 1, llm  ! re-evaporation de l'eau liquide nuageuse      ! \'Evaporation de l'eau liquide nuageuse :
577        DO k = 1, llm
578         DO i = 1, klon         DO i = 1, klon
579            zlvdcp=RLVTT/RCPD/(1.0+RVTMP2*q_seri(i, k))            zb = MAX(0., ql_seri(i, k))
580            zlsdcp=RLVTT/RCPD/(1.0+RVTMP2*q_seri(i, k))            t_seri(i, k) = t_seri(i, k) &
581            zdelta = MAX(0., SIGN(1., RTT-t_seri(i, k)))                 - zb * RLVTT / RCPD / (1. + RVTMP2 * q_seri(i, k))
           zb = MAX(0.0, ql_seri(i, k))  
           za = - MAX(0.0, ql_seri(i, k)) &  
                * (zlvdcp*(1.-zdelta)+zlsdcp*zdelta)  
           t_seri(i, k) = t_seri(i, k) + za  
582            q_seri(i, k) = q_seri(i, k) + zb            q_seri(i, k) = q_seri(i, k) + zb
           ql_seri(i, k) = 0.0  
583         ENDDO         ENDDO
584      ENDDO      ENDDO
585        ql_seri = 0.
586    
587      IF (if_ebil >= 2) THEN      frugs = MAX(frugs, 0.000015)
588         ztit='after reevap'      zxrugs = sum(frugs * pctsrf, dim = 2)
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 1, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        call diagphy(airephy, ztit, ip_ebil &  
             , zero_v, zero_v, zero_v, zero_v, zero_v &  
             , zero_v, zero_v, zero_v, ztsol &  
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
589    
590      END IF      ! Calculs n\'ecessaires au calcul de l'albedo dans l'interface avec
591        ! la surface.
592    
593      ! Appeler la diffusion verticale (programme de couche limite)      CALL orbite(REAL(julien), longi, dist)
   
     DO i = 1, klon  
        zxrugs(i) = 0.0  
     ENDDO  
     DO nsrf = 1, nbsrf  
        DO i = 1, klon  
           frugs(i, nsrf) = MAX(frugs(i, nsrf), 0.000015)  
        ENDDO  
     ENDDO  
     DO nsrf = 1, nbsrf  
        DO i = 1, klon  
           zxrugs(i) = zxrugs(i) + frugs(i, nsrf)*pctsrf(i, nsrf)  
        ENDDO  
     ENDDO  
   
     ! calculs necessaires au calcul de l'albedo dans l'interface  
   
     CALL orbite(REAL(julien), zlongi, dist)  
594      IF (cycle_diurne) THEN      IF (cycle_diurne) THEN
595         zdtime = dtime * REAL(radpas)         CALL zenang(longi, time, dtphys * radpas, mu0, fract)
        CALL zenang(zlongi, gmtime, zdtime, rmu0, fract)  
596      ELSE      ELSE
597         rmu0 = -999.999         mu0 = - 999.999
598      ENDIF      ENDIF
599    
600      !     Calcul de l'abedo moyen par maille      ! Calcul de l'abedo moyen par maille
601      albsol(:)=0.      albsol = sum(falbe * pctsrf, dim = 2)
     albsollw(:)=0.  
     DO nsrf = 1, nbsrf  
        DO i = 1, klon  
           albsol(i) = albsol(i) + falbe(i, nsrf) * pctsrf(i, nsrf)  
           albsollw(i) = albsollw(i) + falblw(i, nsrf) * pctsrf(i, nsrf)  
        ENDDO  
     ENDDO  
602    
603      !     Repartition sous maille des flux LW et SW      ! R\'epartition sous maille des flux longwave et shortwave
604      ! Repartition du longwave par sous-surface linearisee      ! R\'epartition du longwave par sous-surface lin\'earis\'ee
605    
606      DO nsrf = 1, nbsrf      forall (nsrf = 1: nbsrf)
607         DO i = 1, klon         fsollw(:, nsrf) = sollw + 4. * RSIGMA * ztsol**3 &
608            fsollw(i, nsrf) = sollw(i) &              * (ztsol - ftsol(:, nsrf))
609                 + 4.0*RSIGMA*ztsol(i)**3 * (ztsol(i)-ftsol(i, nsrf))         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
610            fsolsw(i, nsrf) = solsw(i)*(1.-falbe(i, nsrf))/(1.-albsol(i))      END forall
        ENDDO  
     ENDDO  
611    
612      fder = dlw      fder = dlw
613    
614      CALL clmain(dtime, itap, date0, pctsrf, pctsrf_new, &      CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &
615           t_seri, q_seri, u_seri, v_seri, &           ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &
616           julien, rmu0, co2_ppm,  &           paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &
617           ok_veget, ocean, npas, nexca, ftsol, &           snow_fall, fsolsw, fsollw, fder, rlat, frugs, agesno, rugoro, &
618           soil_model, cdmmax, cdhmax, &           d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, &
619           ksta, ksta_ter, ok_kzmin, ftsoil, qsol,  &           flux_v, cdragh, cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, &
620           paprs, pplay, fsnow, fqsurf, fevap, falbe, falblw, &           u10m, v10m, pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, &
621           fluxlat, rain_fall, snow_fall, &           trmb3, plcl, fqcalving, ffonte, run_off_lic_0)
622           fsolsw, fsollw, sollwdown, fder, &  
623           rlon, rlat, cuphy, cvphy, frugs, &      ! Incr\'ementation des flux
624           firstcal, lafin, agesno, rugoro, &  
625           d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, &      sens = - sum(flux_t * pctsrf, dim = 2)
626           fluxt, fluxq, fluxu, fluxv, cdragh, cdragm, &      evap = - sum(flux_q * pctsrf, dim = 2)
627           q2, dsens, devap, &      fder = dlw + 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)  
   
     !XXX Incrementation des flux  
   
     zxfluxt=0.  
     zxfluxq=0.  
     zxfluxu=0.  
     zxfluxv=0.  
     DO nsrf = 1, nbsrf  
        DO k = 1, llm  
           DO i = 1, klon  
              zxfluxt(i, k) = zxfluxt(i, k) +  &  
                   fluxt(i, k, nsrf) * pctsrf( i, nsrf)  
              zxfluxq(i, k) = zxfluxq(i, k) +  &  
                   fluxq(i, k, nsrf) * pctsrf( i, nsrf)  
              zxfluxu(i, k) = zxfluxu(i, k) +  &  
                   fluxu(i, k, nsrf) * pctsrf( i, nsrf)  
              zxfluxv(i, k) = zxfluxv(i, k) +  &  
                   fluxv(i, k, nsrf) * pctsrf( i, nsrf)  
           END DO  
        END DO  
     END DO  
     DO i = 1, klon  
        sens(i) = - zxfluxt(i, 1) ! flux de chaleur sensible au sol  
        evap(i) = - zxfluxq(i, 1) ! flux d'evaporation au sol  
        fder(i) = dlw(i) + dsens(i) + devap(i)  
     ENDDO  
628    
629      DO k = 1, llm      DO k = 1, llm
630         DO i = 1, klon         DO i = 1, klon
# Line 1204  contains Line 635  contains
635         ENDDO         ENDDO
636      ENDDO      ENDDO
637    
638      IF (if_ebil >= 2) THEN      ! Update surface temperature:
        ztit='after clmain'  
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        call diagphy(airephy, ztit, ip_ebil &  
             , zero_v, zero_v, zero_v, zero_v, sens &  
             , evap, zero_v, zero_v, ztsol &  
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
     END IF  
   
     ! Incrementer la temperature du sol  
639    
640      DO i = 1, klon      DO i = 1, klon
641         zxtsol(i) = 0.0         zxfluxlat(i) = 0.
        zxfluxlat(i) = 0.0  
642    
643         zt2m(i) = 0.0         zt2m(i) = 0.
644         zq2m(i) = 0.0         zq2m(i) = 0.
645         zu10m(i) = 0.0         zu10m(i) = 0.
646         zv10m(i) = 0.0         zv10m(i) = 0.
647         zxffonte(i) = 0.0         zxffonte(i) = 0.
648         zxfqcalving(i) = 0.0         zxfqcalving(i) = 0.
649    
650         s_pblh(i) = 0.0         s_pblh(i) = 0.
651         s_lcl(i) = 0.0         s_lcl(i) = 0.
652         s_capCL(i) = 0.0         s_capCL(i) = 0.
653         s_oliqCL(i) = 0.0         s_oliqCL(i) = 0.
654         s_cteiCL(i) = 0.0         s_cteiCL(i) = 0.
655         s_pblT(i) = 0.0         s_pblT(i) = 0.
656         s_therm(i) = 0.0         s_therm(i) = 0.
657         s_trmb1(i) = 0.0         s_trmb1(i) = 0.
658         s_trmb2(i) = 0.0         s_trmb2(i) = 0.
659         s_trmb3(i) = 0.0         s_trmb3(i) = 0.
   
        IF ( abs( pctsrf(i, is_ter) + pctsrf(i, is_lic) +  &  
             pctsrf(i, is_oce) + pctsrf(i, is_sic)  - 1.) .GT. EPSFRA)  &  
             THEN  
           WRITE(*, *) 'physiq : pb sous surface au point ', i,  &  
                pctsrf(i, 1 : nbsrf)  
        ENDIF  
660      ENDDO      ENDDO
661    
662        call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')
663    
664        ftsol = ftsol + d_ts
665        ztsol = sum(ftsol * pctsrf, dim = 2)
666      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
667         DO i = 1, klon         DO i = 1, klon
668            ftsol(i, nsrf) = ftsol(i, nsrf) + d_ts(i, nsrf)            zxfluxlat(i) = zxfluxlat(i) + fluxlat(i, nsrf) * pctsrf(i, nsrf)
669            zxtsol(i) = zxtsol(i) + ftsol(i, nsrf)*pctsrf(i, nsrf)  
670            zxfluxlat(i) = zxfluxlat(i) + fluxlat(i, nsrf)*pctsrf(i, nsrf)            zt2m(i) = zt2m(i) + t2m(i, nsrf) * pctsrf(i, nsrf)
671              zq2m(i) = zq2m(i) + q2m(i, nsrf) * pctsrf(i, nsrf)
672            zt2m(i) = zt2m(i) + t2m(i, nsrf)*pctsrf(i, nsrf)            zu10m(i) = zu10m(i) + u10m(i, nsrf) * pctsrf(i, nsrf)
673            zq2m(i) = zq2m(i) + q2m(i, nsrf)*pctsrf(i, nsrf)            zv10m(i) = zv10m(i) + v10m(i, nsrf) * pctsrf(i, nsrf)
674            zu10m(i) = zu10m(i) + u10m(i, nsrf)*pctsrf(i, nsrf)            zxffonte(i) = zxffonte(i) + ffonte(i, nsrf) * pctsrf(i, nsrf)
675            zv10m(i) = zv10m(i) + v10m(i, nsrf)*pctsrf(i, nsrf)            zxfqcalving(i) = zxfqcalving(i) + &
676            zxffonte(i) = zxffonte(i) + ffonte(i, nsrf)*pctsrf(i, nsrf)                 fqcalving(i, nsrf) * pctsrf(i, nsrf)
677            zxfqcalving(i) = zxfqcalving(i) +  &            s_pblh(i) = s_pblh(i) + pblh(i, nsrf) * pctsrf(i, nsrf)
678                 fqcalving(i, nsrf)*pctsrf(i, nsrf)            s_lcl(i) = s_lcl(i) + plcl(i, nsrf) * pctsrf(i, nsrf)
679            s_pblh(i) = s_pblh(i) + pblh(i, nsrf)*pctsrf(i, nsrf)            s_capCL(i) = s_capCL(i) + capCL(i, nsrf) * pctsrf(i, nsrf)
680            s_lcl(i) = s_lcl(i) + plcl(i, nsrf)*pctsrf(i, nsrf)            s_oliqCL(i) = s_oliqCL(i) + oliqCL(i, nsrf) * pctsrf(i, nsrf)
681            s_capCL(i) = s_capCL(i) + capCL(i, nsrf) *pctsrf(i, nsrf)            s_cteiCL(i) = s_cteiCL(i) + cteiCL(i, nsrf) * pctsrf(i, nsrf)
682            s_oliqCL(i) = s_oliqCL(i) + oliqCL(i, nsrf) *pctsrf(i, nsrf)            s_pblT(i) = s_pblT(i) + pblT(i, nsrf) * pctsrf(i, nsrf)
683            s_cteiCL(i) = s_cteiCL(i) + cteiCL(i, nsrf) *pctsrf(i, nsrf)            s_therm(i) = s_therm(i) + therm(i, nsrf) * pctsrf(i, nsrf)
684            s_pblT(i) = s_pblT(i) + pblT(i, nsrf) *pctsrf(i, nsrf)            s_trmb1(i) = s_trmb1(i) + trmb1(i, nsrf) * pctsrf(i, nsrf)
685            s_therm(i) = s_therm(i) + therm(i, nsrf) *pctsrf(i, nsrf)            s_trmb2(i) = s_trmb2(i) + trmb2(i, nsrf) * pctsrf(i, nsrf)
686            s_trmb1(i) = s_trmb1(i) + trmb1(i, nsrf) *pctsrf(i, nsrf)            s_trmb3(i) = s_trmb3(i) + trmb3(i, nsrf) * pctsrf(i, nsrf)
           s_trmb2(i) = s_trmb2(i) + trmb2(i, nsrf) *pctsrf(i, nsrf)  
           s_trmb3(i) = s_trmb3(i) + trmb3(i, nsrf) *pctsrf(i, nsrf)  
687         ENDDO         ENDDO
688      ENDDO      ENDDO
689    
690      ! Si une sous-fraction n'existe pas, elle prend la temp. moyenne      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :
   
691      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
692         DO i = 1, klon         DO i = 1, klon
693            IF (pctsrf(i, nsrf)  <  epsfra) ftsol(i, nsrf) = zxtsol(i)            IF (pctsrf(i, nsrf) < epsfra) then
694                 ftsol(i, nsrf) = ztsol(i)
695            IF (pctsrf(i, nsrf)  <  epsfra) t2m(i, nsrf) = zt2m(i)               t2m(i, nsrf) = zt2m(i)
696            IF (pctsrf(i, nsrf)  <  epsfra) q2m(i, nsrf) = zq2m(i)               q2m(i, nsrf) = zq2m(i)
697            IF (pctsrf(i, nsrf)  <  epsfra) u10m(i, nsrf) = zu10m(i)               u10m(i, nsrf) = zu10m(i)
698            IF (pctsrf(i, nsrf)  <  epsfra) v10m(i, nsrf) = zv10m(i)               v10m(i, nsrf) = zv10m(i)
699            IF (pctsrf(i, nsrf)  <  epsfra) ffonte(i, nsrf) = zxffonte(i)               ffonte(i, nsrf) = zxffonte(i)
700            IF (pctsrf(i, nsrf)  <  epsfra)  &               fqcalving(i, nsrf) = zxfqcalving(i)
701                 fqcalving(i, nsrf) = zxfqcalving(i)               pblh(i, nsrf) = s_pblh(i)
702            IF (pctsrf(i, nsrf)  <  epsfra) pblh(i, nsrf)=s_pblh(i)               plcl(i, nsrf) = s_lcl(i)
703            IF (pctsrf(i, nsrf)  <  epsfra) plcl(i, nsrf)=s_lcl(i)               capCL(i, nsrf) = s_capCL(i)
704            IF (pctsrf(i, nsrf)  <  epsfra) capCL(i, nsrf)=s_capCL(i)               oliqCL(i, nsrf) = s_oliqCL(i)
705            IF (pctsrf(i, nsrf)  <  epsfra) oliqCL(i, nsrf)=s_oliqCL(i)               cteiCL(i, nsrf) = s_cteiCL(i)
706            IF (pctsrf(i, nsrf)  <  epsfra) cteiCL(i, nsrf)=s_cteiCL(i)               pblT(i, nsrf) = s_pblT(i)
707            IF (pctsrf(i, nsrf)  <  epsfra) pblT(i, nsrf)=s_pblT(i)               therm(i, nsrf) = s_therm(i)
708            IF (pctsrf(i, nsrf)  <  epsfra) therm(i, nsrf)=s_therm(i)               trmb1(i, nsrf) = s_trmb1(i)
709            IF (pctsrf(i, nsrf)  <  epsfra) trmb1(i, nsrf)=s_trmb1(i)               trmb2(i, nsrf) = s_trmb2(i)
710            IF (pctsrf(i, nsrf)  <  epsfra) trmb2(i, nsrf)=s_trmb2(i)               trmb3(i, nsrf) = s_trmb3(i)
711            IF (pctsrf(i, nsrf)  <  epsfra) trmb3(i, nsrf)=s_trmb3(i)            end IF
712         ENDDO         ENDDO
713      ENDDO      ENDDO
714    
715      ! Calculer la derive du flux infrarouge      ! Calculer la dérive du flux infrarouge
716    
717      DO i = 1, klon      DO i = 1, klon
718         dlw(i) = - 4.0*RSIGMA*zxtsol(i)**3         dlw(i) = - 4. * RSIGMA * ztsol(i)**3
719      ENDDO      ENDDO
720    
721      ! Appeler la convection (au choix)      ! Appeler la convection
   
     DO k = 1, llm  
        DO i = 1, klon  
           conv_q(i, k) = d_q_dyn(i, k)  &  
                + d_q_vdf(i, k)/dtime  
           conv_t(i, k) = d_t_dyn(i, k)  &  
                + d_t_vdf(i, k)/dtime  
        ENDDO  
     ENDDO  
     IF (check) THEN  
        za = qcheck(klon, llm, paprs, q_seri, ql_seri, airephy)  
        WRITE(lunout, *) "avantcon=", za  
     ENDIF  
     zx_ajustq = .FALSE.  
     IF (iflag_con == 2) zx_ajustq=.TRUE.  
     IF (zx_ajustq) THEN  
        DO i = 1, klon  
           z_avant(i) = 0.0  
        ENDDO  
        DO k = 1, llm  
           DO i = 1, klon  
              z_avant(i) = z_avant(i) + (q_seri(i, k)+ql_seri(i, k)) &  
                   *(paprs(i, k)-paprs(i, k+1))/RG  
           ENDDO  
        ENDDO  
     ENDIF  
     IF (iflag_con == 1) THEN  
        stop 'reactiver le call conlmd dans physiq.F'  
     ELSE IF (iflag_con == 2) THEN  
        CALL conflx(dtime, paprs, pplay, t_seri, q_seri, &  
             conv_t, conv_q, zxfluxq(1, 1), omega, &  
             d_t_con, d_q_con, rain_con, snow_con, &  
             pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &  
             kcbot, kctop, kdtop, pmflxr, pmflxs)  
        WHERE (rain_con < 0.) rain_con = 0.  
        WHERE (snow_con < 0.) snow_con = 0.  
        DO i = 1, klon  
           ibas_con(i) = llm+1 - kcbot(i)  
           itop_con(i) = llm+1 - kctop(i)  
        ENDDO  
     ELSE IF (iflag_con >= 3) THEN  
        ! nb of tracers for the KE convection:  
        ! MAF la partie traceurs est faite dans phytrac  
        ! on met ntra=1 pour limiter les appels mais on peut  
        ! supprimer les calculs / ftra.  
        ntra = 1  
        ! Schema de convection modularise et vectorise:  
        ! (driver commun aux versions 3 et 4)  
   
        IF (ok_cvl) THEN ! new driver for convectL  
   
           CALL concvl (iflag_con, &  
                dtime, paprs, pplay, t_seri, q_seri, &  
                u_seri, v_seri, tr_seri, ntra, &  
                ema_work1, ema_work2, &  
                d_t_con, d_q_con, d_u_con, d_v_con, d_tr, &  
                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)  
   
           clwcon0=qcondc  
           pmfu(:, :)=upwd(:, :)+dnwd(:, :)  
   
        ELSE ! ok_cvl  
           ! MAF conema3 ne contient pas les traceurs  
           CALL conema3 (dtime, &  
                paprs, pplay, t_seri, q_seri, &  
                u_seri, v_seri, tr_seri, ntra, &  
                ema_work1, ema_work2, &  
                d_t_con, d_q_con, d_u_con, d_v_con, d_tr, &  
                rain_con, snow_con, ibas_con, itop_con, &  
                upwd, dnwd, dnwd0, bas, top, &  
                Ma, cape, tvp, rflag, &  
                pbase &  
                , bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr &  
                , clwcon0)  
   
        ENDIF ! ok_cvl  
722    
723         IF (.NOT. ok_gust) THEN      if (conv_emanuel) then
724            do i = 1, klon         CALL concvl(paprs, play, t_seri, q_seri, u_seri, v_seri, sig1, w01, &
725               wd(i)=0.0              d_t_con, d_q_con, d_u_con, d_v_con, rain_con, ibas_con, itop_con, &
726            enddo              upwd, dnwd, Ma, cape, iflagctrl, qcondc, pmflxr, da, phi, mp)
727           snow_con = 0.
728           clwcon0 = qcondc
729           mfu = upwd + dnwd
730    
731           IF (thermcep) THEN
732              zqsat = MIN(0.5, r2es * FOEEW(t_seri, rtt >= t_seri) / play)
733              zqsat = zqsat / (1. - retv * zqsat)
734           ELSE
735              zqsat = merge(qsats(t_seri), qsatl(t_seri), t_seri < t_coup) / play
736         ENDIF         ENDIF
737    
738         ! Calcul des proprietes des nuages convectifs         ! Properties of convective clouds
739           clwcon0 = fact_cldcon * clwcon0
740         DO k = 1, llm         call clouds_gno(klon, llm, q_seri, zqsat, clwcon0, ptconv, ratqsc, &
741            DO i = 1, klon              rnebcon0)
742               zx_t = t_seri(i, k)  
743               IF (thermcep) THEN         forall (i = 1:klon) ema_pct(i) = paprs(i, itop_con(i) + 1)
744                  zdelta = MAX(0., SIGN(1., rtt-zx_t))         mfd = 0.
745                  zx_qs  = r2es * FOEEW(zx_t, zdelta)/pplay(i, k)         pen_u = 0.
746                  zx_qs  = MIN(0.5, zx_qs)         pen_d = 0.
747                  zcor   = 1./(1.-retv*zx_qs)         pde_d = 0.
748                  zx_qs  = zx_qs*zcor         pde_u = 0.
749               ELSE      else
750                  IF (zx_t < t_coup) THEN         conv_q = d_q_dyn + d_q_vdf / dtphys
751                     zx_qs = qsats(zx_t)/pplay(i, k)         conv_t = d_t_dyn + d_t_vdf / dtphys
752                  ELSE         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)
753                     zx_qs = qsatl(zx_t)/pplay(i, k)         CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &
754                  ENDIF              q_seri(:, llm:1:- 1), conv_t, conv_q, - evap, omega, &
755               ENDIF              d_t_con, d_q_con, rain_con, snow_con, mfu(:, llm:1:- 1), &
756               zqsat(i, k)=zx_qs              mfd(:, llm:1:- 1), pen_u, pde_u, pen_d, pde_d, kcbot, kctop, &
757            ENDDO              kdtop, pmflxr, pmflxs)
758         ENDDO         WHERE (rain_con < 0.) rain_con = 0.
759           WHERE (snow_con < 0.) snow_con = 0.
760         !   calcul des proprietes des nuages convectifs         ibas_con = llm + 1 - kcbot
761         clwcon0(:, :)=fact_cldcon*clwcon0(:, :)         itop_con = llm + 1 - kctop
762         call clouds_gno &      END if
             (klon, llm, q_seri, zqsat, clwcon0, ptconv, ratqsc, rnebcon0)  
     ELSE  
        WRITE(lunout, *) "iflag_con non-prevu", iflag_con  
        stop 1  
     ENDIF  
763    
764      DO k = 1, llm      DO k = 1, llm
765         DO i = 1, klon         DO i = 1, klon
# Line 1434  contains Line 770  contains
770         ENDDO         ENDDO
771      ENDDO      ENDDO
772    
773      IF (if_ebil >= 2) THEN      IF (.not. conv_emanuel) THEN
774         ztit='after convect'         z_apres = sum((q_seri + ql_seri) * zmasse, dim=2)
775         CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &         z_factor = (z_avant - (rain_con + snow_con) * dtphys) / z_apres
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        call diagphy(airephy, ztit, ip_ebil &  
             , zero_v, zero_v, zero_v, zero_v, zero_v &  
             , zero_v, rain_con, snow_con, ztsol &  
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
     END IF  
   
     IF (check) THEN  
        za = qcheck(klon, llm, paprs, q_seri, ql_seri, airephy)  
        WRITE(lunout, *)"aprescon=", za  
        zx_t = 0.0  
        za = 0.0  
        DO i = 1, klon  
           za = za + airephy(i)/REAL(klon)  
           zx_t = zx_t + (rain_con(i)+ &  
                snow_con(i))*airephy(i)/REAL(klon)  
        ENDDO  
        zx_t = zx_t/za*dtime  
        WRITE(lunout, *)"Precip=", zx_t  
     ENDIF  
     IF (zx_ajustq) THEN  
        DO i = 1, klon  
           z_apres(i) = 0.0  
        ENDDO  
        DO k = 1, llm  
           DO i = 1, klon  
              z_apres(i) = z_apres(i) + (q_seri(i, k)+ql_seri(i, k)) &  
                   *(paprs(i, k)-paprs(i, k+1))/RG  
           ENDDO  
        ENDDO  
        DO i = 1, klon  
           z_factor(i) = (z_avant(i)-(rain_con(i)+snow_con(i))*dtime) &  
                /z_apres(i)  
        ENDDO  
776         DO k = 1, llm         DO k = 1, llm
777            DO i = 1, klon            DO i = 1, klon
778               IF (z_factor(i).GT.(1.0+1.0E-08) .OR. &               IF (z_factor(i) > 1. + 1E-8 .OR. z_factor(i) < 1. - 1E-8) THEN
                   z_factor(i) < (1.0-1.0E-08)) THEN  
779                  q_seri(i, k) = q_seri(i, k) * z_factor(i)                  q_seri(i, k) = q_seri(i, k) * z_factor(i)
780               ENDIF               ENDIF
781            ENDDO            ENDDO
782         ENDDO         ENDDO
783      ENDIF      ENDIF
     zx_ajustq=.FALSE.  
784    
785      ! Convection seche (thermiques ou ajustement)      ! Convection s\`eche (thermiques ou ajustement)
786    
787      d_t_ajs(:, :)=0.      d_t_ajs = 0.
788      d_u_ajs(:, :)=0.      d_u_ajs = 0.
789      d_v_ajs(:, :)=0.      d_v_ajs = 0.
790      d_q_ajs(:, :)=0.      d_q_ajs = 0.
791      fm_therm(:, :)=0.      fm_therm = 0.
792      entr_therm(:, :)=0.      entr_therm = 0.
793    
794      IF(prt_level>9)WRITE(lunout, *) &      if (iflag_thermals == 0) then
795           'AVANT LA CONVECTION SECHE, iflag_thermals=' &         ! Ajustement sec
796           , iflag_thermals, '   nsplit_thermals=', nsplit_thermals         CALL ajsec(paprs, play, t_seri, q_seri, d_t_ajs, d_q_ajs)
797      if(iflag_thermals < 0) then         t_seri = t_seri + d_t_ajs
798         !  Rien         q_seri = q_seri + d_q_ajs
        IF(prt_level>9)WRITE(lunout, *)'pas de convection'  
     else if(iflag_thermals == 0) then  
        !  Ajustement sec  
        IF(prt_level>9)WRITE(lunout, *)'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(:, :)  
799      else      else
800         !  Thermiques         call calltherm(dtphys, play, paprs, pphi, u_seri, v_seri, t_seri, &
801         IF(prt_level>9)WRITE(lunout, *)'JUSTE AVANT, iflag_thermals=' &              q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
             , iflag_thermals, '   nsplit_thermals=', nsplit_thermals  
        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)  
802      endif      endif
803    
804      IF (if_ebil >= 2) THEN      ! Caclul des ratqs
        ztit='after dry_adjust'  
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
     END IF  
805    
806      !  Caclul des ratqs      ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q
807        ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno
     !   ratqs convectifs a l'ancienne en fonction de q(z=0)-q / q  
     !   on ecrase le tableau ratqsc calcule par clouds_gno  
808      if (iflag_cldcon == 1) then      if (iflag_cldcon == 1) then
809         do k=1, llm         do k = 1, llm
810            do i=1, klon            do i = 1, klon
811               if(ptconv(i, k)) then               if(ptconv(i, k)) then
812                  ratqsc(i, k)=ratqsbas &                  ratqsc(i, k) = ratqsbas + fact_cldcon &
813                       +fact_cldcon*(q_seri(i, 1)-q_seri(i, k))/q_seri(i, k)                       * (q_seri(i, 1) - q_seri(i, k)) / q_seri(i, k)
814               else               else
815                  ratqsc(i, k)=0.                  ratqsc(i, k) = 0.
816               endif               endif
817            enddo            enddo
818         enddo         enddo
819      endif      endif
820    
821      !   ratqs stables      ! ratqs stables
822      do k=1, llm      do k = 1, llm
823         do i=1, klon         do i = 1, klon
824            ratqss(i, k)=ratqsbas+(ratqshaut-ratqsbas)* &            ratqss(i, k) = ratqsbas + (ratqshaut - ratqsbas) &
825                 min((paprs(i, 1)-pplay(i, k))/(paprs(i, 1)-30000.), 1.)                 * min((paprs(i, 1) - play(i, k)) / (paprs(i, 1) - 3e4), 1.)
826         enddo         enddo
827      enddo      enddo
828    
829      !  ratqs final      ! ratqs final
830      if (iflag_cldcon == 1 .or.iflag_cldcon == 2) then      if (iflag_cldcon == 1 .or. iflag_cldcon == 2) then
831         !   les ratqs sont une conbinaison de ratqss et ratqsc         ! les ratqs sont une conbinaison de ratqss et ratqsc
832         !   ratqs final         ! ratqs final
833         !   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
834         !   relaxation des ratqs         ! relaxation des ratqs
835         facteur=exp(-pdtphys*facttemps)         ratqs = max(ratqs * exp(- dtphys * facttemps), ratqss)
836         ratqs(:, :)=max(ratqs(:, :)*facteur, ratqss(:, :))         ratqs = max(ratqs, ratqsc)
        ratqs(:, :)=max(ratqs(:, :), ratqsc(:, :))  
837      else      else
838         !   on ne prend que le ratqs stable pour fisrtilp         ! on ne prend que le ratqs stable pour fisrtilp
839         ratqs(:, :)=ratqss(:, :)         ratqs = ratqss
840      endif      endif
841    
842      ! Appeler le processus de condensation a grande echelle      CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &
843      ! et le processus de precipitation           d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, rain_lsc, snow_lsc, &
844      CALL fisrtilp(dtime, paprs, pplay, &           pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &
845           t_seri, q_seri, ptconv, ratqs, &           psfl, rhcl)
          d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, &  
          rain_lsc, snow_lsc, &  
          pfrac_impa, pfrac_nucl, pfrac_1nucl, &  
          frac_impa, frac_nucl, &  
          prfl, psfl, rhcl)  
846    
847      WHERE (rain_lsc < 0) rain_lsc = 0.      WHERE (rain_lsc < 0) rain_lsc = 0.
848      WHERE (snow_lsc < 0) snow_lsc = 0.      WHERE (snow_lsc < 0) snow_lsc = 0.
# Line 1583  contains Line 855  contains
855            IF (.NOT.new_oliq) cldliq(i, k) = ql_seri(i, k)            IF (.NOT.new_oliq) cldliq(i, k) = ql_seri(i, k)
856         ENDDO         ENDDO
857      ENDDO      ENDDO
     IF (check) THEN  
        za = qcheck(klon, llm, paprs, q_seri, ql_seri, airephy)  
        WRITE(lunout, *)"apresilp=", za  
        zx_t = 0.0  
        za = 0.0  
        DO i = 1, klon  
           za = za + airephy(i)/REAL(klon)  
           zx_t = zx_t + (rain_lsc(i) &  
                + snow_lsc(i))*airephy(i)/REAL(klon)  
        ENDDO  
        zx_t = zx_t/za*dtime  
        WRITE(lunout, *)"Precip=", zx_t  
     ENDIF  
   
     IF (if_ebil >= 2) THEN  
        ztit='after fisrt'  
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        call diagphy(airephy, ztit, ip_ebil &  
             , zero_v, zero_v, zero_v, zero_v, zero_v &  
             , zero_v, rain_lsc, snow_lsc, ztsol &  
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
     END IF  
858    
859      !  PRESCRIPTION DES NUAGES POUR LE RAYONNEMENT      ! PRESCRIPTION DES NUAGES POUR LE RAYONNEMENT
860    
861      ! 1. NUAGES CONVECTIFS      ! 1. NUAGES CONVECTIFS
862    
863      IF (iflag_cldcon.le.-1) THEN ! seulement pour Tiedtke      IF (iflag_cldcon <= - 1) THEN
864         snow_tiedtke=0.         ! seulement pour Tiedtke
865         if (iflag_cldcon == -1) then         snow_tiedtke = 0.
866            rain_tiedtke=rain_con         if (iflag_cldcon == - 1) then
867              rain_tiedtke = rain_con
868         else         else
869            rain_tiedtke=0.            rain_tiedtke = 0.
870            do k=1, llm            do k = 1, llm
871               do i=1, klon               do i = 1, klon
872                  if (d_q_con(i, k) < 0.) then                  if (d_q_con(i, k) < 0.) then
873                     rain_tiedtke(i)=rain_tiedtke(i)-d_q_con(i, k)/pdtphys &                     rain_tiedtke(i) = rain_tiedtke(i) - d_q_con(i, k) / dtphys &
874                          *(paprs(i, k)-paprs(i, k+1))/rg                          * zmasse(i, k)
875                  endif                  endif
876               enddo               enddo
877            enddo            enddo
878         endif         endif
879    
880         ! Nuages diagnostiques pour Tiedtke         ! Nuages diagnostiques pour Tiedtke
881         CALL diagcld1(paprs, pplay, &         CALL diagcld1(paprs, play, rain_tiedtke, snow_tiedtke, ibas_con, &
882              rain_tiedtke, snow_tiedtke, ibas_con, itop_con, &              itop_con, diafra, dialiq)
             diafra, dialiq)  
883         DO k = 1, llm         DO k = 1, llm
884            DO i = 1, klon            DO i = 1, klon
885               IF (diafra(i, k).GT.cldfra(i, k)) THEN               IF (diafra(i, k) > cldfra(i, k)) THEN
886                  cldliq(i, k) = dialiq(i, k)                  cldliq(i, k) = dialiq(i, k)
887                  cldfra(i, k) = diafra(i, k)                  cldfra(i, k) = diafra(i, k)
888               ENDIF               ENDIF
889            ENDDO            ENDDO
890         ENDDO         ENDDO
   
891      ELSE IF (iflag_cldcon == 3) THEN      ELSE IF (iflag_cldcon == 3) THEN
892         ! On prend pour les nuages convectifs le max du calcul de la         ! On prend pour les nuages convectifs le maximum du calcul de
893         ! convection et du calcul du pas de temps précédent diminué d'un facteur         ! la convection et du calcul du pas de temps pr\'ec\'edent diminu\'e
894         ! facttemps         ! d'un facteur facttemps.
895         facteur = pdtphys *facttemps         facteur = dtphys * facttemps
896         do k=1, llm         do k = 1, llm
897            do i=1, klon            do i = 1, klon
898               rnebcon(i, k)=rnebcon(i, k)*facteur               rnebcon(i, k) = rnebcon(i, k) * facteur
899               if (rnebcon0(i, k)*clwcon0(i, k).gt.rnebcon(i, k)*clwcon(i, k)) &               if (rnebcon0(i, k) * clwcon0(i, k) &
900                    then                    > rnebcon(i, k) * clwcon(i, k)) then
901                  rnebcon(i, k)=rnebcon0(i, k)                  rnebcon(i, k) = rnebcon0(i, k)
902                  clwcon(i, k)=clwcon0(i, k)                  clwcon(i, k) = clwcon0(i, k)
903               endif               endif
904            enddo            enddo
905         enddo         enddo
906    
907         !   On prend la somme des fractions nuageuses et des contenus en eau         ! On prend la somme des fractions nuageuses et des contenus en eau
908         cldfra(:, :)=min(max(cldfra(:, :), rnebcon(:, :)), 1.)         cldfra = min(max(cldfra, rnebcon), 1.)
909         cldliq(:, :)=cldliq(:, :)+rnebcon(:, :)*clwcon(:, :)         cldliq = cldliq + rnebcon * clwcon
   
910      ENDIF      ENDIF
911    
912      ! 2. NUAGES STARTIFORMES      ! 2. Nuages stratiformes
913    
914      IF (ok_stratus) THEN      IF (ok_stratus) THEN
915         CALL diagcld2(paprs, pplay, t_seri, q_seri, diafra, dialiq)         CALL diagcld2(paprs, play, t_seri, q_seri, diafra, dialiq)
916         DO k = 1, llm         DO k = 1, llm
917            DO i = 1, klon            DO i = 1, klon
918               IF (diafra(i, k).GT.cldfra(i, k)) THEN               IF (diafra(i, k) > cldfra(i, k)) THEN
919                  cldliq(i, k) = dialiq(i, k)                  cldliq(i, k) = dialiq(i, k)
920                  cldfra(i, k) = diafra(i, k)                  cldfra(i, k) = diafra(i, k)
921               ENDIF               ENDIF
# Line 1679  contains Line 924  contains
924      ENDIF      ENDIF
925    
926      ! Precipitation totale      ! Precipitation totale
   
927      DO i = 1, klon      DO i = 1, klon
928         rain_fall(i) = rain_con(i) + rain_lsc(i)         rain_fall(i) = rain_con(i) + rain_lsc(i)
929         snow_fall(i) = snow_con(i) + snow_lsc(i)         snow_fall(i) = snow_con(i) + snow_lsc(i)
930      ENDDO      ENDDO
931    
932      IF (if_ebil >= 2) THEN      ! Humidit\'e relative pour diagnostic :
        ztit="after diagcld"  
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
     END IF  
   
     ! Calculer l'humidite relative pour diagnostique  
   
933      DO k = 1, llm      DO k = 1, llm
934         DO i = 1, klon         DO i = 1, klon
935            zx_t = t_seri(i, k)            zx_t = t_seri(i, k)
936            IF (thermcep) THEN            IF (thermcep) THEN
937               zdelta = MAX(0., SIGN(1., rtt-zx_t))               zx_qs = r2es * FOEEW(zx_t, rtt >= zx_t) / play(i, k)
938               zx_qs  = r2es * FOEEW(zx_t, zdelta)/pplay(i, k)               zx_qs = MIN(0.5, zx_qs)
939               zx_qs  = MIN(0.5, zx_qs)               zcor = 1. / (1. - retv * zx_qs)
940               zcor   = 1./(1.-retv*zx_qs)               zx_qs = zx_qs * zcor
              zx_qs  = zx_qs*zcor  
941            ELSE            ELSE
942               IF (zx_t < t_coup) THEN               IF (zx_t < t_coup) THEN
943                  zx_qs = qsats(zx_t)/pplay(i, k)                  zx_qs = qsats(zx_t) / play(i, k)
944               ELSE               ELSE
945                  zx_qs = qsatl(zx_t)/pplay(i, k)                  zx_qs = qsatl(zx_t) / play(i, k)
946               ENDIF               ENDIF
947            ENDIF            ENDIF
948            zx_rh(i, k) = q_seri(i, k)/zx_qs            zx_rh(i, k) = q_seri(i, k) / zx_qs
949            zqsat(i, k)=zx_qs            zqsat(i, k) = zx_qs
950         ENDDO         ENDDO
951      ENDDO      ENDDO
     !jq - introduce the aerosol direct and first indirect radiative forcings  
     !jq - Johannes Quaas, 27/11/2003 (quaas@lmd.jussieu.fr)  
     IF (ok_ade.OR.ok_aie) THEN  
        ! Get sulfate aerosol distribution  
        CALL readsulfate(rdayvrai, firstcal, sulfate)  
        CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi)  
   
        ! Calculate aerosol optical properties (Olivier Boucher)  
        CALL aeropt(pplay, paprs, t_seri, sulfate, rhcl, &  
             tau_ae, piz_ae, cg_ae, aerindex)  
     ELSE  
        tau_ae(:, :, :)=0.0  
        piz_ae(:, :, :)=0.0  
        cg_ae(:, :, :)=0.0  
     ENDIF  
952    
953      ! Calculer les parametres optiques des nuages et quelques      ! Introduce the aerosol direct and first indirect radiative forcings:
954      ! parametres pour diagnostiques:      tau_ae = 0.
955        piz_ae = 0.
956        cg_ae = 0.
957    
958        ! Param\`etres optiques des nuages et quelques param\`etres pour
959        ! diagnostics :
960      if (ok_newmicro) then      if (ok_newmicro) then
961         CALL newmicro (paprs, pplay, ok_newmicro, &         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &
962              t_seri, cldliq, cldfra, cldtau, cldemi, &              cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, fiwc, ok_aie, &
963              cldh, cldl, cldm, cldt, cldq, &              sulfate, sulfate_pi, bl95_b0, bl95_b1, cldtaupi, re, fl)
             flwp, fiwp, flwc, fiwc, &  
             ok_aie, &  
             sulfate, sulfate_pi, &  
             bl95_b0, bl95_b1, &  
             cldtaupi, re, fl)  
964      else      else
965         CALL nuage (paprs, pplay, &         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &
966              t_seri, cldliq, cldfra, cldtau, cldemi, &              cldl, cldm, cldt, cldq, ok_aie, sulfate, sulfate_pi, bl95_b0, &
967              cldh, cldl, cldm, cldt, cldq, &              bl95_b1, cldtaupi, re, fl)
             ok_aie, &  
             sulfate, sulfate_pi, &  
             bl95_b0, bl95_b1, &  
             cldtaupi, re, fl)  
   
968      endif      endif
969    
970      ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol.      IF (MOD(itap - 1, radpas) == 0) THEN
971           ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol.
972      IF (MOD(itaprad, radpas) == 0) THEN         ! Calcul de l'abedo moyen par maille
973         DO i = 1, klon         albsol = sum(falbe * pctsrf, dim = 2)
974            albsol(i) = falbe(i, is_oce) * pctsrf(i, is_oce) &  
975                 + falbe(i, is_lic) * pctsrf(i, is_lic) &         ! Rayonnement (compatible Arpege-IFS) :
976                 + falbe(i, is_ter) * pctsrf(i, is_ter) &         CALL radlwsw(dist, mu0, fract, paprs, play, ztsol, albsol, t_seri, &
977                 + falbe(i, is_sic) * pctsrf(i, is_sic)              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &
978            albsollw(i) = falblw(i, is_oce) * pctsrf(i, is_oce) &              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &
979                 + falblw(i, is_lic) * pctsrf(i, is_lic) &              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &
980                 + falblw(i, is_ter) * pctsrf(i, is_ter) &              swup0, swup, ok_ade, ok_aie, tau_ae, piz_ae, cg_ae, topswad, &
981                 + falblw(i, is_sic) * pctsrf(i, is_sic)              solswad, cldtaupi, topswai, solswai)
        ENDDO  
        ! nouveau rayonnement (compatible Arpege-IFS):  
        CALL radlwsw(dist, rmu0, fract,  &  
             paprs, pplay, zxtsol, albsol, albsollw, t_seri, q_seri, &  
             wo, &  
             cldfra, cldemi, cldtau, &  
             heat, heat0, cool, cool0, radsol, albpla, &  
             topsw, toplw, solsw, sollw, &  
             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)  
        itaprad = 0  
982      ENDIF      ENDIF
     itaprad = itaprad + 1  
983    
984      ! Ajouter la tendance des rayonnements (tous les pas)      ! Ajouter la tendance des rayonnements (tous les pas)
985    
986      DO k = 1, llm      DO k = 1, llm
987         DO i = 1, klon         DO i = 1, klon
988            t_seri(i, k) = t_seri(i, k) &            t_seri(i, k) = t_seri(i, k) + (heat(i, k) - cool(i, k)) * dtphys &
989                 + (heat(i, k)-cool(i, k)) * dtime/86400.                 / 86400.
990         ENDDO         ENDDO
991      ENDDO      ENDDO
992    
     IF (if_ebil >= 2) THEN  
        ztit='after rad'  
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        call diagphy(airephy, ztit, ip_ebil &  
             , topsw, toplw, solsw, sollw, zero_v &  
             , zero_v, zero_v, zero_v, ztsol &  
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
     END IF  
   
993      ! Calculer l'hydrologie de la surface      ! Calculer l'hydrologie de la surface
   
994      DO i = 1, klon      DO i = 1, klon
995         zxqsurf(i) = 0.0         zxqsurf(i) = 0.
996         zxsnow(i) = 0.0         zxsnow(i) = 0.
997      ENDDO      ENDDO
998      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
999         DO i = 1, klon         DO i = 1, klon
1000            zxqsurf(i) = zxqsurf(i) + fqsurf(i, nsrf)*pctsrf(i, nsrf)            zxqsurf(i) = zxqsurf(i) + fqsurf(i, nsrf) * pctsrf(i, nsrf)
1001            zxsnow(i) = zxsnow(i) + fsnow(i, nsrf)*pctsrf(i, nsrf)            zxsnow(i) = zxsnow(i) + fsnow(i, nsrf) * pctsrf(i, nsrf)
1002         ENDDO         ENDDO
1003      ENDDO      ENDDO
1004    
1005      ! Calculer le bilan du sol et la derive de temperature (couplage)      ! Calculer le bilan du sol et la d\'erive de temp\'erature (couplage)
1006    
1007      DO i = 1, klon      DO i = 1, klon
1008         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
1009      ENDDO      ENDDO
1010    
1011      !moddeblott(jan95)      ! Param\'etrisation de l'orographie \`a l'\'echelle sous-maille :
     ! Appeler le programme de parametrisation de l'orographie  
     ! a l'echelle sous-maille:  
1012    
1013      IF (ok_orodr) THEN      IF (ok_orodr) THEN
1014           ! S\'election des points pour lesquels le sch\'ema est actif :
1015         !  selection des points pour lesquels le shema est actif:         igwd = 0
1016         igwd=0         DO i = 1, klon
1017         DO i=1, klon            itest(i) = 0
1018            itest(i)=0            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN
1019            IF (((zpic(i)-zmea(i)).GT.100.).AND.(zstd(i).GT.10.0)) THEN               itest(i) = 1
1020               itest(i)=1               igwd = igwd + 1
              igwd=igwd+1  
              idx(igwd)=i  
1021            ENDIF            ENDIF
1022         ENDDO         ENDDO
1023    
1024         CALL drag_noro(klon, llm, dtime, paprs, pplay, &         CALL drag_noro(klon, llm, dtphys, paprs, play, zmea, zstd, zsig, zgam, &
1025              zmea, zstd, zsig, zgam, zthe, zpic, zval, &              zthe, zpic, zval, itest, t_seri, u_seri, v_seri, zulow, zvlow, &
1026              igwd, idx, itest, &              zustrdr, zvstrdr, d_t_oro, d_u_oro, d_v_oro)
             t_seri, u_seri, v_seri, &  
             zulow, zvlow, zustrdr, zvstrdr, &  
             d_t_oro, d_u_oro, d_v_oro)  
1027    
1028         !  ajout des tendances         ! ajout des tendances
1029         DO k = 1, llm         DO k = 1, llm
1030            DO i = 1, klon            DO i = 1, klon
1031               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 1858  contains Line 1033  contains
1033               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)
1034            ENDDO            ENDDO
1035         ENDDO         ENDDO
1036        ENDIF
     ENDIF ! fin de test sur ok_orodr  
1037    
1038      IF (ok_orolf) THEN      IF (ok_orolf) THEN
1039           ! S\'election des points pour lesquels le sch\'ema est actif :
1040         !  selection des points pour lesquels le shema est actif:         igwd = 0
1041         igwd=0         DO i = 1, klon
1042         DO i=1, klon            itest(i) = 0
1043            itest(i)=0            IF (zpic(i) - zmea(i) > 100.) THEN
1044            IF ((zpic(i)-zmea(i)).GT.100.) THEN               itest(i) = 1
1045               itest(i)=1               igwd = igwd + 1
              igwd=igwd+1  
              idx(igwd)=i  
1046            ENDIF            ENDIF
1047         ENDDO         ENDDO
1048    
1049         CALL lift_noro(klon, llm, dtime, paprs, pplay, &         CALL lift_noro(klon, llm, dtphys, paprs, play, rlat, zmea, zstd, zpic, &
1050              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, &  
1051              d_t_lif, d_u_lif, d_v_lif)              d_t_lif, d_u_lif, d_v_lif)
1052    
1053         !  ajout des tendances         ! Ajout des tendances :
1054         DO k = 1, llm         DO k = 1, llm
1055            DO i = 1, klon            DO i = 1, klon
1056               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 1889  contains Line 1058  contains
1058               v_seri(i, k) = v_seri(i, k) + d_v_lif(i, k)               v_seri(i, k) = v_seri(i, k) + d_v_lif(i, k)
1059            ENDDO            ENDDO
1060         ENDDO         ENDDO
1061        ENDIF
1062    
1063      ENDIF ! fin de test sur ok_orolf      ! Stress n\'ecessaires : toute la physique
   
     ! STRESS NECESSAIRES: TOUTE LA PHYSIQUE  
1064    
1065      DO i = 1, klon      DO i = 1, klon
1066         zustrph(i)=0.         zustrph(i) = 0.
1067         zvstrph(i)=0.         zvstrph(i) = 0.
1068      ENDDO      ENDDO
1069      DO k = 1, llm      DO k = 1, llm
1070         DO i = 1, klon         DO i = 1, klon
1071            zustrph(i)=zustrph(i)+(u_seri(i, k)-u(i, k))/dtime* &            zustrph(i) = zustrph(i) + (u_seri(i, k) - u(i, k)) / dtphys &
1072                 (paprs(i, k)-paprs(i, k+1))/rg                 * zmasse(i, k)
1073            zvstrph(i)=zvstrph(i)+(v_seri(i, k)-v(i, k))/dtime* &            zvstrph(i) = zvstrph(i) + (v_seri(i, k) - v(i, k)) / dtphys &
1074                 (paprs(i, k)-paprs(i, k+1))/rg                 * zmasse(i, k)
1075         ENDDO         ENDDO
1076      ENDDO      ENDDO
1077    
1078      !IM calcul composantes axiales du moment angulaire et couple des montagnes      CALL aaam_bud(rg, romega, rlat, rlon, pphis, zustrdr, zustrli, zustrph, &
1079             zvstrdr, zvstrli, zvstrph, paprs, u, v, aam, torsfc)
     CALL aaam_bud (27, klon, llm, gmtime, &  
          ra, rg, romega, &  
          rlat, rlon, pphis, &  
          zustrdr, zustrli, zustrph, &  
          zvstrdr, zvstrli, zvstrph, &  
          paprs, u, v, &  
          aam, torsfc)  
   
     IF (if_ebil >= 2) THEN  
        ztit='after orography'  
        CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
     END IF  
   
     !AA Installation de l'interface online-offline pour traceurs  
   
     !   Calcul  des tendances traceurs  
   
     call phytrac(rnpb, itap, lmt_pas, julien,  gmtime, firstcal, lafin, nq-2, &  
          dtime, u, v, t, paprs, pplay, &  
          pmfu,  pmfd,  pen_u,  pde_u,  pen_d,  pde_d, &  
          ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, &  
          pctsrf, frac_impa,  frac_nucl, &  
          presnivs, pphis, pphi, albsol, qx(1, 1, 1),  &  
          rhcl, cldfra,  rneb,  diafra,  cldliq,  &  
          itop_con, ibas_con, pmflxr, pmflxs, &  
          prfl, psfl, da, phi, mp, upwd, dnwd, &  
          tr_seri)  
   
     IF (offline) THEN  
   
        print*, 'Attention on met a 0 les thermiques pour phystoke'  
        call phystokenc(pdtphys, rlon, rlat, &  
             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, dtime, itap)  
1080    
1081      ENDIF      ! Calcul des tendances traceurs
1082        call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &
1083             mfd, pde_u, pen_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, &
1084             pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, tr_seri, &
1085             zmasse, ncid_startphy)
1086    
1087      ! Calculer le transport de l'eau et de l'energie (diagnostique)      IF (offline) call phystokenc(dtphys, t, mfu, mfd, pen_u, pde_u, pen_d, &
1088             pde_d, fm_therm, entr_therm, ycoefh, yu1, yv1, ftsol, pctsrf, &
1089             frac_impa, frac_nucl, pphis, airephy, dtphys)
1090    
1091      CALL transp (paprs, zxtsol, &      ! Calculer le transport de l'eau et de l'energie (diagnostique)
1092           t_seri, q_seri, u_seri, v_seri, zphi, &      CALL transp(paprs, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, ue, uq)
          ve, vq, ue, uq)  
1093    
1094      !IM diag. bilKP      ! diag. bilKP
1095    
1096      CALL transp_lay (paprs, zxtsol, &      CALL transp_lay(paprs, t_seri, q_seri, u_seri, v_seri, zphi, &
          t_seri, q_seri, u_seri, v_seri, zphi, &  
1097           ve_lay, vq_lay, ue_lay, uq_lay)           ve_lay, vq_lay, ue_lay, uq_lay)
1098    
1099      ! Accumuler les variables a stocker dans les fichiers histoire:      ! Accumuler les variables a stocker dans les fichiers histoire:
1100    
1101      !+jld ec_conser      ! conversion Ec en énergie thermique
1102      DO k = 1, llm      DO k = 1, llm
1103         DO i = 1, klon         DO i = 1, klon
1104            ZRCPD = RCPD*(1.0+RVTMP2*q_seri(i, k))            ZRCPD = RCPD * (1. + RVTMP2 * q_seri(i, k))
1105            d_t_ec(i, k)=0.5/ZRCPD &            d_t_ec(i, k) = 0.5 / ZRCPD &
1106                 *(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)
1107            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)
1108            d_t_ec(i, k) = d_t_ec(i, k)/dtime            d_t_ec(i, k) = d_t_ec(i, k) / dtphys
1109         END DO         END DO
1110      END DO      END DO
     !-jld ec_conser  
     IF (if_ebil >= 1) THEN  
        ztit='after physic'  
        CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, dtime &  
             , t_seri, q_seri, ql_seri, qs_seri, u_seri, v_seri, paprs &  
             , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
        !     Comme les tendances de la physique sont ajoute dans la dynamique,  
        !     on devrait avoir que la variation d'entalpie par la dynamique  
        !     est egale a la variation de la physique au pas de temps precedent.  
        !     Donc la somme de ces 2 variations devrait etre nulle.  
        call diagphy(airephy, ztit, ip_ebil &  
             , topsw, toplw, solsw, sollw, sens &  
             , evap, rain_fall, snow_fall, ztsol &  
             , d_h_vcol, d_qt, d_ec &  
             , fs_bound, fq_bound )  
   
        d_h_vcol_phy=d_h_vcol  
   
     END IF  
   
     !   SORTIES  
1111    
1112      !IM Interpolation sur les niveaux de pression du NMC      ! SORTIES
     call calcul_STDlev  
1113    
1114      !cc prw = eau precipitable      ! prw = eau precipitable
1115      DO i = 1, klon      DO i = 1, klon
1116         prw(i) = 0.         prw(i) = 0.
1117         DO k = 1, llm         DO k = 1, llm
1118            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  
1119         ENDDO         ENDDO
1120      ENDDO      ENDDO
1121    
     !IM initialisation + calculs divers diag AMIP2  
     call calcul_divers  
   
1122      ! Convertir les incrementations en tendances      ! Convertir les incrementations en tendances
1123    
1124      DO k = 1, llm      DO k = 1, llm
1125         DO i = 1, klon         DO i = 1, klon
1126            d_u(i, k) = ( u_seri(i, k) - u(i, k) ) / dtime            d_u(i, k) = (u_seri(i, k) - u(i, k)) / dtphys
1127            d_v(i, k) = ( v_seri(i, k) - v(i, k) ) / dtime            d_v(i, k) = (v_seri(i, k) - v(i, k)) / dtphys
1128            d_t(i, k) = ( t_seri(i, k)-t(i, k) ) / dtime            d_t(i, k) = (t_seri(i, k) - t(i, k)) / dtphys
1129            d_qx(i, k, ivap) = ( q_seri(i, k) - qx(i, k, ivap) ) / dtime            d_qx(i, k, ivap) = (q_seri(i, k) - qx(i, k, ivap)) / dtphys
1130            d_qx(i, k, iliq) = ( ql_seri(i, k) - qx(i, k, iliq) ) / dtime            d_qx(i, k, iliq) = (ql_seri(i, k) - qx(i, k, iliq)) / dtphys
1131         ENDDO         ENDDO
1132      ENDDO      ENDDO
1133    
1134      IF (nq >= 3) THEN      DO iq = 3, nqmx
1135         DO iq = 3, nq         DO k = 1, llm
1136            DO  k = 1, llm            DO i = 1, klon
1137               DO  i = 1, klon               d_qx(i, k, iq) = (tr_seri(i, k, iq - 2) - qx(i, k, iq)) / dtphys
                 d_qx(i, k, iq) = ( tr_seri(i, k, iq-2) - qx(i, k, iq) ) / dtime  
              ENDDO  
1138            ENDDO            ENDDO
1139         ENDDO         ENDDO
1140      ENDIF      ENDDO
1141    
1142      ! 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:
   
1143      DO k = 1, llm      DO k = 1, llm
1144         DO i = 1, klon         DO i = 1, klon
1145            t_ancien(i, k) = t_seri(i, k)            t_ancien(i, k) = t_seri(i, k)
# Line 2043  contains Line 1147  contains
1147         ENDDO         ENDDO
1148      ENDDO      ENDDO
1149    
1150      !   Ecriture des sorties      CALL histwrite_phy("phis", pphis)
1151        CALL histwrite_phy("aire", airephy)
1152      call write_histhf      CALL histwrite_phy("psol", paprs(:, 1))
1153      call write_histday      CALL histwrite_phy("precip", rain_fall + snow_fall)
1154      call write_histins      CALL histwrite_phy("plul", rain_lsc + snow_lsc)
1155        CALL histwrite_phy("pluc", rain_con + snow_con)
1156      ! Si c'est la fin, il faut conserver l'etat de redemarrage      CALL histwrite_phy("tsol", ztsol)
1157        CALL histwrite_phy("t2m", zt2m)
1158      IF (lafin) THEN      CALL histwrite_phy("q2m", zq2m)
1159         itau_phy = itau_phy + itap      CALL histwrite_phy("u10m", zu10m)
1160         CALL phyredem ("restartphy.nc", dtime, radpas, &      CALL histwrite_phy("v10m", zv10m)
1161              rlat, rlon, pctsrf, ftsol, ftsoil, &      CALL histwrite_phy("snow", snow_fall)
1162              tslab, seaice,  & !IM "slab" ocean      CALL histwrite_phy("cdrm", cdragm)
1163              fqsurf, qsol, &      CALL histwrite_phy("cdrh", cdragh)
1164              fsnow, falbe, falblw, fevap, rain_fall, snow_fall, &      CALL histwrite_phy("topl", toplw)
1165              solsw, sollwdown, dlw, &      CALL histwrite_phy("evap", evap)
1166              radsol, frugs, agesno, &      CALL histwrite_phy("sols", solsw)
1167              zmea, zstd, zsig, zgam, zthe, zpic, zval, rugoro, &      CALL histwrite_phy("soll", sollw)
1168              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0)      CALL histwrite_phy("solldown", sollwdown)
1169      ENDIF      CALL histwrite_phy("bils", bils)
1170        CALL histwrite_phy("sens", - sens)
1171    contains      CALL histwrite_phy("fder", fder)
1172        CALL histwrite_phy("dtsvdfo", d_ts(:, is_oce))
1173      subroutine calcul_STDlev      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
1174        CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))
1175        CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))
1176    
1177        !     From phylmd/calcul_STDlev.h, v 1.1 2005/05/25 13:10:09      DO nsrf = 1, nbsrf
1178           CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
1179        !IM on initialise les champs en debut du jour ou du mois         CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))
1180           CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))
1181           CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))
1182           CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf))
1183           CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf))
1184           CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1185           CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1186           CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1187        END DO
1188    
1189        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("albs", albsol)
1190             ecrit_day, ecrit_mth, &      CALL histwrite_phy("rugs", zxrugs)
1191             tnondef, tsumSTD)      CALL histwrite_phy("s_pblh", s_pblh)
1192        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("s_pblt", s_pblt)
1193             ecrit_day, ecrit_mth, &      CALL histwrite_phy("s_lcl", s_lcl)
1194             tnondef, usumSTD)      CALL histwrite_phy("s_capCL", s_capCL)
1195        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("s_oliqCL", s_oliqCL)
1196             ecrit_day, ecrit_mth, &      CALL histwrite_phy("s_cteiCL", s_cteiCL)
1197             tnondef, vsumSTD)      CALL histwrite_phy("s_therm", s_therm)
1198        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("s_trmb1", s_trmb1)
1199             ecrit_day, ecrit_mth, &      CALL histwrite_phy("s_trmb2", s_trmb2)
1200             tnondef, wsumSTD)      CALL histwrite_phy("s_trmb3", s_trmb3)
1201        CALL ini_undefSTD(nlevSTD, itap, &  
1202             ecrit_day, ecrit_mth, &      if (conv_emanuel) then
1203             tnondef, phisumSTD)         CALL histwrite_phy("ptop", ema_pct)
1204        CALL ini_undefSTD(nlevSTD, itap, &         CALL histwrite_phy("dnwd0", - mp)
1205             ecrit_day, ecrit_mth, &      end if
1206             tnondef, qsumSTD)  
1207        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("temp", t_seri)
1208             ecrit_day, ecrit_mth, &      CALL histwrite_phy("vitu", u_seri)
1209             tnondef, rhsumSTD)      CALL histwrite_phy("vitv", v_seri)
1210        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("geop", zphi)
1211             ecrit_day, ecrit_mth, &      CALL histwrite_phy("pres", play)
1212             tnondef, uvsumSTD)      CALL histwrite_phy("dtvdf", d_t_vdf)
1213        CALL ini_undefSTD(nlevSTD, itap, &      CALL histwrite_phy("dqvdf", d_q_vdf)
1214             ecrit_day, ecrit_mth, &      CALL histwrite_phy("rhum", zx_rh)
1215             tnondef, vqsumSTD)  
1216        CALL ini_undefSTD(nlevSTD, itap, &      if (ok_instan) call histsync(nid_ins)
1217             ecrit_day, ecrit_mth, &  
1218             tnondef, vTsumSTD)      IF (lafin) then
1219        CALL ini_undefSTD(nlevSTD, itap, &         call NF95_CLOSE(ncid_startphy)
1220             ecrit_day, ecrit_mth, &         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, &
1221             tnondef, wqsumSTD)              fsnow, falbe, fevap, rain_fall, snow_fall, solsw, sollw, dlw, &
1222        CALL ini_undefSTD(nlevSTD, itap, &              radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
1223             ecrit_day, ecrit_mth, &              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &
1224             tnondef, vphisumSTD)              w01)
1225        CALL ini_undefSTD(nlevSTD, itap, &      end IF
            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  
   
     !***********************************************  
   
     subroutine write_histday  
   
       !     From phylmd/write_histday.h, v 1.3 2005/05/25 13:10:09  
   
       if (ok_journe) THEN  
   
          ndex2d = 0  
          ndex3d = 0  
   
          ! Champs 2D:  
   
          itau_w = itau_phy + itap  
   
          !   FIN ECRITURE DES CHAMPS 3D  
   
          if (ok_sync) then  
             call histsync(nid_day)  
          endif  
   
       ENDIF  
   
     End subroutine write_histday  
   
     !****************************  
   
     subroutine write_histhf  
   
       ! From phylmd/write_histhf.h, v 1.5 2005/05/25 13:10:09  
   
       ndex2d = 0  
       ndex3d = 0  
   
       itau_w = itau_phy + itap  
   
       call write_histhf3d  
   
       IF (ok_sync) THEN  
          call histsync(nid_hf)  
       ENDIF  
   
     end subroutine write_histhf  
   
     !***************************************************************  
   
     subroutine write_histins  
   
       ! From phylmd/write_histins.h, v 1.2 2005/05/25 13:10:09  
   
       real zout  
   
       !--------------------------------------------------  
   
       IF (ok_instan) THEN  
   
          ndex2d = 0  
          ndex3d = 0  
   
          ! Champs 2D:  
   
          zsto = dtime * ecrit_ins  
          zout = dtime * ecrit_ins  
          itau_w = itau_phy + itap  
   
          i = NINT(zout/zsto)  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), pphis, zx_tmp_2d)  
          CALL histwrite(nid_ins, "phis", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          i = NINT(zout/zsto)  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), airephy, zx_tmp_2d)  
          CALL histwrite(nid_ins, "aire", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          DO i = 1, klon  
             zx_tmp_fi2d(i) = paprs(i, 1)  
          ENDDO  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
          CALL histwrite(nid_ins, "psol", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          DO i = 1, klon  
             zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)  
          ENDDO  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
          CALL histwrite(nid_ins, "precip", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          DO i = 1, klon  
             zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)  
          ENDDO  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
          CALL histwrite(nid_ins, "plul", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          DO i = 1, klon  
             zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)  
          ENDDO  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
          CALL histwrite(nid_ins, "pluc", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxtsol, zx_tmp_2d)  
          CALL histwrite(nid_ins, "tsol", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
          !ccIM  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zt2m, zx_tmp_2d)  
          CALL histwrite(nid_ins, "t2m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zq2m, zx_tmp_2d)  
          CALL histwrite(nid_ins, "q2m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zu10m, zx_tmp_2d)  
          CALL histwrite(nid_ins, "u10m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zv10m, zx_tmp_2d)  
          CALL histwrite(nid_ins, "v10m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), snow_fall, zx_tmp_2d)  
          CALL histwrite(nid_ins, "snow", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragm, zx_tmp_2d)  
          CALL histwrite(nid_ins, "cdrm", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragh, zx_tmp_2d)  
          CALL histwrite(nid_ins, "cdrh", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), toplw, zx_tmp_2d)  
          CALL histwrite(nid_ins, "topl", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), evap, zx_tmp_2d)  
          CALL histwrite(nid_ins, "evap", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), solsw, zx_tmp_2d)  
          CALL histwrite(nid_ins, "sols", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollw, zx_tmp_2d)  
          CALL histwrite(nid_ins, "soll", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollwdown, zx_tmp_2d)  
          CALL histwrite(nid_ins, "solldown", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), bils, zx_tmp_2d)  
          CALL histwrite(nid_ins, "bils", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          zx_tmp_fi2d(1:klon)=-1*sens(1:klon)  
          !     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sens, zx_tmp_2d)  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
          CALL histwrite(nid_ins, "sens", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), fder, zx_tmp_2d)  
          CALL histwrite(nid_ins, "fder", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_oce), zx_tmp_2d)  
          CALL histwrite(nid_ins, "dtsvdfo", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_ter), zx_tmp_2d)  
          CALL histwrite(nid_ins, "dtsvdft", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_lic), zx_tmp_2d)  
          CALL histwrite(nid_ins, "dtsvdfg", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_sic), zx_tmp_2d)  
          CALL histwrite(nid_ins, "dtsvdfi", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          DO nsrf = 1, nbsrf  
             !XXX  
             zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "pourc_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "fract_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "sens_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "lat_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "tsol_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "taux_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "tauy_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "rugs_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
             zx_tmp_fi2d(1 : klon) = falbe( 1 : klon, nsrf)  
             CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d)  
             CALL histwrite(nid_ins, "albe_"//clnsurf(nsrf), itau_w, &  
                  zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          END DO  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsol, zx_tmp_2d)  
          CALL histwrite(nid_ins, "albs", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsollw, zx_tmp_2d)  
          CALL histwrite(nid_ins, "albslw", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxrugs, zx_tmp_2d)  
          CALL histwrite(nid_ins, "rugs", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          !IM cf. AM 081204 BEG  
   
          !HBTM2  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblh, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_pblh", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblt, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_pblt", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_lcl, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_lcl", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_capCL, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_capCL", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_oliqCL, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_oliqCL", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_cteiCL, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_cteiCL", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_therm, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_therm", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb1, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_trmb1", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb2, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_trmb2", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb3, zx_tmp_2d)  
          CALL histwrite(nid_ins, "s_trmb3", itau_w, zx_tmp_2d, iim*(jjm + 1), &  
               ndex2d)  
   
          !IM cf. AM 081204 END  
   
          ! Champs 3D:  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d)  
          CALL histwrite(nid_ins, "temp", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d)  
          CALL histwrite(nid_ins, "vitu", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d)  
          CALL histwrite(nid_ins, "vitv", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), zphi, zx_tmp_3d)  
          CALL histwrite(nid_ins, "geop", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), pplay, zx_tmp_3d)  
          CALL histwrite(nid_ins, "pres", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_t_vdf, zx_tmp_3d)  
          CALL histwrite(nid_ins, "dtvdf", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_q_vdf, zx_tmp_3d)  
          CALL histwrite(nid_ins, "dqvdf", itau_w, zx_tmp_3d, &  
               iim*(jjm + 1)*llm, ndex3d)  
   
          if (ok_sync) then  
             call histsync(nid_ins)  
          endif  
       ENDIF  
   
     end subroutine write_histins  
   
     !****************************************************  
   
     subroutine write_histhf3d  
   
       ! From phylmd/write_histhf3d.h, v 1.2 2005/05/25 13:10:09  
   
       ndex2d = 0  
       ndex3d = 0  
   
       itau_w = itau_phy + itap  
   
       ! Champs 3D:  
   
       CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d)  
       CALL histwrite(nid_hf3d, "temp", itau_w, zx_tmp_3d, &  
            iim*(jjm + 1)*llm, ndex3d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), qx(1, 1, ivap), zx_tmp_3d)  
       CALL histwrite(nid_hf3d, "ovap", itau_w, zx_tmp_3d, &  
            iim*(jjm + 1)*llm, ndex3d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d)  
       CALL histwrite(nid_hf3d, "vitu", itau_w, zx_tmp_3d, &  
            iim*(jjm + 1)*llm, ndex3d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d)  
       CALL histwrite(nid_hf3d, "vitv", itau_w, zx_tmp_3d, &  
            iim*(jjm + 1)*llm, ndex3d)  
   
       if (nbtr >= 3) then  
          CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), tr_seri(1, 1, 3), &  
               zx_tmp_3d)  
          CALL histwrite(nid_hf3d, "O3", itau_w, zx_tmp_3d, iim*(jjm + 1)*llm, &  
               ndex3d)  
       end if  
   
       if (ok_sync) then  
          call histsync(nid_hf3d)  
       endif  
1226    
1227      end subroutine write_histhf3d      firstcal = .FALSE.
1228    
1229    END SUBROUTINE physiq    END SUBROUTINE physiq
1230    
   !****************************************************  
   
   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  
   
1231  end module physiq_m  end module physiq_m

Legend:
Removed from v.10  
changed lines
  Added in v.206

  ViewVC Help
Powered by ViewVC 1.1.21