Changeset 3870


Ignore:
Timestamp:
Apr 8, 2021, 10:58:58 PM (3 years ago)
Author:
Laurent Fairhead
Message:

Corrections to r3865 that will hopefully repair the debug compilation
TL

Location:
LMDZ6/trunk/libf
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r3869 r3870  
    1515  INTEGER, SAVE :: nqperes
    1616
    17 ! ThL: nb traceurs spécifiques à INCA
     17! ThL: nb traceurs INCA
    1818  INTEGER, SAVE :: nqINCA
     19
     20! ThL: nb traceurs CO2
     21  INTEGER, SAVE :: nqCO2
    1922
    2023! Name variables
     
    4548  CHARACTER(len=4),SAVE :: type_trac
    4649  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
    47    
     50
    4851! CRisi: cas particulier des isotopes
    4952  LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
     
    107110    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca  ! index of vertical trasport schema
    108111
     112    INTEGER, ALLOCATABLE, DIMENSION(:) :: conv_flg_inca
     113    INTEGER, ALLOCATABLE, DIMENSION(:) :: pbl_flg_inca
     114    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca
     115
    109116    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    110117    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
     
    123130    character(len=*),parameter :: modname="infotrac_init"
    124131
    125     INTEGER :: nqexcl ! ThL. Nb de traceurs dans traceur.def. Egal à nqtrue,
    126                       ! sauf pour 'inca' = nqtrue-nbtr, et 'inco' = 4.
    127132!-----------------------------------------------------------------------
    128133! Initialization :
     
    199204!-----------------------------------------------------------------------
    200205    IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag' .OR. type_trac == 'co2i') THEN
     206       IF (type_trac=='co2i') THEN              ! ModThL
     207          nqCO2 = 1
     208       ELSE
     209          nqCO2 = 0
     210       ENDIF
    201211       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    202212       IF(ierr.EQ.0) THEN
     
    213223          ENDIF
    214224       ENDIF
    215        nqexcl=nqtrue
    216225!jyg<
    217226!!       if ( planet_type=='earth') then
     
    224233!!       endif
    225234!>jyg
    226     ELSE ! type_trac=inca (or inco ThL)
     235    ELSE ! type_trac=inca or inco
     236       IF (type_trac=='inco') THEN              ! ModThL
     237          nqCO2 = 1
     238       ELSE
     239          nqCO2 = 0
     240       ENDIF
    227241!jyg<
    228242       ! The traceur.def file is used to define the number "nqo" of water phases
     
    248262       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
    249263#ifdef INCA
    250        CALL Init_chem_inca_trac(nbtr)
    251 #endif       
    252        IF (type_trac=='inco') THEN          ! Add ThL
    253           nqexcl = nqo+1                    ! Tracers excluding INCA's = water + CO2 in 'inco' case
    254        ELSE
    255           nqexcl = nqo                      ! Tracers excluding INCA's = water
    256        ENDIF
    257        nqtrue = nbtr + nqexcl               ! Total nb of tracers = INCA's + traceur.def
    258        IF (type_trac=='inco') THEN          !
    259           nqINCA = nbtr                     ! nbtr = other tracers than H2O = INCA's + CO2i
    260           nbtr = nqINCA + 1                 !
    261        ELSEIF (type_trac=='inca') THEN      !
    262           nqINCA = nbtr                     !
    263        ELSE                                 !
    264           nqINCA = 0                        !
    265        ENDIF                                !
     264       CALL Init_chem_inca_trac(nqINCA)
     265#else
     266       nqINCA=0
     267#endif
     268       nbtr=nqINCA+nqCO2
     269
    266270       WRITE(lunout,*) trim(modname),': nqo = ',nqo
    267271       WRITE(lunout,*) trim(modname),': nbtr = ',nbtr
    268        WRITE(lunout,*) trim(modname),': nqexcl = ',nqexcl
    269272       WRITE(lunout,*) trim(modname),': nqtrue = ',nqtrue
    270        WRITE(lunout,*) trim(modname),': nqINCA = ',nqINCA
    271        ALLOCATE(hadv_inca(nqINCA), vadv_inca(nqINCA)) ! ThL
    272     ENDIF   ! type_trac
     273       WRITE(lunout,*) trim(modname),': nqCO2 = ',nqCO2
     274       ALLOCATE(hadv_inca(nqINCA), vadv_inca(nqINCA), conv_flg_inca(nqINCA), pbl_flg_inca(nqINCA), solsym_inca(nqINCA))         ! Mod ThL
     275    ENDIF   ! type_trac 'inca' ou 'inco'
    273276!>jyg
    274277
     
    401404       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
    402405       WRITE(lunout,*) trim(modname),': nombre total de traceurs ',nqtrue
    403        WRITE(lunout,*) trim(modname),': nombre de traceurs dans traceur.def ',nqexcl
    404406       DO iq=1,nqtrue
    405407          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq),tnom_transp(iq)
     
    477479!!    ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
    478480!
    479     IF (type_trac == 'inca') THEN   ! config_inca='aero' ou 'chem'
     481    IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN   ! config_inca='aero' ou 'chem'
    480482!>jyg
    481483! le module de chimie fournit les noms des traceurs
     
    541543            hadv_inca, &
    542544            vadv_inca, &
    543             conv_flg, &
    544             pbl_flg,  &
    545             solsym)
     545            conv_flg_inca, &                            ! ModThL
     546            pbl_flg_inca,  &                            ! ModThL
     547            solsym_inca)                                ! ModThL
     548       conv_flg(1+nqCO2:nbtr) = conv_flg_inca           ! ModThL
     549       pbl_flg(1+nqCO2:nbtr) = pbl_flg_inca             ! ModThL
     550       solsym(1+nqCO2:nbtr) = solsym_inca               ! ModThL
     551       IF (type_trac == 'inco') THEN            ! ModThL
     552          conv_flg(1:nqCO2) = 1                 ! ModThL
     553          pbl_flg(1:nqCO2) = 1                  ! ModThL
     554          solsym(1:nqCO2) = 'CO2'               ! ModThL
     555       ENDIF                                    ! ModThL
     556
    546557#endif
    547558
    548 
    549559!jyg<
    550        DO iq = nqo+1, nqtrue
    551           hadv(iq) = hadv_inca(iq-nqo)
    552           vadv(iq) = vadv_inca(iq-nqo)
    553           tnom_0(iq)=solsym(iq-nqo)
     560       DO iq = nqo+nqCO2+1, nqtrue      ! ModThL
     561          hadv(iq) = hadv_inca(iq-nqo-nqCO2)            ! ModThL
     562          vadv(iq) = vadv_inca(iq-nqo-nqCO2)            ! ModThL
     563          tnom_0(iq)=solsym(iq-nqo-nqCO2)               ! ModThL
    554564          tnom_transp(iq) = 'air'
    555565       END DO
    556566
    557     END IF ! (type_trac == 'inca')
    558 
    559     !< add ThL case 'inco'
    560     IF (type_trac == 'inco') THEN
    561  ! le module de chimie fournit les noms des traceurs
    562  ! et les schemas d'advection associes. excepte pour ceux lus
    563  ! dans traceur.def
    564        IF (ierr .eq. 0) then
    565           DO iq=1,nqexcl
    566              write(*,*) 'infotrac 237: iq=',iq
    567              ! CRisi: ajout du nom du fluide transporteur
    568              ! mais rester retro compatible
    569              READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
    570              write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
    571              write(lunout,*) 'tchaine=',trim(tchaine)
    572              write(*,*) 'infotrac 238: IOstatus=',IOstatus
    573              if (IOstatus.ne.0) then
    574                 CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
    575              endif
    576              ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
    577              ! espace ou pas au milieu de la chaine.
    578              continu=.true.
    579              nouveau_traceurdef=.false.
    580              iiq=1
    581              do while (continu)
    582                 if (tchaine(iiq:iiq).eq.' ') then
    583                   nouveau_traceurdef=.true.
    584                   continu=.false.
    585                 else if (iiq.lt.LEN_TRIM(tchaine)) then
    586                   iiq=iiq+1
    587                 else
    588                   continu=.false.
    589                 endif
    590              enddo
    591              write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
    592              if (nouveau_traceurdef) then
    593                 write(lunout,*) 'C''est la nouvelle version de traceur.def'
    594                 tnom_0(iq)=tchaine(1:iiq-1)
    595                 tnom_transp(iq)=tchaine(iiq+1:15)
    596              else
    597                 write(lunout,*) 'C''est l''ancienne version de traceur.def'
    598                 write(lunout,*) 'On suppose que les traceurs sont tous d''air'
    599                 tnom_0(iq)=tchaine
    600                 tnom_transp(iq) = 'air'
    601              endif
    602              write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
    603              write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
    604           END DO !DO iq=1,nqexcl
    605           CLOSE(90) 
    606        ELSE  !! if traceur.def doesn't exist
    607           tnom_0(1)='H2Ov'
    608           tnom_transp(1) = 'air'
    609           tnom_0(2)='H2Ol'
    610           tnom_transp(2) = 'air'
    611           hadv(1) = 10
    612           hadv(2) = 10
    613           vadv(1) = 10
    614           vadv(2) = 10
    615        ENDIF
    616 
    617 #ifdef INCA
    618        CALL init_transport( &
    619             hadv_inca, &
    620             vadv_inca, &
    621             conv_flg, &
    622             pbl_flg,  &
    623             solsym)
    624 #endif
    625 
    626        DO iq = nqexcl+1, nqtrue
    627           hadv(iq) = hadv_inca(iq-nqexcl)     ! mod. Thl : nqexcl was nqo (in order to shift)
    628           vadv(iq) = vadv_inca(iq-nqexcl)     ! idem
    629           tnom_0(iq)=solsym(iq-nqexcl)        ! idem
    630           tnom_transp(iq) = 'air'
    631        END DO
    632 
    633     END IF ! (type_trac == 'inco')
    634 !> add ThL case 'inco'
     567    END IF ! (type_trac == 'inca' or 'inco')
    635568
    636569!-----------------------------------------------------------------------
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r3865 r3870  
    1616  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
    1717  USE vertical_layers_mod, ONLY : init_vertical_layers
    18   USE infotrac, ONLY: nqtot,nqo,nbtr,nqINCA,tname,ttext,type_trac,&
     18  USE infotrac, ONLY: nqtot,nqo,nbtr,nqCO2,tname,ttext,type_trac,&
    1919                      niadv,conv_flg,pbl_flg,solsym,&
    2020                      nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,&
     
    146146
    147147  ! Initialize tracer names, numbers, etc. for physics
    148   CALL init_infotrac_phy(nqtot,nqo,nbtr,nqINCA,tname,ttext,type_trac,&
     148  CALL init_infotrac_phy(nqtot,nqo,nbtr,nqCO2,tname,ttext,type_trac,&
    149149                         niadv,conv_flg,pbl_flg,solsym,&
    150150                         nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,&
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r3865 r3870  
    2121!$OMP THREADPRIVATE(nbtr)
    2222
    23 ! ThL : number of tracers specific to INCA
    24   INTEGER, SAVE :: nqINCA
    25 !$OMP THREADPRIVATE(nqINCA)
     23! ThL : number of CO2 tracers                   ModThL
     24  INTEGER, SAVE :: nqCO2
     25!$OMP THREADPRIVATE(nqCO2)
    2626
    2727#ifdef CPP_StratAer
     
    3737  INTEGER, SAVE :: nqperes
    3838!$OMP THREADPRIVATE(nqperes)
    39 
    40 ! ThL : nb de traceurs dans le traceur.def
    41   INTEGER, SAVE :: nqexcl
    42 !$OMP THREADPRIVATE(nqexcl)
    4339
    4440! Name variables
     
    104100CONTAINS
    105101
    106   SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqINCA_,tname_,ttext_,type_trac_,&
     102  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqCO2_,tname_,ttext_,type_trac_,&
    107103                               niadv_,conv_flg_,pbl_flg_,solsym_,&
    108104                               nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
     
    126122    INTEGER,INTENT(IN) :: nqo_
    127123    INTEGER,INTENT(IN) :: nbtr_
    128     INTEGER,INTENT(IN) :: nqINCA_
     124    INTEGER,INTENT(IN) :: nqCO2_
    129125#ifdef CPP_StratAer
    130126    INTEGER,INTENT(IN) :: nbtr_bin_
     
    139135    CHARACTER(len=4),INTENT(IN) :: type_trac_
    140136    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
    141     INTEGER,INTENT(IN) :: conv_flg_(nqINCA_)
    142     INTEGER,INTENT(IN) :: pbl_flg_(nqINCA_)
    143     CHARACTER(len=8),INTENT(IN) :: solsym_(nqINCA_)
     137    INTEGER,INTENT(IN) :: conv_flg_(nbtr_)      ! ModThL
     138    INTEGER,INTENT(IN) :: pbl_flg_(nbtr_)       ! ModThL
     139    CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_)       ! ModThL
    144140    ! Isotopes:
    145141    INTEGER,INTENT(IN) :: nqfils_(nqtot_)
     
    172168    nqo=nqo_
    173169    nbtr=nbtr_
    174     nqINCA=nqINCA_
     170    nqCO2=nqCO2_        ! ModThL
    175171#ifdef CPP_StratAer
    176172    nbtr_bin=nbtr_bin_
     
    189185    niadv(:)=niadv_(:)
    190186    ALLOCATE(conv_flg(nbtr))
    191     IF (type_trac == 'inco') THEN
    192       conv_flg(1)=1
    193       conv_flg(2:nbtr)=conv_flg_(:)
    194     ELSE
    195       conv_flg(:)=conv_flg_(:)
    196     ENDIF
     187    conv_flg(:)=conv_flg_(:)
    197188    ALLOCATE(pbl_flg(nbtr))
    198     IF (type_trac == 'inco') THEN
    199       pbl_flg(1)=1
    200       pbl_flg(2:nbtr)=pbl_flg_(:)
    201     ELSE
    202       pbl_flg(:)=pbl_flg_(:)
    203     ENDIF
     189    pbl_flg(:)=pbl_flg_(:)
    204190    ALLOCATE(solsym(nbtr))
    205     IF (type_trac == 'inco') THEN
    206       solsym(1)='CO2'
    207       solsym(2:nbtr)=solsym_(:)
    208     ELSE
    209       solsym(:)=solsym_(:)
    210     ENDIF
     191    solsym(:)=solsym_(:)
    211192     
    212193    IF(prt_level.ge.1) THEN
    213       write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqINCA",nqtot,nqo,nbtr,nqINCA
     194      write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqCO2",nqtot,nqo,nbtr,nqCO2      ! ModThL
    214195    ENDIF
    215196   
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r3865 r3870  
    3939    USE ioipsl_getin_p_mod, ONLY : getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac, nqINCA
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac, nqCO2
    4242    USE iophy
    4343    USE limit_read_mod, ONLY : init_limit_read
     
    19261926       !c         ENDDO
    19271927       !
    1928        IF (type_trac == 'inca') THEN
     1928       IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN                   ! ModThL
    19291929#ifdef INCA
    19301930          CALL VTe(VTphysiq)
     
    19431943               klon, &
    19441944               nqtot, &
    1945                nqo, &
     1945               nqo+nqCO2, &     ! ModThL
    19461946               pdtphys, &
    19471947               annee_ref, &
     
    19681968          cg_aero(:,:,:,:) = init_cginca
    19691969!         
    1970 
    1971 
    1972           CALL VTe(VTinca)
    1973           CALL VTb(VTphysiq)
    1974 #endif
    1975        ELSEIF (type_trac == 'inco') THEN
    1976 #ifdef INCA
    1977           CALL VTe(VTphysiq)
    1978           CALL VTb(VTinca)
    1979           calday = REAL(days_elapsed) + jH_cur
    1980           WRITE(lunout,*) 'initial time chemini', days_elapsed, calday
    1981 
    1982           CALL chemini(  &
    1983                rg, &
    1984                ra, &
    1985                cell_area, &
    1986                latitude_deg, &
    1987                longitude_deg, &
    1988                presnivs, &
    1989                calday, &
    1990                klon, &
    1991                nqtot, &
    1992                nqo+1, &   ! Note ThL: diff is here with case 'inca'
    1993                pdtphys, &
    1994                annee_ref, &
    1995                year_cur, &
    1996                day_ref,  &
    1997                day_ini, &
    1998                start_time, &
    1999                itau_phy, &
    2000                date0, &
    2001                io_lon, &
    2002                io_lat, &
    2003                chemistry_couple, &
    2004                init_source, &
    2005                init_tauinca, &
    2006                init_pizinca, &
    2007                init_cginca, &
    2008                init_ccminca)
    2009 
    2010 
    2011           ! initialisation des variables depuis le restart de inca
    2012           ccm(:,:,:) = init_ccminca
    2013           tau_aero(:,:,:,:) = init_tauinca
    2014           piz_aero(:,:,:,:) = init_pizinca
    2015           cg_aero(:,:,:,:) = init_cginca
    2016 !
    20171970
    20181971
     
    37853738    ENDDO
    37863739
    3787     IF (type_trac == 'inca') THEN
     3740    IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN      ! ModThL
    37883741#ifdef INCA
    37893742       CALL VTe(VTphysiq)
     
    38283781            nbp_lon, &
    38293782            nbp_lat-1, &
    3830             tr_seri, &
    3831             ftsol, &
    3832             paprs, &
    3833             cdragh, &
    3834             cdragm, &
    3835             pctsrf, &
    3836             pdtphys, &
    3837             itap)
    3838 
    3839        CALL VTe(VTinca)
    3840        CALL VTb(VTphysiq)
    3841 #endif
    3842     ELSEIF (type_trac == 'inco') THEN
    3843 #ifdef INCA
    3844        CALL VTe(VTphysiq)
    3845        CALL VTb(VTinca)
    3846        calday = REAL(days_elapsed + 1) + jH_cur
    3847 
    3848        CALL chemtime(itap+itau_phy-1, date0, phys_tstep, itap)
    3849        CALL AEROSOL_METEO_CALC( &
    3850             calday,pdtphys,pplay,paprs,t,pmflxr,pmflxs, &
    3851             prfl,psfl,pctsrf,cell_area, &
    3852             latitude_deg,longitude_deg,u10m,v10m)
    3853 
    3854        zxsnow_dummy(:) = 0.0
    3855 
    3856        CALL chemhook_begin (calday, &
    3857             days_elapsed+1, &
    3858             jH_cur, &
    3859             pctsrf(1,1), &
    3860             latitude_deg, &
    3861             longitude_deg, &
    3862             cell_area, &
    3863             paprs, &
    3864             pplay, &
    3865             coefh(1:klon,1:klev,is_ave), &
    3866             pphi, &
    3867             t_seri, &
    3868             u, &
    3869             v, &
    3870             rot, &
    3871             wo(:, :, 1), &
    3872             q_seri, &
    3873             zxtsol, &
    3874             zt2m, &
    3875             zxsnow_dummy, &
    3876             solsw, &
    3877             albsol1, &
    3878             rain_fall, &
    3879             snow_fall, &
    3880             itop_con, &
    3881             ibas_con, &
    3882             cldfra, &
    3883             nbp_lon, &
    3884             nbp_lat-1, &
    3885             tr_seri(:,:,2:nbtr), &  ! Note ThL: diff is here with case 'inca'
     3783            tr_seri(:,:,1+nqCO2:nbtr), &                ! ModThL
    38863784            ftsol, &
    38873785            paprs, &
     
    50254923    ENDDO
    50264924    !
    5027     IF (type_trac == 'inca') THEN
     4925    IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN      ! ModThL
    50284926#ifdef INCA
    50294927       CALL VTe(VTphysiq)
     
    50344932            pplay, &
    50354933            t_seri, &
    5036             tr_seri, &
    5037             nbtr, &
    5038             paprs, &
    5039             q_seri, &
    5040             cell_area, &
    5041             pphi, &
    5042             pphis, &
    5043             zx_rh, &
    5044             aps, bps, ap, bp)
    5045 
    5046        CALL VTe(VTinca)
    5047        CALL VTb(VTphysiq)
    5048 #endif
    5049     ELSEIF (type_trac == 'inco') THEN
    5050 #ifdef INCA
    5051        CALL VTe(VTphysiq)
    5052        CALL VTb(VTinca)
    5053 
    5054        CALL chemhook_end ( &
    5055             phys_tstep, &
    5056             pplay, &
    5057             t_seri, &
    5058             tr_seri(:,:,2:nbtr), & ! Note ThL: diff is here with case 'inca'
     4934            tr_seri(:,:,1+nqCO2:nbtr), &        ! ModThL
    50594935            nbtr, &
    50604936            paprs, &
  • LMDZ6/trunk/libf/phylmd/phytrac_mod.F90

    r3865 r3870  
    5656  SUBROUTINE phytrac_init()
    5757    USE dimphy
    58     USE infotrac_phy, ONLY: nbtr, nqINCA, type_trac
     58    USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac
    5959    USE tracco2i_mod, ONLY: tracco2i_init
    6060    IMPLICIT NONE
     
    124124    USE phys_cal_mod, only : hour
    125125    USE dimphy
    126     USE infotrac_phy, ONLY: nbtr, nqINCA, type_trac, conv_flg, solsym, pbl_flg
     126    USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac, conv_flg, solsym, pbl_flg
    127127    USE mod_grid_phy_lmdz
    128128    USE mod_phys_lmdz_para
     
    508508          iflag_con_trac= 1
    509509       CASE('inco')
    510           source(:,1) = 0.                          ! from CO2i
    511           source(:,2:nbtr)=init_source(:,:)         ! from INCA
    512           aerosol(1) = .FALSE.                      ! from CO2i
    513           CALL tracinca_init(aerosol(2:nbtr),lessivage)     ! from INCA
    514           pbl_flg(1) = 1              ! From CO2i
     510          source(:,1:nqCO2) = 0.                          ! from CO2i   ModThL
     511          source(:,nqCO2+1:nbtr)=init_source(:,:)         ! from INCA   ModThL
     512          aerosol(1:nqCO2) = .FALSE.                      ! from CO2i   ModThL
     513          CALL tracinca_init(aerosol(nqCO2+1:nbtr),lessivage)     ! from INCA   ModThL
     514          pbl_flg(1:nqCO2) = 1              ! From CO2i         ModThL
    515515          iflag_the_trac= 1           ! From CO2i
    516516          iflag_vdf_trac= 1           ! From CO2i
     
    11081108
    11091109    !    -- CHIMIE INCA  config_inca = aero or chem --
    1110     IF (type_trac == 'inca') THEN
     1110    IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN  ! ModThL
    11111111
    11121112       CALL tracinca(&
     
    11201120            tau_aero, piz_aero, cg_aero,        ccm,       &
    11211121            rfname,                                        &
    1122             tr_seri,  source)
    1123     ELSEIF (type_trac == 'inco') THEN       ! Add ThL
    1124        CALL tracinca(&
    1125             nstep,    julien,   gmtime,         lafin,     &
    1126             pdtphys,  t_seri,   paprs,          pplay,     &
    1127             pmfu,     upwd,     ftsol,  pctsrf, pphis,     &
    1128             pphi,     albsol,   sh,    ch,     rh,        &
    1129             cldfra,   rneb,     diafra,         cldliq,    &
    1130             itop_con, ibas_con, pmflxr,         pmflxs,    &
    1131             prfl,     psfl,     aerosol_couple, flxmass_w, &
    1132             tau_aero, piz_aero, cg_aero,        ccm,       &
    1133             rfname,                                        &
    1134             tr_seri(:,:,2:nbtr),  source(:,2:nbtr))     ! Difference with case 'inca' 
     1122            tr_seri(:,:,1+nqCO2:nbtr),  source(:,1+nqCO2:nbtr))  ! ModThL 
    11351123    ENDIF
    11361124    !=============================================================
Note: See TracChangeset for help on using the changeset viewer.