Changeset 3865


Ignore:
Timestamp:
Mar 23, 2021, 4:14:07 PM (3 years ago)
Author:
lmdz-users
Message:

Modifications from Thibaut to create an ESM with interactive CO2 + INCA aerosols

Location:
LMDZ6/trunk/libf
Files:
15 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/conf_gcm.F90

    r3540 r3865  
    595595     !Config         'inca' = model de chime INCA
    596596     !Config         'repr' = model de chime REPROBUS
     597     !Config         'inco' = INCA + CO2i (temporaire)
    597598     type_trac = 'lmdz'
    598599     CALL getin('type_trac',type_trac)
     
    790791     !Config         'inca' = model de chime INCA
    791792     !Config         'repr' = model de chime REPROBUS
     793     !Config         'inco' = INCA + CO2i (temporaire)
    792794     type_trac = 'lmdz'
    793795     CALL getin('type_trac',type_trac)
  • LMDZ6/trunk/libf/dyn3d/dynredem.F90

    r3803 r3865  
    227227!--- Tracers in file "start_trac.nc" (added by Anne)
    228228  lread_inca=.FALSE.; fil="start_trac.nc"
    229   IF(type_trac=='inca') INQUIRE(FILE=fil,EXIST=lread_inca)
     229  IF(type_trac=='inca' .OR. type_trac=='inco') INQUIRE(FILE=fil,EXIST=lread_inca)
    230230  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
    231231
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r3800 r3865  
    1414! CRisi: nb traceurs pères= directement advectés par l'air
    1515  INTEGER, SAVE :: nqperes
     16
     17! ThL: nb traceurs spécifiques à INCA
     18  INTEGER, SAVE :: nqINCA
    1619
    1720! Name variables
     
    7376  SUBROUTINE infotrac_init
    7477    USE control_mod, ONLY: planet_type, config_inca
     78    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    7579#ifdef REPROBUS
    7680    USE CHEM_REP, ONLY : Init_chem_rep_trac
     
    118122
    119123    character(len=*),parameter :: modname="infotrac_init"
     124
     125    INTEGER :: nqexcl ! ThL. Nb de traceurs dans traceur.def. Egal à nqtrue,
     126                      ! sauf pour 'inca' = nqtrue-nbtr, et 'inco' = 4.
    120127!-----------------------------------------------------------------------
    121128! Initialization :
     
    138145    ! Coherence test between parameter type_trac, config_inca and preprocessing keys
    139146    IF (type_trac=='inca') THEN
    140        WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     147       WRITE(lunout,*) 'You have chosen to couple with INCA chemistry model : type_trac=', &
    141148            type_trac,' config_inca=',config_inca
    142149       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
     
    149156#endif
    150157    ELSE IF (type_trac=='repr') THEN
    151        WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     158       WRITE(lunout,*) 'You have chosen to couple with REPROBUS chemestry model : type_trac=', type_trac
    152159#ifndef REPROBUS
    153160       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     
    164171    ELSE IF (type_trac == 'lmdz') THEN
    165172       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
     173    ELSE IF (type_trac == 'inco') THEN ! ThL
     174       WRITE(lunout,*) 'Using jointly INCA and CO2 cycle: type_trac =', type_trac
     175       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
     176          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     177          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     178       END IF
     179#ifndef INCA
     180       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compilewith INCA code'
     181       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     182#endif   
    166183    ELSE
    167184       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     
    170187
    171188    ! Test if config_inca is other then none for run without INCA
    172     IF (type_trac/='inca' .AND. config_inca/='none') THEN
     189    IF (type_trac/='inca' .AND. type_trac/='inco' .AND. config_inca/='none') THEN
    173190       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
    174191       config_inca='none'
     
    206223!!       endif
    207224!>jyg
    208     ELSE ! type_trac=inca
     225    ELSE ! type_trac=inca (or inco ThL)
    209226!jyg<
    210227       ! The traceur.def file is used to define the number "nqo" of water phases
     
    219236       ENDIF
    220237       IF (nqo /= 2 .AND. nqo /= 3 ) THEN
    221           WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowded. Only 2 or 3 water phases allowed'
     238          IF (nqo == 4 .AND. type_trac=='inco') THEN ! ThL
     239             WRITE(lunout,*) trim(modname),': you are coupling with INCA, and also using CO2i.'
     240             nqo = 3    ! A améliorier... je force 3 traceurs eau...  ThL
     241             WRITE(lunout,*) trim(modname),': nqo = ',nqo
     242          ELSE
     243          WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowed. Only 2 or 3 water phases allowed'
    222244          CALL abort_gcm('infotrac_init','Bad number of water phases',1)
     245          ENDIF
    223246       END IF
    224247       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
     
    226249       CALL Init_chem_inca_trac(nbtr)
    227250#endif       
    228        nqtrue=nbtr+nqo
    229 
    230        ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr))
    231 
     251       IF (type_trac=='inco') THEN          ! Add ThL
     252          nqexcl = nqo+1                    ! Tracers excluding INCA's = water + CO2 in 'inco' case
     253       ELSE
     254          nqexcl = nqo                      ! Tracers excluding INCA's = water
     255       ENDIF
     256       nqtrue = nbtr + nqexcl               ! Total nb of tracers = INCA's + traceur.def
     257       IF (type_trac=='inco') THEN          !
     258          nqINCA = nbtr                     ! nbtr = other tracers than H2O = INCA's + CO2i
     259          nbtr = nqINCA + 1                 !
     260       ELSEIF (type_trac=='inca') THEN      !
     261          nqINCA = nbtr                     !
     262       ELSE                                 !
     263          nqINCA = 0                        !
     264       ENDIF                                !
     265       WRITE(lunout,*) trim(modname),': nqo = ',nqo
     266       WRITE(lunout,*) trim(modname),': nbtr = ',nbtr
     267       WRITE(lunout,*) trim(modname),': nqexcl = ',nqexcl
     268       WRITE(lunout,*) trim(modname),': nqtrue = ',nqtrue
     269       WRITE(lunout,*) trim(modname),': nqINCA = ',nqINCA
     270       ALLOCATE(hadv_inca(nqINCA), vadv_inca(nqINCA)) ! ThL
    232271    ENDIF   ! type_trac
    233272!>jyg
     
    360399       
    361400       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
    362        WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
     401       WRITE(lunout,*) trim(modname),': nombre total de traceurs ',nqtrue
     402       WRITE(lunout,*) trim(modname),': nombre de traceurs dans traceur.def ',nqexcl
    363403       DO iq=1,nqtrue
    364404          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq),tnom_transp(iq)
     
    418458#endif
    419459
    420     ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac = 'coag')
     460    ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac = 'coag' .OR. type_trac = 'co2i')
    421461!jyg<
    422462!
     
    483523             write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
    484524
    485           END DO !DO iq=1,nqtrue
     525          END DO !DO iq=1,nqo
    486526          CLOSE(90) 
    487527       ELSE  !! if traceur.def doesn't exist
     
    515555
    516556    END IF ! (type_trac == 'inca')
     557
     558    !< add ThL case 'inco'
     559    IF (type_trac == 'inco') THEN
     560 ! le module de chimie fournit les noms des traceurs
     561 ! et les schemas d'advection associes. excepte pour ceux lus
     562 ! dans traceur.def
     563       IF (ierr .eq. 0) then
     564          DO iq=1,nqexcl
     565             write(*,*) 'infotrac 237: iq=',iq
     566             ! CRisi: ajout du nom du fluide transporteur
     567             ! mais rester retro compatible
     568             READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
     569             write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
     570             write(lunout,*) 'tchaine=',trim(tchaine)
     571             write(*,*) 'infotrac 238: IOstatus=',IOstatus
     572             if (IOstatus.ne.0) then
     573                CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
     574             endif
     575             ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
     576             ! espace ou pas au milieu de la chaine.
     577             continu=.true.
     578             nouveau_traceurdef=.false.
     579             iiq=1
     580             do while (continu)
     581                if (tchaine(iiq:iiq).eq.' ') then
     582                  nouveau_traceurdef=.true.
     583                  continu=.false.
     584                else if (iiq.lt.LEN_TRIM(tchaine)) then
     585                  iiq=iiq+1
     586                else
     587                  continu=.false.
     588                endif
     589             enddo
     590             write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
     591             if (nouveau_traceurdef) then
     592                write(lunout,*) 'C''est la nouvelle version de traceur.def'
     593                tnom_0(iq)=tchaine(1:iiq-1)
     594                tnom_transp(iq)=tchaine(iiq+1:15)
     595             else
     596                write(lunout,*) 'C''est l''ancienne version de traceur.def'
     597                write(lunout,*) 'On suppose que les traceurs sont tous d''air'
     598                tnom_0(iq)=tchaine
     599                tnom_transp(iq) = 'air'
     600             endif
     601             write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
     602             write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
     603          END DO !DO iq=1,nqexcl
     604          CLOSE(90) 
     605       ELSE  !! if traceur.def doesn't exist
     606          tnom_0(1)='H2Ov'
     607          tnom_transp(1) = 'air'
     608          tnom_0(2)='H2Ol'
     609          tnom_transp(2) = 'air'
     610          hadv(1) = 10
     611          hadv(2) = 10
     612          vadv(1) = 10
     613          vadv(2) = 10
     614       ENDIF
     615
     616#ifdef INCA
     617       CALL init_transport( &
     618            hadv_inca, &
     619            vadv_inca, &
     620            conv_flg, &
     621            pbl_flg,  &
     622            solsym)
     623#endif
     624
     625       DO iq = nqexcl+1, nqtrue
     626          hadv(iq) = hadv_inca(iq-nqexcl)     ! mod. Thl : nqexcl was nqo (in order to shift)
     627          vadv(iq) = vadv_inca(iq-nqexcl)     ! idem
     628          tnom_0(iq)=solsym(iq-nqexcl)        ! idem
     629          tnom_transp(iq) = 'air'
     630       END DO
     631
     632    END IF ! (type_trac == 'inco')
     633!> add ThL case 'inco'
    517634
    518635!-----------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90

    r3803 r3865  
    242242!$OMP MASTER
    243243  fil="start_trac.nc"
    244   IF(type_trac=='inca') INQUIRE(FILE=fil,EXIST=lread_inca)
     244  IF(type_trac=='inca' .OR. type_trac=='inco') INQUIRE(FILE=fil,EXIST=lread_inca)
    245245  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
    246246!$OMP END MASTER
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F

    r3666 r3865  
    15391539
    15401540#ifdef INCA
    1541          if (type_trac == 'inca') then
     1541         if (type_trac == 'inca' .OR. type_trac == 'inco') then
    15421542            call finalize_inca
    15431543         endif
     
    15941594
    15951595#ifdef INCA
    1596               if (type_trac == 'inca') then
     1596              if (type_trac == 'inca' .OR. type_trac == 'inco') then
    15971597                 call finalize_inca
    15981598              endif
     
    17501750
    17511751#ifdef INCA
    1752                  if (type_trac == 'inca') then
     1752                 if (type_trac == 'inca' .OR. type_trac == 'inco') then
    17531753                    call finalize_inca
    17541754                 endif
     
    18451845
    18461846#ifdef INCA
    1847       if (type_trac == 'inca') then
     1847      if (type_trac == 'inca' .OR. type_trac == 'inco') then
    18481848         call finalize_inca
    18491849      endif
  • LMDZ6/trunk/libf/dyn3dpar/dynredem.F

    r2622 r3865  
    568568      call NF95_PUT_VAR(nid,nvarid,teta)
    569569
    570       IF (type_trac == 'inca') THEN
     570      IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    571571! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    572572         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    581581      do iq=1,nqtot
    582582
    583          IF (type_trac /= 'inca') THEN
     583         IF (type_trac /= 'inca' .AND. type_trac /= 'inco') THEN
    584584            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    585585            IF (ierr .NE. NF_NOERR) THEN
  • LMDZ6/trunk/libf/dyn3dpar/dynredem_p.F

    r2622 r3865  
    580580      call NF95_PUT_VAR(nid,nvarid,teta)
    581581
    582       IF (type_trac == 'inca') THEN
     582      IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    583583! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    584584         inquire(FILE="start_trac.nc", EXIST=exist_file)
     
    597597      do iq=1,nqtot
    598598
    599          IF (type_trac /= 'inca') THEN
     599         IF (type_trac /= 'inca' .AND. type_trac /= 'inco') THEN
    600600            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    601601            IF (ierr .NE. NF_NOERR) THEN
  • LMDZ6/trunk/libf/dyn3dpar/gcm.F

    r2622 r3865  
    209209#endif
    210210
    211       IF (type_trac == 'inca') THEN
     211      IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    212212#ifdef INCA
    213213         call init_const_lmdz(
     
    415415c   Initialisation des dimensions d'INCA :
    416416c   --------------------------------------
    417       IF (type_trac == 'inca') THEN
     417      IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    418418!$OMP PARALLEL
    419419#ifdef INCA
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r3677 r3865  
    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,tname,ttext,type_trac,&
     18  USE infotrac, ONLY: nqtot,nqo,nbtr,nqINCA,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,tname,ttext,type_trac,&
     148  CALL init_infotrac_phy(nqtot,nqo,nbtr,nqINCA,tname,ttext,type_trac,&
    149149                         niadv,conv_flg,pbl_flg,solsym,&
    150150                         nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,&
     
    172172!$OMP END PARALLEL
    173173
    174   IF (type_trac == 'inca') THEN
     174  IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    175175#ifdef INCA
    176176     call init_const_lmdz( &
     
    198198  END IF
    199199
    200   IF (type_trac == 'inca') THEN
     200  IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    201201#ifdef INCA
    202202     CALL init_inca_dim(klon_omp,nbp_lev,nbp_lon,nbp_lat - 1, &
  • LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.F90

    r3857 r3865  
    4545  LOGICAL, PUBLIC :: read_fco2_ocean_cor    ! flag to read corrective oceanic CO2 flux
    4646!$OMP THREADPRIVATE(read_fco2_ocean_cor) 
    47   REAL, PUBLIC :: var_fco2_ocean_cor        ! corrective oceanic CO2 flux
     47  REAL, SAVE, PUBLIC :: var_fco2_ocean_cor        ! corrective oceanic CO2 flux
    4848!$OMP THREADPRIVATE(var_fco2_ocean_cor)
    49   REAL, PUBLIC :: ocean_area_tot            ! total oceanic area to convert flux
     49  REAL, SAVE, PUBLIC :: ocean_area_tot            ! total oceanic area to convert flux
    5050!$OMP THREADPRIVATE(ocean_area_tot)
    5151  LOGICAL, PUBLIC :: read_fco2_land_cor     ! flag to read corrective land CO2 flux
    5252!$OMP THREADPRIVATE(read_fco2_land_cor) 
    53   REAL, PUBLIC :: var_fco2_land_cor         ! corrective land CO2 flux
     53  REAL, SAVE, PUBLIC :: var_fco2_land_cor         ! corrective land CO2 flux
    5454!$OMP THREADPRIVATE(var_fco2_land_cor)
    55   REAL, PUBLIC :: land_area_tot             ! total land area to convert flux
     55  REAL, SAVE, PUBLIC :: land_area_tot             ! total land area to convert flux
    5656!$OMP THREADPRIVATE(land_area_tot)
    5757
     
    108108  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean ! Net flux from ocean [kgCO2/m2/s]
    109109!$OMP THREADPRIVATE(fco2_ocean)
    110   REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean_cor ! Net corrective flux from ocean [kgCO2/m2/s]
     110  REAL, DIMENSION(:), ALLOCATABLE, SAVE, PUBLIC :: fco2_ocean_cor ! Net corrective flux from ocean [kgCO2/m2/s]
    111111!$OMP THREADPRIVATE(fco2_ocean_cor)
    112   REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_land_cor  ! Net corrective flux from land [kgCO2/m2/s]
     112  REAL, DIMENSION(:), ALLOCATABLE, SAVE, PUBLIC :: fco2_land_cor  ! Net corrective flux from land [kgCO2/m2/s]
    113113!$OMP THREADPRIVATE(fco2_land_cor)
    114114
     
    123123
    124124! Calculated co2 field to be send to the ocean via the coupler and to ORCHIDEE
    125   REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: co2_send ! Field allocated in phyetat0
     125  REAL, DIMENSION(:), ALLOCATABLE, SAVE, PUBLIC :: co2_send ! Field allocated in phyetat0
    126126!$OMP THREADPRIVATE(co2_send)
    127127
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r3677 r3865  
    2020  INTEGER, SAVE :: nbtr
    2121!$OMP THREADPRIVATE(nbtr)
     22
     23! ThL : number of tracers specific to INCA
     24  INTEGER, SAVE :: nqINCA
     25!$OMP THREADPRIVATE(nqINCA)
    2226
    2327#ifdef CPP_StratAer
     
    3337  INTEGER, SAVE :: nqperes
    3438!$OMP THREADPRIVATE(nqperes)
     39
     40! ThL : nb de traceurs dans le traceur.def
     41  INTEGER, SAVE :: nqexcl
     42!$OMP THREADPRIVATE(nqexcl)
    3543
    3644! Name variables
     
    96104CONTAINS
    97105
    98   SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,tname_,ttext_,type_trac_,&
     106  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqINCA_,tname_,ttext_,type_trac_,&
    99107                               niadv_,conv_flg_,pbl_flg_,solsym_,&
    100108                               nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
     
    118126    INTEGER,INTENT(IN) :: nqo_
    119127    INTEGER,INTENT(IN) :: nbtr_
     128    INTEGER,INTENT(IN) :: nqINCA_
    120129#ifdef CPP_StratAer
    121130    INTEGER,INTENT(IN) :: nbtr_bin_
     
    130139    CHARACTER(len=4),INTENT(IN) :: type_trac_
    131140    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
    132     INTEGER,INTENT(IN) :: conv_flg_(nbtr_)
    133     INTEGER,INTENT(IN) :: pbl_flg_(nbtr_)
    134     CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_)
     141    INTEGER,INTENT(IN) :: conv_flg_(nqINCA_)
     142    INTEGER,INTENT(IN) :: pbl_flg_(nqINCA_)
     143    CHARACTER(len=8),INTENT(IN) :: solsym_(nqINCA_)
    135144    ! Isotopes:
    136145    INTEGER,INTENT(IN) :: nqfils_(nqtot_)
     
    163172    nqo=nqo_
    164173    nbtr=nbtr_
     174    nqINCA=nqINCA_
    165175#ifdef CPP_StratAer
    166176    nbtr_bin=nbtr_bin_
     
    179189    niadv(:)=niadv_(:)
    180190    ALLOCATE(conv_flg(nbtr))
    181     conv_flg(:)=conv_flg_(:)
     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
    182197    ALLOCATE(pbl_flg(nbtr))
    183     pbl_flg(:)=pbl_flg_(:)
     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
    184204    ALLOCATE(solsym(nbtr))
    185     solsym(:)=solsym_(:)
    186  
     205    IF (type_trac == 'inco') THEN
     206      solsym(1)='CO2'
     207      solsym(2:nbtr)=solsym_(:)
     208    ELSE
     209      solsym(:)=solsym_(:)
     210    ENDIF
     211     
    187212    IF(prt_level.ge.1) THEN
    188       write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr",nqtot,nqo,nbtr
     213      write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqINCA",nqtot,nqo,nbtr,nqINCA
    189214    ENDIF
    190215   
  • LMDZ6/trunk/libf/phylmd/phyetat0.F90

    r3862 r3865  
    452452  ENDIF
    453453
    454 !--OB now this is for co2i
    455   IF (type_trac == 'co2i') THEN
     454!--OB now this is for co2i - ThL: and therefore also for inco
     455  IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
    456456     IF (carbon_cycle_cpl) THEN
    457457        ALLOCATE(co2_send(klon), stat=ierr)
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r3857 r3865  
    453453    REAL,DIMENSION(klon)      :: zrho, zt
    454454
     455    INTEGER :: nqup
     456
    455457    ! On calcul le nouveau tau:
    456458    itau_w = itau_phy + itap
     
    24362438         ENDIF !--type_trac co2i
    24372439
     2440         IF (type_trac == 'inco') THEN
     2441           nqup = nqo+1
     2442           DO iq=nqo+1, nqup
     2443             !--3D fields
     2444             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
     2445             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
     2446             CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
     2447             CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
     2448             !--2D fields
     2449             !--CO2 burden
     2450             zx_tmp_fi2d=0.
     2451             IF (vars_defined) THEN
     2452                DO k=1,klev
     2453                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,iq-nqo)
     2454                ENDDO
     2455             ENDIF
     2456             CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
     2457           ENDDO !--iq
     2458           !--CO2 net fluxes
     2459           CALL histwrite_phy(o_flx_co2_land,  fco2_land)
     2460           CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
     2461           CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
     2462           CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
     2463           CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
     2464           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
     2465         ENDIF !--type_trac inco
     2466
    24382467       ENDIF   !(iflag_phytrac==1)
    24392468
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r3861 r3865  
    3939    USE ioipsl_getin_p_mod, ONLY : getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac, nqINCA
    4242    USE iophy
    4343    USE limit_read_mod, ONLY : init_limit_read
     
    14121412       tau_overturning_th(:)=0.
    14131413
    1414        IF (type_trac == 'inca') THEN
     1414       IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
    14151415          ! jg : initialisation jusqu'au ces variables sont dans restart
    14161416          ccm(:,:,:) = 0.
     
    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!
    19702017
    19712018
     
    37923839       CALL VTe(VTinca)
    37933840       CALL VTb(VTphysiq)
    3794 #endif
    3795     ENDIF !type_trac = inca
     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'
     3886            ftsol, &
     3887            paprs, &
     3888            cdragh, &
     3889            cdragm, &
     3890            pctsrf, &
     3891            pdtphys, &
     3892            itap)
     3893
     3894       CALL VTe(VTinca)
     3895       CALL VTb(VTphysiq)
     3896#endif
     3897    ENDIF !type_trac = inca or inco
    37963898    IF (type_trac == 'repr') THEN
    37973899#ifdef REPROBUS
     
    49455047       CALL VTb(VTphysiq)
    49465048#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'
     5059            nbtr, &
     5060            paprs, &
     5061            q_seri, &
     5062            cell_area, &
     5063            pphi, &
     5064            pphis, &
     5065            zx_rh, &
     5066            aps, bps, ap, bp)
     5067
     5068       CALL VTe(VTinca)
     5069       CALL VTb(VTphysiq)
     5070#endif
    49475071    ENDIF
    49485072
  • LMDZ6/trunk/libf/phylmd/phytrac_mod.F90

    r3861 r3865  
    5656  SUBROUTINE phytrac_init()
    5757    USE dimphy
    58     USE infotrac_phy, ONLY: nbtr, type_trac
     58    USE infotrac_phy, ONLY: nbtr, nqINCA, type_trac
    5959    USE tracco2i_mod, ONLY: tracco2i_init
    6060    IMPLICIT NONE
     
    8181    CASE('co2i')
    8282       !   -- CO2 interactif --
     83       CALL tracco2i_init()
     84    CASE('inco')
    8385       CALL tracco2i_init()
    8486    END SELECT
     
    122124    USE phys_cal_mod, only : hour
    123125    USE dimphy
    124     USE infotrac_phy, ONLY: nbtr, type_trac, conv_flg, solsym, pbl_flg
     126    USE infotrac_phy, ONLY: nbtr, nqINCA, type_trac, conv_flg, solsym, pbl_flg
    125127    USE mod_grid_phy_lmdz
    126128    USE mod_phys_lmdz_para
     
    505507          iflag_vdf_trac= 1
    506508          iflag_con_trac= 1
     509       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
     515          iflag_the_trac= 1           ! From CO2i
     516          iflag_vdf_trac= 1           ! From CO2i
     517          iflag_con_trac= 1           ! From CO2i
    507518#ifdef CPP_StratAer
    508519       CASE('coag')
     
    571582                !--co2 tracers are not scavenged
    572583                flag_cvltr(it)=.FALSE.
    573 
     584             CASE('inco')     ! Add ThL
     585                flag_cvltr(it)=.FALSE.
    574586#ifdef CPP_StratAer
    575587             CASE('coag')
     
    614626       write(lunout,*)  'flag_cvltr    = ', flag_cvltr
    615627
    616        IF (lessivage .AND. type_trac .EQ. 'inca') THEN
     628       IF (lessivage .AND. (type_trac .EQ. 'inca' .OR. type_trac .EQ. 'inco')) THEN     ! Mod ThL
    617629          CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1)
    618630!          STOP
     
    666678       !   -- sign convention : positive into the atmosphere
    667679
     680       CALL tracco2i(pdtphys, debutphy, &
     681            xlat, xlon, pphis, pphi, &
     682            t_seri, pplay, paprs, tr_seri, source)
     683    CASE('inco')      ! Add ThL
    668684       CALL tracco2i(pdtphys, debutphy, &
    669685            xlat, xlon, pphis, pphi, &
     
    11041120            tau_aero, piz_aero, cg_aero,        ccm,       &
    11051121            rfname,                                        &
    1106             tr_seri,  source)     
    1107        
    1108        
     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' 
    11091135    ENDIF
    11101136    !=============================================================
Note: See TracChangeset for help on using the changeset viewer.