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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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!-----------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.