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

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

  ViewVC Help
Powered by ViewVC 1.1.21