Ignore:
Timestamp:
Jun 17, 2022, 4:24:49 PM (2 years ago)
Author:
lguez
Message:

Sync latest trunk changes to branch LMDZ-ECRAD.

Location:
LMDZ6/branches/LMDZ-ECRAD
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ-ECRAD

  • LMDZ6/branches/LMDZ-ECRAD/libf/phylmd/physiq_mod.F90

    r3880 r4171  
    3434    USE FLOTT_GWD_rando_m, only: FLOTT_GWD_rando
    3535    USE fonte_neige_mod, ONLY  : fonte_neige_get_vars
    36     USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg
     36    USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg, longitude,latitude, &
     37         boundslon,boundslat, dx, dy, ind_cell_glo
    3738    USE ioipsl, only: histbeg, histvert, histdef, histend, histsync, &
    3839         histwrite, ju2ymds, ymds2ju, getin
    3940    USE ioipsl_getin_p_mod, ONLY : getin_p
    4041    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac
     42    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, types_trac, nqCO2
     43    USE readTracFiles_mod, ONLY: addPhase
     44    USE strings_mod,  ONLY: strIdx
    4245    USE iophy
    4346    USE limit_read_mod, ONLY : init_limit_read
     
    5356    USE phystokenc_mod, ONLY: offline, phystokenc
    5457    USE phys_cal_mod, only: year_len, mth_len, days_elapsed, jh_1jan, &
    55          year_cur, mth_cur,jD_cur, jH_cur, jD_ref, day_cur, hour
     58         year_cur, mth_cur,jD_cur, jH_cur, jD_ref, day_cur, hour, calend
    5659!!  USE phys_local_var_mod, ONLY : a long list of variables
    5760!!              ==> see below, after "CPP Keys" section
     
    5962    USE phys_output_mod
    6063    USE phys_output_ctrlout_mod
    61     USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
     64    USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level, &
     65         alert_first_call, call_alert, prt_alerte
    6266    USE readaerosol_mod, ONLY : init_aero_fromfile
    6367    USE readaerosolstrato_m, ONLY : init_readaerosolstrato
     
    6771    USE surface_data,     ONLY : type_ocean, ok_veget, landice_opt
    6872    USE time_phylmdz_mod, only: annee_ref, current_time, day_ini, day_ref, &
    69           day_step_phy, itau_phy, pdtphys, raz_date, start_time, update_time
     73          day_step_phy, itau_phy, pdtphys, raz_date, start_time, update_time, ndays
    7074    USE tracinca_mod, ONLY: config_inca
    7175    USE tropopause_m,     ONLY: dyn_tropopause
     76    USE ice_sursat_mod,  ONLY: flight_init, airplane
    7277    USE vampir
    7378    USE VERTICAL_LAYERS_MOD, ONLY: aps,bps, ap, bp
    7479    USE write_field_phy
     80    USE lscp_mod, ONLY : lscp
     81    USE wake_ini_mod, ONLY : wake_ini
     82    USE thermcell_ini_mod, ONLY : thermcell_ini
    7583
    7684    !USE cmp_seri_mod
     
    123131       ! [Variables internes non sauvegardees de la physique]
    124132       ! Variables locales pour effectuer les appels en serie
    125        t_seri,q_seri,ql_seri,qs_seri,u_seri,v_seri,tr_seri, &
     133       t_seri,q_seri,ql_seri,qs_seri,u_seri,v_seri,tr_seri,rneb_seri, &
    126134       ! Dynamic tendencies (diagnostics)
    127        d_t_dyn,d_q_dyn,d_ql_dyn,d_qs_dyn,d_u_dyn,d_v_dyn,d_tr_dyn, &
     135       d_t_dyn,d_q_dyn,d_ql_dyn,d_qs_dyn,d_u_dyn,d_v_dyn,d_tr_dyn,d_rneb_dyn, &
    128136       d_q_dyn2d,d_ql_dyn2d,d_qs_dyn2d, &
    129137       ! Physic tendencies
     
    144152       !
    145153       d_t_vdf,d_q_vdf,d_u_vdf,d_v_vdf,d_t_diss, &
     154       d_t_vdf_x, d_t_vdf_w, &
     155       d_q_vdf_x, d_q_vdf_w, &
    146156       d_ts, &
    147157       !
     
    197207       cdragm, cdragh,                   &
    198208       zustar, zu10m, zv10m, rh2m, qsat2m, &
    199        zq2m, zt2m, weak_inversion, &
    200        zq2m_cor,zt2m_cor,zu10m_cor,zv10m_cor, & ! pour corriger d'un bug
    201        zrh2m_cor,zqsat2m_cor, &
     209       zq2m, zt2m, zn2mout, weak_inversion, &
    202210       zt2m_min_mon, zt2m_max_mon,   &         ! pour calcul_divers.h
    203211       t2m_min_mon, t2m_max_mon,  &            ! pour calcul_divers.h
     
    212220       zxrunofflic,                            &
    213221       zxtsol, snow_lsc, zxfqfonte, zxqsurf,   &
     222       delta_qsurf,                            &
    214223       rain_lsc, rain_num,                     &
    215224       !
     
    217226       zxfluxlat_x, zxfluxlat_w, &
    218227       !
    219        d_t_vdf_x, d_t_vdf_w, &
    220        d_q_vdf_x, d_q_vdf_w, &
    221        pbl_tke_input, &
     228       pbl_tke_input, tke_dissip, l_mix, wprime,&
    222229       t_therm, q_therm, u_therm, v_therm, &
    223230       cdragh_x, cdragh_w, &
     
    246253       alp_bl_stat, n2, s2,  &
    247254       proba_notrig, random_notrig,  &
    248        cv_gen,  &
     255!!       cv_gen,  &  !moved to phys_state_var_mod
    249256       !
    250257       dnwd0,  &
     
    350357    include "dimsoil.h"
    351358    include "clesphys.h"
    352     include "thermcell.h"
     359    include "alpale.h"
    353360    include "dimpft.h"
    354361    !======================================================================
    355362    LOGICAL, SAVE :: ok_volcan ! pour activer les diagnostics volcaniques
    356363    !$OMP THREADPRIVATE(ok_volcan)
     364    INTEGER, SAVE :: flag_volc_surfstrat ! pour imposer le cool/heat rate à la surf/strato
     365    !$OMP THREADPRIVATE(flag_volc_surfstrat)
    357366    LOGICAL ok_cvl  ! pour activer le nouveau driver pour convection KE
    358367    PARAMETER (ok_cvl=.TRUE.)
     
    435444    !======================================================================
    436445    !
    437     INTEGER ivap          ! indice de traceurs pour vapeur d'eau
    438     PARAMETER (ivap=1)
    439     INTEGER iliq          ! indice de traceurs pour eau liquide
    440     PARAMETER (iliq=2)
    441     !CR: on ajoute la phase glace
    442     INTEGER isol          ! indice de traceurs pour eau glace
    443     PARAMETER (isol=3)
     446    ! indices de traceurs eau vapeur, liquide, glace, fraction nuageuse LS (optional)
     447    INTEGER,SAVE :: ivap, iliq, isol, irneb
     448!$OMP THREADPRIVATE(ivap, iliq, isol, irneb)
    444449    !
    445450    !
     
    616621                                                        ! gust-front in the grid cell.
    617622    !$OMP THREADPRIVATE(iflag_alp_wk_cond)
    618 
    619     INTEGER,  SAVE               :: iflag_bug_t2m_ipslcm61=1 !
    620     !$OMP THREADPRIVATE(iflag_bug_t2m_ipslcm61)
    621     INTEGER,  SAVE               :: iflag_bug_t2m_stab_ipslcm61=-1 !
    622     !$OMP THREADPRIVATE(iflag_bug_t2m_stab_ipslcm61)
    623623
    624624    REAL t_w(klon,klev),q_w(klon,klev) ! temperature and moisture profiles in the wake region
     
    856856    real zqsat(klon,klev)
    857857    !
    858     INTEGER i, k, iq, j, nsrf, ll, l
     858    INTEGER i, k, iq, j, nsrf, ll, l, itr
    859859    !
    860860    REAL t_coup
     
    963963    !IM cf. AM 081204 BEG
    964964    LOGICAL ptconvth(klon,klev)
     965
     966    REAL picefra(klon,klev)
    965967    !IM cf. AM 081204 END
    966968    !
     
    10341036!JLD    REAL zstophy, zout
    10351037
    1036     CHARACTER*20 modname
     1038    CHARACTER (LEN=20) :: modname='physiq_mod'
    10371039    CHARACTER*80 abort_message
    10381040    LOGICAL, SAVE ::  ok_sync, ok_sync_omp
     
    11861188    integer iostat
    11871189
     1190    REAL, dimension(klon,klev+1) :: tke_dissip_ave, l_mix_ave, wprime_ave
    11881191    REAL zzz
    11891192    !albedo SB >>>
     
    12001203    pi = 4. * ATAN(1.)
    12011204
     1205    ! set-up call to alerte function
     1206    call_alert = (alert_first_call .AND. is_master)
     1207   
    12021208    ! Ehouarn: set value of jjmp1 since it is no longer a "fixed parameter"
    12031209    jjmp1=nbp_lat
     
    12441250
    12451251    IF (first) THEN
     1252       ivap = strIdx(tracers(:)%name, addPhase('H2O', 'g'))
     1253       iliq = strIdx(tracers(:)%name, addPhase('H2O', 'l'))
     1254       isol = strIdx(tracers(:)%name, addPhase('H2O', 's'))
     1255       irneb= strIdx(tracers(:)%name, addPhase('H2O', 'r'))
    12461256       CALL init_etat0_limit_unstruct
    12471257       IF (.NOT. create_etat0_limit) CALL init_limit_read(days_elapsed)
     
    12611271            fact_cldcon, facttemps,ok_newmicro,iflag_radia, &
    12621272            iflag_cld_th,iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    1263             ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, aerosol_couple, &
    1264             chemistry_couple, &
    1265             flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
     1273            ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, flag_volc_surfstrat, aerosol_couple, &
     1274            chemistry_couple, flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    12661275            flag_bc_internal_mixture, bl95_b0, bl95_b1, &
    12671276                                ! nv flags pour la convection et les
     
    12781287#endif
    12791288
     1289       !!CALL flight_init
     1290
    12801291       print*, '================================================='
    12811292       !
     
    12831294       IF ((iflag_ice_thermo.gt.0).and.(nqo==2)) THEN
    12841295          WRITE (lunout, *) ' iflag_ice_thermo==1 requires 3 H2O tracers ', &
    1285                '(H2Ov, H2Ol, H2Oi) but nqo=', nqo, '. Might as well stop here.'
     1296               '(H2O_g, H2O_l, H2O_s) but nqo=', nqo, '. Might as well stop here.'
     1297          abort_message='see above'
     1298          CALL abort_physic(modname,abort_message,1)
     1299       ENDIF
     1300
     1301       IF (ok_ice_sursat.AND.(iflag_ice_thermo.EQ.0)) THEN
     1302          WRITE (lunout, *) ' ok_ice_sursat=y requires iflag_ice_thermo=1 as well'
     1303          abort_message='see above'
     1304          CALL abort_physic(modname,abort_message,1)
     1305       ENDIF
     1306
     1307       IF (ok_ice_sursat.AND.(nqo.NE.4)) THEN
     1308          WRITE (lunout, *) ' ok_ice_sursat=y requires 4 H2O tracers ', &
     1309               '(H2O_g, H2O_l, H2O_s, H2O_r) but nqo=', nqo, '. Might as well stop here.'
     1310          abort_message='see above'
     1311          CALL abort_physic(modname,abort_message,1)
     1312       ENDIF
     1313
     1314       IF (ok_plane_h2o.AND..NOT.ok_ice_sursat) THEN
     1315          WRITE (lunout, *) ' ok_plane_h2o=y requires ok_ice_sursat=y '
     1316          abort_message='see above'
     1317          CALL abort_physic(modname,abort_message,1)
     1318       ENDIF
     1319
     1320       IF (ok_plane_contrail.AND..NOT.ok_ice_sursat) THEN
     1321          WRITE (lunout, *) ' ok_plane_contrail=y requires ok_ice_sursat=y '
    12861322          abort_message='see above'
    12871323          CALL abort_physic(modname,abort_message,1)
     
    13171353    forall (k=1: nbp_lev) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg
    13181354
    1319     modname = 'physiq'
    13201355
    13211356    IF (debut) THEN
     
    13281363       tau_gl=86400.*tau_gl
    13291364       WRITE(lunout,*) 'debut physiq_mod tau_gl=',tau_gl
    1330 
    1331        iflag_bug_t2m_ipslcm61 = 1
    1332        CALL getin_p('iflag_bug_t2m_ipslcm61', iflag_bug_t2m_ipslcm61)
    1333        iflag_bug_t2m_stab_ipslcm61 = -1
    1334        CALL getin_p('iflag_bug_t2m_stab_ipslcm61', iflag_bug_t2m_stab_ipslcm61)
    13351365
    13361366       CALL getin_p('iflag_alp_wk_cond', iflag_alp_wk_cond)
     
    13661396         iflag_phytrac = 1
    13671397       ENDIF
    1368 #endif 
     1398#endif
    13691399       nvm_lmdz = 13
    13701400       CALL getin_p('NVM',nvm_lmdz)
     
    14241454       tau_overturning_th(:)=0.
    14251455
    1426        IF (type_trac == 'inca') THEN
     1456       IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
    14271457          ! jg : initialisation jusqu'au ces variables sont dans restart
    14281458          ccm(:,:,:) = 0.
     
    15351565       ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    15361566       CALL init_iophy_new(latitude_deg,longitude_deg)
    1537        CALL create_etat0_limit_unstruct
    1538        CALL phyetat0 ("startphy.nc",clesphy0,tabcntr0)
    15391567
    15401568          !===================================================================
     
    16991727!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    17001728       ! Nouvelle initialisation pour le rayonnement RRTM
    1701        !
    17021729!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    17031730
    17041731       CALL iniradia(klon,klev,paprs(1,1:klev+1))
    17051732
    1706        ! Initialisation des champs dans phytrac* qui sont utilisés par phys_output_write*
     1733!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1734       CALL wake_ini(rg,rd,rv,prt_level)
     1735       CALL thermcell_ini(iflag_thermals,prt_level,tau_thermals,lunout, &
     1736   &    RG,RD,RCPD,RKAPPA,RLVTT,RETV)
     1737
     1738!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1739
     1740       !
     1741!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1742       ! Initialisation des champs dans phytrac* qui sont utilises par phys_output_write*
     1743       !
     1744!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1745
    17071746#ifdef CPP_Dust
    17081747       ! Quand on utilise SPLA, on force iflag_phytrac=1
     
    17331772#endif
    17341773       IF(read_climoz>=1 .AND. create_etat0_limit) CALL regr_horiz_time_climoz(read_climoz,ok_daily_climoz)
     1774       CALL create_etat0_limit_unstruct
     1775       CALL phyetat0 ("startphy.nc",clesphy0,tabcntr0)
    17351776
    17361777!jyg<
     
    17471788            ENDDO
    17481789          ENDDO
    1749         ELSE
     1790       ELSE
    17501791          pbl_tke(:,:,is_ave) = 0. !ym missing init : maybe must be initialized in the same way that for klon_glo==1 ??
    17511792!>jyg
     
    17911832          CALL abort_physic(modname,abort_message,1)
    17921833       ENDIF
     1834
     1835!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1836       ! Initialisation pour la convection de K.E. et pour les poches froides
     1837       !
     1838!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1839
    17931840       WRITE(lunout,*)"Clef pour la convection, iflag_con=", iflag_con
    1794        WRITE(lunout,*)"Clef pour le driver de la convection, ok_cvl=", &
    1795             ok_cvl
     1841       WRITE(lunout,*)"Clef pour le driver de la convection, ok_cvl=", ok_cvl
    17961842       !
    17971843       !KE43
     
    18401886             d_s_wk(:) = 0.
    18411887             d_dens_wk(:) = 0.
    1842           ENDIF
     1888          ENDIF  !  (iflag_wake>=1)
    18431889
    18441890          !        do i = 1,klon
     
    18511897       !   ALLOCATE(lonGCM(0), latGCM(0))
    18521898       !   ALLOCATE(iGCM(0), jGCM(0))
    1853        ENDIF
    1854 
     1899       ENDIF  !  (iflag_con.GE.3)
     1900       !
    18551901       DO i=1,klon
    18561902          rugoro(i) = f_rugoro * MAX(1.0e-05, zstd(i)*zsig(i)/2.0)
     
    19211967       !$OMP BARRIER
    19221968       missing_val=missing_val_omp
     1969       !
     1970       ! Now we activate some double radiation call flags only if some
     1971       ! diagnostics are requested, otherwise there is no point in doing this
     1972       IF (is_master) THEN
     1973         !--setting up swaero_diag to TRUE in XIOS case
     1974         IF (xios_field_is_active("topswad").OR.xios_field_is_active("topswad0").OR. &
     1975            xios_field_is_active("solswad").OR.xios_field_is_active("solswad0").OR. &
     1976            xios_field_is_active("topswai").OR.xios_field_is_active("solswai").OR.  &
     1977              (iflag_rrtm==1.AND.(xios_field_is_active("toplwad").OR.xios_field_is_active("toplwad0").OR. &
     1978                                  xios_field_is_active("sollwad").OR.xios_field_is_active("sollwad0"))))  &
     1979            !!!--for now these fields are not in the XML files so they are omitted
     1980            !!!  xios_field_is_active("toplwai").OR.xios_field_is_active("sollwai") !))) &
     1981            swaero_diag=.TRUE.
     1982 
     1983         !--setting up swaerofree_diag to TRUE in XIOS case
     1984         IF (xios_field_is_active("SWdnSFCcleanclr").OR.xios_field_is_active("SWupSFCcleanclr").OR. &
     1985            xios_field_is_active("SWupTOAcleanclr").OR.xios_field_is_active("rsucsaf").OR.   &
     1986            xios_field_is_active("rsdcsaf") .OR. xios_field_is_active("LWdnSFCcleanclr").OR. &
     1987            xios_field_is_active("LWupTOAcleanclr")) &
     1988            swaerofree_diag=.TRUE.
     1989 
     1990         !--setting up dryaod_diag to TRUE in XIOS case
     1991         DO naero = 1, naero_tot-1
     1992          IF (xios_field_is_active("dryod550_"//name_aero_tau(naero))) dryaod_diag=.TRUE.
     1993         ENDDO
     1994         !
     1995         !--setting up ok_4xCO2atm to TRUE in XIOS case
     1996         IF (xios_field_is_active("rsut4co2").OR.xios_field_is_active("rlut4co2").OR. &
     1997            xios_field_is_active("rsutcs4co2").OR.xios_field_is_active("rlutcs4co2").OR. &
     1998            xios_field_is_active("rsu4co2").OR.xios_field_is_active("rsucs4co2").OR. &
     1999            xios_field_is_active("rsd4co2").OR.xios_field_is_active("rsdcs4co2").OR. &
     2000            xios_field_is_active("rlu4co2").OR.xios_field_is_active("rlucs4co2").OR. &
     2001            xios_field_is_active("rld4co2").OR.xios_field_is_active("rldcs4co2")) &
     2002            ok_4xCO2atm=.TRUE.
     2003       ENDIF
     2004       !$OMP BARRIER
     2005       CALL bcast(swaero_diag)
     2006       CALL bcast(swaerofree_diag)
     2007       CALL bcast(dryaod_diag)
     2008       CALL bcast(ok_4xCO2atm)
    19232009#endif
    1924 
    1925 
     2010       !
    19262011       CALL printflag( tabcntr0,radpas,ok_journe, &
    19272012            ok_instan, ok_region )
    19282013       !
    19292014       !
    1930        !
    19312015       ! Prescrire l'ozone dans l'atmosphere
    1932        !
    19332016       !
    19342017       !c         DO i = 1, klon
     
    19382021       !c         ENDDO
    19392022       !
    1940        IF (type_trac == 'inca') THEN
     2023       IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
    19412024#ifdef INCA
    19422025          CALL VTe(VTphysiq)
     
    19452028          WRITE(lunout,*) 'initial time chemini', days_elapsed, calday
    19462029
    1947           CALL chemini(  &
    1948                rg, &
    1949                ra, &
    1950                cell_area, &
     2030          call init_const_lmdz( &
     2031          ndays, nbsrf, is_oce,is_sic, is_ter,is_lic, calend, &
     2032          config_inca)
     2033
     2034          CALL init_inca_geometry( &
     2035               longitude, latitude, &
     2036               boundslon, boundslat, &
     2037               dx, dy, cell_area, ind_cell_glo)
     2038
     2039
     2040          CALL chemini(  pplay, &
     2041               nbp_lon, nbp_lat, &
    19512042               latitude_deg, &
    19522043               longitude_deg, &
     
    19552046               klon, &
    19562047               nqtot, &
    1957                nqo, &
     2048               nqo+nqCO2, &
    19582049               pdtphys, &
    19592050               annee_ref, &
     
    19862077#endif
    19872078       ENDIF
    1988        IF (type_trac == 'repr') THEN
     2079       !
     2080       IF (ANY(types_trac == 'repr')) THEN
    19892081#ifdef REPROBUS
    19902082          CALL chemini_rep(  &
     
    20342126          SFRWL(6)=3.02191470E-02
    20352127       END SELECT
    2036 
    2037 
    20382128       !albedo SB <<<
    20392129
     
    20742164
    20752165
     2166
    20762167    ENDIF
    20772168    !
     
    21002191
    21012192    ! Update time and other variables in Reprobus
    2102     IF (type_trac == 'repr') THEN
     2193    IF (ANY(types_trac == 'repr')) THEN
    21032194#ifdef REPROBUS
    21042195       CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     
    21582249      ! RomP <<<
    21592250    ENDIF
    2160 
    21612251    !
    21622252    ! Ne pas affecter les valeurs entrees de u, v, h, et q
     
    21702260          ql_seri(i,k) = qx(i,k,iliq)
    21712261          !CR: ATTENTION, on rajoute la variable glace
    2172           IF (nqo.eq.2) THEN
     2262          IF (nqo.EQ.2) THEN             !--vapour and liquid only
    21732263             qs_seri(i,k) = 0.
    2174           ELSE IF (nqo.eq.3) THEN
     2264             rneb_seri(i,k) = 0.
     2265          ELSE IF (nqo.EQ.3) THEN        !--vapour, liquid and ice
    21752266             qs_seri(i,k) = qx(i,k,isol)
     2267             rneb_seri(i,k) = 0.
     2268          ELSE IF (nqo.EQ.4) THEN        !--vapour, liquid, ice and rneb
     2269             qs_seri(i,k) = qx(i,k,isol)
     2270             rneb_seri(i,k) = qx(i,k,irneb)
    21762271          ENDIF
    21772272       ENDDO
     
    21892284
    21902285    tke0(:,:)=pbl_tke(:,:,is_ave)
    2191     !CR:Nombre de traceurs de l'eau: nqo
    2192     !  IF (nqtot.GE.3) THEN
    2193     IF (nqtot.GE.(nqo+1)) THEN
    2194        !     DO iq = 3, nqtot       
    2195        DO iq = nqo+1, nqtot 
     2286    IF (nqtot > nqo) THEN
     2287       ! water isotopes are not included in tr_seri
     2288       itr = 0
     2289       DO iq = 1, nqtot
     2290         IF(.NOT.tracers(iq)%isInPhysics) CYCLE
     2291         itr = itr+1
    21962292          DO  k = 1, klev
    21972293             DO  i = 1, klon
    2198                 !              tr_seri(i,k,iq-2) = qx(i,k,iq)
    2199                 tr_seri(i,k,iq-nqo) = qx(i,k,iq)
     2294                tr_seri(i,k,itr) = qx(i,k,iq)
    22002295             ENDDO
    22012296          ENDDO
    22022297       ENDDO
    22032298    ELSE
    2204        DO k = 1, klev
    2205           DO i = 1, klon
    2206              tr_seri(i,k,1) = 0.0
    2207           ENDDO
    2208        ENDDO
     2299! DC: make sure the final "1" index was meant for 1st H2O phase (vapor) !!!
     2300       tr_seri(:,:,strIdx(tracers(:)%name,addPhase('H2O','g'))) = 0.0
    22092301    ENDIF
    22102302!
     
    22132305    IF (debut) THEN
    22142306      WRITE(lunout,*)' WARNING: tr_ancien initialised to tr_seri'
    2215       DO iq = nqo+1, nqtot
    2216            tr_ancien(:,:,iq-nqo)=tr_seri(:,:,iq-nqo)
    2217       ENDDO
     2307       itr = 0
     2308       do iq = 1, nqtot
     2309         IF(.NOT.tracers(iq)%isInPhysics) CYCLE
     2310         itr = itr+1
     2311         tr_ancien(:,:,itr)=tr_seri(:,:,itr)       
     2312       enddo
    22182313    ENDIF
    22192314    !
     
    22462341       d_qs_dyn2d(:)=(zx_tmp_fi2d(:)-prsw_ancien(:))/phys_tstep
    22472342       ! !! RomP >>>   td dyn traceur
    2248        IF (nqtot.GT.nqo) THEN     ! jyg
    2249           DO iq = nqo+1, nqtot      ! jyg
    2250               d_tr_dyn(:,:,iq-nqo)=(tr_seri(:,:,iq-nqo)-tr_ancien(:,:,iq-nqo))/phys_tstep ! jyg
    2251           ENDDO
    2252        ENDIF
     2343       IF (nqtot > nqo) d_tr_dyn(:,:,:)=(tr_seri(:,:,:)-tr_ancien(:,:,:))/phys_tstep
    22532344       ! !! RomP <<<
     2345       !!d_rneb_dyn(:,:)=(rneb_seri(:,:)-rneb_ancien(:,:))/phys_tstep
     2346       d_rneb_dyn(:,:)=0.0
    22542347    ELSE
    22552348       d_u_dyn(:,:)  = 0.0
     
    22632356       d_qs_dyn2d(:) = 0.0
    22642357       ! !! RomP >>>   td dyn traceur
    2265        IF (nqtot.GT.nqo) THEN                                       ! jyg
    2266           DO iq = nqo+1, nqtot                                      ! jyg
    2267               d_tr_dyn(:,:,iq-nqo)= 0.0                             ! jyg
    2268           ENDDO
    2269        ENDIF
     2358       IF (nqtot > nqo) d_tr_dyn(:,:,:)= 0.0
    22702359       ! !! RomP <<<
     2360       d_rneb_dyn(:,:)=0.0
    22712361       ancien_ok = .TRUE.
    22722362    ENDIF
     
    24972587    !   s_therm,   s_trmb1,   s_trmb2, s_trmb3,
    24982588    !   zu10m,     zv10m,   fder,
    2499     !   zxqsurf,   rh2m,      zxfluxu, zxfluxv,
     2589    !   zxqsurf,   delta_qsurf,
     2590    !   rh2m,      zxfluxu, zxfluxv,
    25002591    !   frugs,     agesno,    fsollw,  fsolsw,
    25012592    !   d_ts,      fevap,     fluxlat, t2m,
     
    25472638            debut,     lafin, &
    25482639            longitude_deg, latitude_deg, rugoro,  zrmu0,      &
    2549             zsig,      sollwdown, pphi,    cldt,      &
     2640            sollwdown,    cldt,      &
    25502641            rain_fall, snow_fall, solsw,   solswfdiff, sollw,     &
    25512642            gustiness,                                &
     
    25582649                                !albedo SB <<<
    25592650            cdragh,    cdragm,  u1,    v1,            &
     2651            beta_aridity, &
    25602652                                !albedo SB >>>
    25612653                                ! albsol1,   albsol2,   sens,    evap,      &
     
    25632655                                !albedo SB <<<
    25642656            albsol3_lic,runoff,   snowhgt,   qsnow, to_ice, sissnow, &
    2565             zxtsol,    zxfluxlat, zt2m,    qsat2m,  &
     2657            zxtsol,    zxfluxlat, zt2m,    qsat2m,  zn2mout, &
    25662658            d_t_vdf,   d_q_vdf,   d_u_vdf, d_v_vdf, d_t_diss, &
    25672659                                !nrlmd<
     
    25842676            s_therm,   s_trmb1,   s_trmb2, s_trmb3, &
    25852677            zustar, zu10m,     zv10m,   fder, &
    2586             zxqsurf,   rh2m,      zxfluxu, zxfluxv, &
     2678            zxqsurf, delta_qsurf,   rh2m,      zxfluxu, zxfluxv, &
    25872679            z0m, z0h,     agesno,    fsollw,  fsolsw, &
    25882680            d_ts,      fevap,     fluxlat, t2m, &
     
    26102702!>jyg
    26112703       ENDIF
    2612 
    2613 !add limitation for t,q at and wind at 10m
    2614         if ( iflag_bug_t2m_ipslcm61 == 0 ) THEN
    2615           CALL borne_var_surf( klon,klev,nbsrf,                 &
    2616             iflag_bug_t2m_stab_ipslcm61,                        &
    2617             t_seri(:,1),q_seri(:,1),u_seri(:,1),v_seri(:,1),    &
    2618             ftsol,zxqsurf,pctsrf,paprs,                         &
    2619             t2m, q2m, u10m, v10m,                               &
    2620             zt2m_cor, zq2m_cor, zu10m_cor, zv10m_cor,           &
    2621             zrh2m_cor, zqsat2m_cor)
    2622         ELSE
    2623           zt2m_cor(:)=zt2m(:)
    2624           zq2m_cor(:)=zq2m(:)
    2625           zu10m_cor(:)=zu10m(:)
    2626           zv10m_cor(:)=zv10m(:)
    2627           zqsat2m_cor=999.999
    2628         ENDIF
    26292704
    26302705       !---------------------------------------------------------------------
     
    28312906         ENDDO
    28322907       ELSE
    2833                t_w(:,:) = t_seri(:,:)
     2908                t_w(:,:) = t_seri(:,:)
    28342909                q_w(:,:) = q_seri(:,:)
    28352910                t_x(:,:) = t_seri(:,:)
     
    29072982          !
    29082983          !>jyg
    2909           IF (type_trac == 'repr') THEN
     2984          IF (ANY(types_trac == 'repr')) THEN
    29102985             nbtr_tmp=ntra
    29112986          ELSE
     
    30473122
    30483123       DO i = 1, klon
    3049           ema_pcb(i)  = paprs(i,ibas_con(i))
     3124          ! C Risi modif: pour éviter pb de dépassement d'indice dans les cas
     3125          ! où i n'est pas un point convectif et donc ibas_con(i)=0
     3126          ! c'est un pb indépendant des isotopes
     3127          if (ibas_con(i) > 0) then
     3128             ema_pcb(i)  = paprs(i,ibas_con(i))
     3129          else
     3130             ema_pcb(i)  = 0.0
     3131          endif
    30503132       ENDDO
    30513133       DO i = 1, klon
     
    34733555    ! Computation of ratqs, the width (normalized) of the subrid scale
    34743556    ! water distribution
     3557
     3558    tke_dissip_ave(:,:)=0.
     3559    l_mix_ave(:,:)=0.
     3560    wprime_ave(:,:)=0.
     3561
     3562    DO nsrf = 1, nbsrf
     3563       DO i = 1, klon
     3564          tke_dissip_ave(i,:) = tke_dissip_ave(i,:) + tke_dissip(i,:,nsrf)*pctsrf(i,nsrf)
     3565          l_mix_ave(i,:) = l_mix_ave(i,:) + l_mix(i,:,nsrf)*pctsrf(i,nsrf)
     3566          wprime_ave(i,:) = wprime_ave(i,:) + wprime(i,:,nsrf)*pctsrf(i,nsrf)
     3567       ENDDO
     3568    ENDDO
     3569
    34753570    CALL  calcratqs(klon,klev,prt_level,lunout,        &
    34763571         iflag_ratqs,iflag_con,iflag_cld_th,pdtphys,  &
    34773572         ratqsbas,ratqshaut,ratqsp0, ratqsdp, &
    3478          tau_ratqs,fact_cldcon,   &
     3573         tau_ratqs,fact_cldcon,wake_s, wake_deltaq,   &
    34793574         ptconv,ptconvth,clwcon0th, rnebcon0th,     &
    3480          paprs,pplay,q_seri,zqsat,fm_therm, &
    3481          ratqs,ratqsc)
    3482 
     3575         paprs,pplay,t_seri,q_seri, qtc_cv, sigt_cv, zqsat, &
     3576         pbl_tke(:,:,is_ave),tke_dissip_ave,l_mix_ave,wprime_ave,t2m,q2m,fm_therm, &
     3577         ratqs,ratqsc,ratqs_inter)
    34833578
    34843579    !
     
    34903585    ENDIF
    34913586    !
     3587
     3588    picefra(:,:)=0.
     3589
     3590    IF (ok_new_lscp) THEN
     3591
     3592    !--mise à jour de flight_m et flight_h2o dans leur module
     3593    IF (ok_plane_h2o .OR. ok_plane_contrail) THEN
     3594      CALL airplane(debut,pphis,pplay,paprs,t_seri)
     3595    ENDIF
     3596
     3597    CALL lscp(phys_tstep,missing_val,paprs,pplay, &
     3598         t_seri, q_seri,ptconv,ratqs, &
     3599         d_t_lsc, d_q_lsc, d_ql_lsc, d_qi_lsc, rneb, rneb_seri, &
     3600         cldliq, picefra, rain_lsc, snow_lsc, &
     3601         pfrac_impa, pfrac_nucl, pfrac_1nucl, &
     3602         frac_impa, frac_nucl, beta_prec_fisrt, &
     3603         prfl, psfl, rhcl,  &
     3604         zqasc, fraca,ztv,zpspsk,ztla,zthl,iflag_cld_th, &
     3605         iflag_ice_thermo, ok_ice_sursat)
     3606
     3607    ELSE
     3608
    34923609    CALL fisrtilp(phys_tstep,paprs,pplay, &
    34933610         t_seri, q_seri,ptconv,ratqs, &
     
    34993616         zqasc, fraca,ztv,zpspsk,ztla,zthl,iflag_cld_th, &
    35003617         iflag_ice_thermo)
     3618
     3619    ENDIF
    35013620    !
    35023621    WHERE (rain_lsc < 0) rain_lsc = 0.
     
    35213640       ENDDO
    35223641    ENDDO
    3523     IF (nqo==3) THEN
     3642    IF (nqo >= 3) THEN
    35243643    DO k = 1, klev
    35253644       DO i = 1, klon
     
    37683887    ENDDO
    37693888
    3770     IF (type_trac == 'inca') THEN
     3889    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
    37713890#ifdef INCA
    37723891       CALL VTe(VTphysiq)
     
    38113930            nbp_lon, &
    38123931            nbp_lat-1, &
    3813             tr_seri, &
     3932            tr_seri(:,:,1+nqCO2:nbtr), &
    38143933            ftsol, &
    38153934            paprs, &
     
    38223941       CALL VTe(VTinca)
    38233942       CALL VTb(VTphysiq)
    3824 #endif 
    3825     ENDIF !type_trac = inca
    3826     IF (type_trac == 'repr') THEN
     3943#endif
     3944    ENDIF !type_trac = inca or inco
     3945    IF (ANY(types_trac == 'repr')) THEN
    38273946#ifdef REPROBUS
    38283947    !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap)
     
    39944113
    39954114       IF (ok_newmicro) then
    3996 !          IF (iflag_rrtm.NE.0) THEN
     4115! AI          IF (iflag_rrtm.NE.0) THEN
    39974116          IF (iflag_rrtm.EQ.1) THEN
    39984117#ifdef CPP_RRTM
     
    40094128          ENDIF
    40104129          CALL newmicro (flag_aerosol, ok_cdnc, bl95_b0, bl95_b1, &
    4011                paprs, pplay, t_seri, cldliq, cldfra, &
     4130               paprs, pplay, t_seri, cldliq, picefra, cldfra, &
    40124131               cldtau, cldemi, cldh, cldl, cldm, cldt, cldq, &
    40134132               flwp, fiwp, flwc, fiwc, &
    40144133               mass_solu_aero, mass_solu_aero_pi, &
    4015                cldtaupi, re, fl, ref_liq, ref_ice, &
     4134               cldtaupi, latitude_deg, re, fl, ref_liq, ref_ice, &
    40164135               ref_liq_pi, ref_ice_pi)
    40174136       ELSE
    40184137          CALL nuage (paprs, pplay, &
    4019                t_seri, cldliq, cldfra, cldtau, cldemi, &
     4138               t_seri, cldliq, picefra, cldfra, cldtau, cldemi, &
    40204139               cldh, cldl, cldm, cldt, cldq, &
    40214140               ok_aie, &
     
    41694288               t_seri,q_seri,wo, &
    41704289               cldfrarad, cldemirad, cldtaurad, &
    4171                ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie,  ok_volcan, &
    4172                flag_aerosol, &
    4173                flag_aerosol_strat, flag_aer_feedback, &
     4290               ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie,  ok_volcan, flag_volc_surfstrat, &
     4291               flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    41744292               tau_aero, piz_aero, cg_aero, &
    41754293               tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, &
     
    42564374                     t_seri,q_seri,wo, &
    42574375                     cldfrarad, cldemirad, cldtaurad, &
    4258                      ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie,  ok_volcan, &
    4259                      flag_aerosol, &
    4260                      flag_aerosol_strat, flag_aer_feedback, &
     4376                     ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie,  ok_volcan, flag_volc_surfstrat, &
     4377                     flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    42614378                     tau_aero, piz_aero, cg_aero, &
    42624379                     tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, &
     
    42874404                     ZLWFT0_i, ZFLDN0, ZFLUP0, &
    42884405                     ZSWFT0_i, ZFSDN0, ZFSUP0)
    4289           endif !ok_4xCO2atm
     4406          ENDIF !ok_4xCO2atm
    42904407       ENDIF ! aerosol_couple
    42914408       itaprad = 0
     
    46684785
    46694786    CALL tend_to_tke(pdtphys,paprs,exner,t_seri,u_seri,v_seri,dtadd,duadd,dvadd,pctsrf,pbl_tke)
    4670 
     4787   !
     4788   ! Prevent pbl_tke_w from becoming negative
     4789    wake_delta_pbl_tke(:,:,:) = max(wake_delta_pbl_tke(:,:,:), -pbl_tke(:,:,:))
     4790   !
    46714791
    46724792       ENDIF
     
    48004920    !
    48014921
    4802     IF (type_trac=='repr') THEN
     4922    IF (ANY(types_trac=='repr')) THEN
    48034923!MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod
    48044924!MM                               dans Reprobus
     
    48114931    ELSE
    48124932       sh_in(:,:) = qx(:,:,ivap)
    4813        ch_in(:,:) = qx(:,:,iliq)
     4933       IF (nqo >= 3) THEN
     4934          ch_in(:,:) = qx(:,:,iliq) + qx(:,:,isol)
     4935       ELSE
     4936          ch_in(:,:) = qx(:,:,iliq)
     4937       ENDIF
    48144938    ENDIF
    48154939
     
    49505074    ENDDO
    49515075    !
    4952     IF (type_trac == 'inca') THEN
     5076    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
    49535077#ifdef INCA
    49545078       CALL VTe(VTphysiq)
     
    49595083            pplay, &
    49605084            t_seri, &
    4961             tr_seri, &
     5085            tr_seri(:,:,1+nqCO2:nbtr), &
    49625086            nbtr, &
    49635087            paprs, &
     
    49675091            pphis, &
    49685092            zx_rh, &
    4969             aps, bps, ap, bp)
     5093            aps, bps, ap, bp, lafin)
    49705094
    49715095       CALL VTe(VTinca)
     
    49745098    ENDIF
    49755099
     5100    IF (ANY(types_trac == 'repr')) THEN
     5101#ifdef REPROBUS
     5102        CALL coord_hyb_rep(paprs, pplay, aps, bps, ap, bp, cell_area)
     5103#endif
     5104    ENDIF
    49765105
    49775106    !
     
    49975126          d_qx(i,k,iliq) = ( ql_seri(i,k) - qx(i,k,iliq) ) / phys_tstep
    49985127          !CR: on ajoute le contenu en glace
    4999           IF (nqo.eq.3) THEN
     5128          IF (nqo >= 3) THEN
    50005129             d_qx(i,k,isol) = ( qs_seri(i,k) - qx(i,k,isol) ) / phys_tstep
     5130          ENDIF
     5131          !--ice_sursat: nqo=4, on ajoute rneb
     5132          IF (nqo == 4) THEN
     5133             d_qx(i,k,irneb) = ( rneb_seri(i,k) - qx(i,k,irneb) ) / phys_tstep
    50015134          ENDIF
    50025135       ENDDO
    50035136    ENDDO
    50045137    !
    5005     !CR: nb de traceurs eau: nqo
    5006     !  IF (nqtot.GE.3) THEN
    5007     IF (nqtot.GE.(nqo+1)) THEN
    5008        !     DO iq = 3, nqtot
    5009        DO iq = nqo+1, nqtot
     5138    IF (nqtot > nqo) THEN
     5139       itr = 0
     5140       DO iq = 1, nqtot
     5141          IF(.NOT.tracers(iq)%isInPhysics) CYCLE
     5142          itr = itr+1
    50105143          DO  k = 1, klev
    50115144             DO  i = 1, klon
    5012                 ! d_qx(i,k,iq) = ( tr_seri(i,k,iq-2) - qx(i,k,iq) ) / phys_tstep
    5013                 d_qx(i,k,iq) = ( tr_seri(i,k,iq-nqo) - qx(i,k,iq) ) / phys_tstep
     5145                d_qx(i,k,iq) = ( tr_seri(i,k,itr) - qx(i,k,iq) ) / phys_tstep
    50145146             ENDDO
    50155147          ENDDO
     
    50485180    ql_ancien(:,:) = ql_seri(:,:)
    50495181    qs_ancien(:,:) = qs_seri(:,:)
     5182    rneb_ancien(:,:) = rneb_seri(:,:)
    50505183    CALL water_int(klon,klev,q_ancien,zmasse,prw_ancien)
    50515184    CALL water_int(klon,klev,ql_ancien,zmasse,prlw_ancien)
    50525185    CALL water_int(klon,klev,qs_ancien,zmasse,prsw_ancien)
    50535186    ! !! RomP >>>
    5054     !CR: nb de traceurs eau: nqo
    5055     IF (nqtot.GT.nqo) THEN
    5056        DO iq = nqo+1, nqtot
    5057           tr_ancien(:,:,iq-nqo) = tr_seri(:,:,iq-nqo)
    5058        ENDDO
    5059     ENDIF
     5187    IF (nqtot > nqo) tr_ancien(:,:,:) = tr_seri(:,:,:)
    50605188    ! !! RomP <<<
    50615189    !==========================================================================
     
    51925320#endif
    51935321
    5194 ! Pour XIOS : On remet des variables a .false. apres un premier appel
    5195     IF (debut) THEN
    5196 #ifdef CPP_XIOS
    5197       swaero_diag=.FALSE.
    5198       swaerofree_diag=.FALSE.
    5199       dryaod_diag=.FALSE.
    5200       ok_4xCO2atm= .FALSE.
    5201 !      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    5202 
    5203       IF (is_master) THEN
    5204         !--setting up swaero_diag to TRUE in XIOS case
    5205         IF (xios_field_is_active("topswad").OR.xios_field_is_active("topswad0").OR. &
    5206            xios_field_is_active("solswad").OR.xios_field_is_active("solswad0").OR. &
    5207            xios_field_is_active("topswai").OR.xios_field_is_active("solswai").OR.  &
    5208              (iflag_rrtm==1.AND.(xios_field_is_active("toplwad").OR.xios_field_is_active("toplwad0").OR. &
    5209                                  xios_field_is_active("sollwad").OR.xios_field_is_active("sollwad0"))))  &
    5210            !!!--for now these fields are not in the XML files so they are omitted
    5211            !!!  xios_field_is_active("toplwai").OR.xios_field_is_active("sollwai") !))) &
    5212            swaero_diag=.TRUE.
    5213 
    5214         !--setting up swaerofree_diag to TRUE in XIOS case
    5215         IF (xios_field_is_active("SWdnSFCcleanclr").OR.xios_field_is_active("SWupSFCcleanclr").OR. &
    5216            xios_field_is_active("SWupTOAcleanclr").OR.xios_field_is_active("rsucsaf").OR.   &
    5217            xios_field_is_active("rsdcsaf") .OR. xios_field_is_active("LWdnSFCcleanclr").OR. &
    5218            xios_field_is_active("LWupTOAcleanclr")) &
    5219            swaerofree_diag=.TRUE.
    5220 
    5221         !--setting up dryaod_diag to TRUE in XIOS case
    5222         DO naero = 1, naero_tot-1
    5223          IF (xios_field_is_active("dryod550_"//name_aero_tau(naero))) dryaod_diag=.TRUE.
    5224         ENDDO
    5225         !
    5226         !--setting up ok_4xCO2atm to TRUE in XIOS case
    5227         IF (xios_field_is_active("rsut4co2").OR.xios_field_is_active("rlut4co2").OR. &
    5228            xios_field_is_active("rsutcs4co2").OR.xios_field_is_active("rlutcs4co2").OR. &
    5229            xios_field_is_active("rsu4co2").OR.xios_field_is_active("rsucs4co2").OR. &
    5230            xios_field_is_active("rsd4co2").OR.xios_field_is_active("rsdcs4co2").OR. &
    5231            xios_field_is_active("rlu4co2").OR.xios_field_is_active("rlucs4co2").OR. &
    5232            xios_field_is_active("rld4co2").OR.xios_field_is_active("rldcs4co2")) &
    5233            ok_4xCO2atm=.TRUE.
    5234       ENDIF
    5235       !$OMP BARRIER
    5236       CALL bcast(swaero_diag)
    5237       CALL bcast(swaerofree_diag)
    5238       CALL bcast(dryaod_diag)
    5239       CALL bcast(ok_4xCO2atm)
    5240 !      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    5241 #endif
    5242     ENDIF
    5243 
    52445322    !====================================================================
    52455323    ! Arret du modele apres hgardfou en cas de detection d'un
     
    52595337    !
    52605338
     5339    ! Disabling calls to the prt_alerte function
     5340    alert_first_call = .FALSE.
     5341   
    52615342    IF (lafin) THEN
    52625343       itau_phy = itau_phy + itap
     
    52775358#ifdef CPP_XIOS
    52785359       IF (is_omp_master) CALL xios_context_finalize
     5360
     5361#ifdef INCA
     5362       if (ANY(types_trac == 'inca' )) then
     5363          IF (is_omp_master .and. grid_type==unstructured) THEN
     5364             CALL finalize_inca
     5365          ENDIF
     5366       endif
     5367#endif
     5368
    52795369#endif
    52805370       WRITE(lunout,*) ' physiq fin, nombre de steps ou cvpas = 1 : ', Ncvpaseq1
Note: See TracChangeset for help on using the changeset viewer.