Changeset 4170


Ignore:
Timestamp:
Jun 16, 2022, 8:16:59 PM (2 years ago)
Author:
dcugnet
Message:

The variable "types_trac" is the equivalent of "type_trac" in case multiple sections must be read
and used in "tracer.def" file.
Tests on the "type_trac" were replaced with tests on the vector "types_trac".
Most of the time, there are two components: 'lmdz' and a second one. The later has priority on 'lmdz'
and must be used for the tests. For more components, care must be taken to execute specific parts
of the code on the right tracers ; the tracers(:)%component has been created in that respect.

Location:
LMDZ6/trunk/libf
Files:
18 edited

Legend:

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

    r4064 r4170  
    167167!-------------------------------------------------------------------------------
    168168  USE strings_mod, ONLY: maxlen
    169   USE infotrac, ONLY: nqtot, tracers, type_trac
     169  USE infotrac, ONLY: nqtot, tracers, types_trac
    170170  USE control_mod
    171171  USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
     
    228228!--- Tracers in file "start_trac.nc" (added by Anne)
    229229  lread_inca=.FALSE.; fil="start_trac.nc"
    230   IF(type_trac=='inca' .OR. type_trac=='inco') INQUIRE(FILE=fil,EXIST=lread_inca)
     230  IF(ANY(types_trac=='inca') .OR. ANY(types_trac=='inco')) INQUIRE(FILE=fil,EXIST=lread_inca)
    231231  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
    232232
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r4169 r4170  
    1414   !=== FOR TRACERS:
    1515   PUBLIC :: infotrac_init                                 !--- Initialization of the tracers
    16    PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
     16   PUBLIC :: tracers, type_trac, types_trac                !--- Full tracers database, tracers type keyword
    1717   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
    1818   PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     
    108108                                    nqtottr, &                  !--- Number of tracers passed to phytrac (TO BE DELETED ?)
    109109                                    nqCO2                       !--- Number of tracers of CO2  (ThL)
    110    CHARACTER(LEN=maxlen),   SAVE :: type_trac                   !--- Keyword for tracers type
     110   CHARACTER(LEN=maxlen),   SAVE :: type_trac                   !--- Keyword for tracers type(s)
     111   CHARACTER(LEN=maxlen),   SAVE, ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
    111112
    112113   !=== DERIVED TYPES EMBEDDING MOST INFORMATIONS ABOUT TRACERS AND ISOTOPES FAMILIES
     
    175176   CHARACTER(LEN=3)      :: descrq(30)                               !--- Advection scheme description tags
    176177   CHARACTER(LEN=maxlen) :: msg1                                     !--- String for messages
    177    CHARACTER(LEN=maxlen), ALLOCATABLE :: str(:)                      !--- Temporary storage
    178178   INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    179179                                                                     !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
     
    201201   
    202202   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
    203    IF(strParse(type_trac, '|', str, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
     203   IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
    204204
    205205   !---------------------------------------------------------------------------------------------------------------------------
     
    207207   !---------------------------------------------------------------------------------------------------------------------------
    208208      !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
    209       msg1 = 'For type_trac = "'//TRIM(str(it))//'":'
    210       SELECT CASE(str(it))
     209      msg1 = 'For type_trac = "'//TRIM(types_trac(it))//'":'
     210      SELECT CASE(types_trac(it))
    211211         CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model, config_inca='//config_inca, modname)
    212212         CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle',  modname)
     
    215215         CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname)
    216216         CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only',          modname)
    217          CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(str(it))//' not possible yet.',1)
     217         CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(types_trac(it))//' not possible yet.',1)
    218218      END SELECT
    219219
    220220      !--- COHERENCE TEST BETWEEN "type_trac" AND "config_inca"
    221       IF(ANY(['inca', 'inco'] == str(it)) .AND. ALL(['aero', 'aeNP', 'chem'] /= config_inca)) &
     221      IF(ANY(['inca', 'inco'] == types_trac(it)) .AND. ALL(['aero', 'aeNP', 'chem'] /= config_inca)) &
    222222         CALL abort_gcm(modname, 'Incoherence between type_trac and config_inca. Please modify "run.def"',1)
    223223
    224224      !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
    225       SELECT CASE(str(it))
     225      SELECT CASE(types_trac(it))
    226226         CASE('inca', 'inco')
    227227#ifndef INCA
     
    244244   !--- DISABLE "config_inca" OPTION FOR A RUN WITHOUT "INCA" IF IT DIFFERS FROM "none"
    245245   IF(fmsg('Setting config_inca="none" as you do not couple with INCA model', &
    246            modname, ALL(str /= 'inca') .AND. ALL(str /= 'inco') .AND. config_inca /= 'none')) config_inca = 'none'
    247 
    248    nqCO2 = 0; IF(ANY(str == 'inco')) nqCO2 = 1
     246         modname, ALL(types_trac /= 'inca') .AND. ALL(types_trac /= 'inco') .AND. config_inca /= 'none')) config_inca = 'none'
     247
     248   nqCO2 = 0; IF(ANY(types_trac == 'inco')) nqCO2 = 1
    249249
    250250!==============================================================================================================================
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90

    r4063 r4170  
    176176  USE mod_hallo
    177177  USE strings_mod, ONLY: maxlen
    178   USE infotrac, ONLY: nqtot, tracers, type_trac
     178  USE infotrac, ONLY: nqtot, tracers, types_trac
    179179  USE control_mod
    180180  USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
     
    244244!$OMP MASTER
    245245  fil="start_trac.nc"
    246   IF(type_trac=='inca' .OR. type_trac=='inco') INQUIRE(FILE=fil,EXIST=lread_inca)
     246  IF(ANY(types_trac=='inca') .OR. ANY(types_trac=='inco')) INQUIRE(FILE=fil,EXIST=lread_inca)
    247247  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
    248248!$OMP END MASTER
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F

    r4148 r4170  
    15191519
    15201520#ifdef INCA
    1521          if (type_trac == 'inca' .OR. type_trac == 'inco') then
     1521         if (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) then
    15221522            call finalize_inca
    15231523         endif
    15241524#endif
    15251525#ifdef REPROBUS
    1526          if (type_trac == 'repr') then
     1526         if (ANY(types_trac == 'repr')) then
    15271527         call finalize_reprobus
    15281528         endif
     
    15721572
    15731573#ifdef INCA
    1574               if (type_trac == 'inca' .OR. type_trac == 'inco') then
     1574              if (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) then
    15751575                 call finalize_inca
    15761576              endif
    15771577#endif
    15781578#ifdef REPROBUS
    1579               if (type_trac == 'repr') then
     1579              if (ANY(types_trac == 'repr')) then
    15801580         call finalize_reprobus
    15811581              endif
     
    17431743
    17441744#ifdef INCA
    1745                  if (type_trac == 'inca' .OR. type_trac == 'inco') then
     1745                 if (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) then
    17461746                    call finalize_inca
    17471747                 endif
    17481748#endif
    17491749#ifdef REPROBUS
    1750                  if (type_trac == 'repr') then
     1750                 if (ANY(types_trac == 'repr')) then
    17511751         call finalize_reprobus
    17521752                 endif
     
    18541854
    18551855#ifdef INCA
    1856       if (type_trac == 'inca' .OR. type_trac == 'inco') then
     1856      if (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) then
    18571857         call finalize_inca
    18581858      endif
    18591859#endif
    18601860#ifdef REPROBUS
    1861       if (type_trac == 'repr') then
     1861      if (ANY(types_trac == 'repr')) then
    18621862         call finalize_reprobus
    18631863      endif
  • LMDZ6/trunk/libf/phy_common/physics_distribution_mod.F90

    r4127 r4170  
    1313  USE mod_grid_phy_lmdz, ONLY: init_grid_phy_lmdz
    1414  USE dimphy, ONLY : Init_dimphy
    15   USE infotrac_phy, ONLY : type_trac
     15  USE infotrac_phy, ONLY : types_trac
    1616#ifdef REPROBUS
    1717  USE CHEM_REP, ONLY : Init_chem_rep_phys
     
    3838
    3939! Initialization of Reprobus
    40     IF (type_trac == 'repr') THEN
     40    IF (ANY(types_trac == 'repr')) THEN
    4141#ifdef REPROBUS
    4242       CALL Init_chem_rep_phys(klon_omp,nbp_lev)
     
    5252!  USE mod_grid_phy_lmdz, ONLY: Init_grid_phy_lmdz!, nbp_lev
    5353!  USE dimphy, ONLY : Init_dimphy
    54 !  USE infotrac_phy, ONLY : type_trac
     54!  USE infotrac_phy, ONLY : types_trac
    5555!#ifdef REPROBUS
    5656!  USE CHEM_REP, ONLY : Init_chem_rep_phys
     
    7272!
    7373!! Initialization of Reprobus
    74 !    IF (type_trac == 'repr') THEN
     74!    IF (ANY(types_trac == 'repr')) THEN
    7575!#ifdef REPROBUS
    7676!       CALL Init_chem_rep_phys(klon_omp,nbp_lev)
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r4154 r4170  
    44MODULE infotrac_phy
    55
    6    USE       strings_mod, ONLY: msg, maxlen, strStack, strHead, strIdx, int2str
     6   USE       strings_mod, ONLY: msg, maxlen, strStack, strHead, strParse, strIdx, int2str
    77   USE readTracFiles_mod, ONLY: trac_type, isot_type, keys_type, delPhase, getKey, tnom_iso => newH2OIso
    88
     
    1313   !=== FOR TRACERS:
    1414   PUBLIC :: init_infotrac_phy                             !--- Initialization of the tracers
    15    PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
     15   PUBLIC :: tracers, type_trac, types_trac                !--- Full tracers database, tracers type keyword
    1616   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
    1717   PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     
    105105                                    nqCO2                       !--- Number of tracers of CO2  (ThL)
    106106   CHARACTER(LEN=maxlen),   SAVE :: type_trac                   !--- Keyword for tracers type
    107 !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nbIso, nqtottr, nqCO2, type_trac)
     107   CHARACTER(LEN=maxlen),   SAVE, ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type
     108
     109!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nbIso, nqtottr, nqCO2, type_trac, types_trac)
    108110
    109111   !=== DERIVED TYPES EMBEDDING MOST INFORMATIONS ABOUT TRACERS AND ISOTOPES FAMILIES
     
    161163
    162164   type_trac = type_trac_
     165   IF(strParse(type_trac, '|', types_trac)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
    163166   tracers   = tracers_
    164167   isotopes  = isotopes_
     
    186189
    187190#ifdef CPP_StratAer
    188    IF (type_trac == 'coag') THEN
     191   IF (ANY(types_trac == 'coag')) THEN
    189192      nbtr_bin    = COUNT([(tracers(iq)%name(1:3)=='BIN', iq=1, nqtot)])
    190193      nbtr_sulgas = COUNT([(tracers(iq)%name(1:3)=='GAS', iq=1, nqtot)])
  • LMDZ6/trunk/libf/phylmd/phyetat0.F90

    r4089 r4170  
    2323  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
    2424  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
    25   USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers
     25  USE infotrac_phy,     ONLY: nqtot, nbtr, types_trac, tracers
    2626  USE traclmdz_mod,     ONLY: traclmdz_from_restart
    2727  USE carbon_cycle_mod, ONLY: carbon_cycle_tr, carbon_cycle_cpl, co2_send
     
    449449!===========================================
    450450
    451   IF (type_trac == 'lmdz') THEN
     451!--OB now this is for co2i - ThL: and therefore also for inco
     452  IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
     453     IF (carbon_cycle_cpl) THEN
     454        ALLOCATE(co2_send(klon), stat=ierr)
     455        IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
     456        found=phyetat0_get(1,co2_send,"co2_send","co2 send",co2_ppm)
     457     ENDIF
     458  ELSE IF (ANY(types_trac == 'lmdz')) THEN
    452459     it = 0
    453460     DO iq = 1, nqtot
     
    460467  ENDIF
    461468
    462 !--OB now this is for co2i - ThL: and therefore also for inco
    463   IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
    464      IF (carbon_cycle_cpl) THEN
    465         ALLOCATE(co2_send(klon), stat=ierr)
    466         IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
    467         found=phyetat0_get(1,co2_send,"co2_send","co2 send",co2_ppm)
    468      ENDIF
    469   ENDIF
    470469
    471470!===========================================
  • LMDZ6/trunk/libf/phylmd/phyredem.F90

    r4089 r4170  
    3535  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
    3636  USE traclmdz_mod, ONLY : traclmdz_to_restart
    37   USE infotrac_phy, ONLY: type_trac, nqtot, tracers, nbtr
     37  USE infotrac_phy, ONLY: types_trac, nqtot, tracers, nbtr
    3838  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    3939  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra
     
    325325
    326326
    327     ! trs from traclmdz_mod
    328     IF (type_trac == 'lmdz') THEN
    329        CALL traclmdz_to_restart(trs)
    330        it = 0
    331        DO iq = 1, nqtot
    332           IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
    333           it = it+1
    334           CALL put_field(pass,"trs_"//tracers(iq)%name, "", trs(:, it))
    335        END DO
    336     END IF
    337 
    338     IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
     327    IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
    339328       IF (carbon_cycle_cpl) THEN
    340329          IF (.NOT. ALLOCATED(co2_send)) THEN
     
    345334          CALL put_field(pass,"co2_send", "co2_ppm for coupling", co2_send)
    346335       END IF
     336
     337    ! trs from traclmdz_mod
     338    ELSE IF (ANY(types_trac == 'lmdz')) THEN
     339       CALL traclmdz_to_restart(trs)
     340       it = 0
     341       DO iq = 1, nqtot
     342          IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
     343          it = it+1
     344          CALL put_field(pass,"trs_"//tracers(iq)%name, "", trs(:, it))
     345       END DO
    347346    END IF
    348347
  • LMDZ6/trunk/libf/phylmd/phys_output_mod.F90

    r4143 r4170  
    3535    USE iophy
    3636    USE dimphy
    37     USE infotrac_phy, ONLY: nqtot, tracers, type_trac, niso
     37    USE infotrac_phy, ONLY: nqtot, tracers, niso
    3838    USE strings_mod,  ONLY: maxlen
    3939    USE ioipsl
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4143 r4170  
    2525
    2626    USE dimphy, ONLY: klon, klev, klevp1
    27     USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, tracers, niso, ntiso
     27    USE infotrac_phy, ONLY: nbtr, nqtot, nqo, types_trac, tracers, niso, ntiso
    2828    USE strings_mod,  ONLY: maxlen
    2929    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
     
    942942       CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d)
    943943
    944        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     944       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    945945          IF (vars_defined) THEN
    946946             zx_tmp_fi2d(:) = swupc0(:,klevp1)*swradcorr(:)
     
    10141014       CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d)
    10151015
    1016        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1016       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    10171017          IF (vars_defined) THEN
    10181018             zx_tmp_fi2d(:) = swupc0(:,1)*swradcorr(:)
     
    10311031       CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d)
    10321032
    1033        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1033       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    10341034          IF (vars_defined) THEN
    10351035             zx_tmp_fi2d(:) = swdnc0(:,1)*swradcorr(:)
     
    10531053       CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr)
    10541054
    1055        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1055       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    10561056          IF (vars_defined) THEN
    10571057             zx_tmp_fi2d(:) = lwupc0(:,klevp1)
     
    10601060       ENDIF
    10611061
    1062        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1062       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    10631063          IF (vars_defined) THEN
    10641064             zx_tmp_fi2d(:) = -1.*lwdnc0(:,1)
     
    15691569!This is warranted by treating INCA aerosols as offline aerosols
    15701570       IF (flag_aerosol.GT.0) THEN
    1571           IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1571          IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    15721572
    15731573             CALL histwrite_phy(o_od443aer, od443aer)
     
    16331633
    16341634#ifdef CPP_StratAer
    1635        IF (type_trac=='coag') THEN
     1635       IF (ANY(types_trac=='coag')) THEN
    16361636          CALL histwrite_phy(o_R2SO4, R2SO4)
    16371637          CALL histwrite_phy(o_OCS_lifetime, OCS_lifetime)
     
    16921692          CALL histwrite_phy(o_solswad0, zx_tmp_fi2d)
    16931693         
    1694           IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1694          IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    16951695
    16961696             CALL histwrite_phy(o_toplwad, toplwad_aero)
     
    17691769       ! Champs 3D:
    17701770       IF (ok_ade .OR. ok_aie) then
    1771           IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     1771          IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    17721772             CALL histwrite_phy(o_ec550aer, ec550aer)
    17731773          ENDIF
     
    22282228       CALL histwrite_phy(o_rsucs, zx_tmp_fi3d1)
    22292229
    2230        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     2230       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    22312231          IF (vars_defined) THEN
    22322232             DO k=1, klevp1
     
    22442244       CALL histwrite_phy(o_rsdcs, zx_tmp_fi3d1)
    22452245
    2246        IF ((type_trac/='inca') .OR. (config_inca=='aeNP')) THEN
     2246       IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
    22472247          IF (vars_defined) THEN
    22482248             DO k=1, klevp1
     
    24892489!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    24902490       IF (iflag_phytrac == 1 ) then
    2491          IF (type_trac == 'lmdz' .OR. type_trac == 'coag') THEN
     2491!
     2492         IF (ANY(types_trac == 'co2i')) THEN
     2493           itr = 0
     2494           DO iq = 1, nqtot
     2495             IF(.NOT.tracers(iq)%isInPhysics) CYCLE
     2496             itr = itr + 1
     2497!            write(*,*) 'phys_output_write_mod 2370: itr=',itr
     2498             !--3D fields
     2499             CALL histwrite_phy(o_trac(itr), tr_seri(:,:,itr))
     2500             CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
     2501             CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
     2502             CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
     2503             !--2D fields
     2504             !--CO2 burden
     2505             zx_tmp_fi2d=0.
     2506             IF (vars_defined) THEN
     2507                DO k=1,klev
     2508                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
     2509                ENDDO
     2510             ENDIF
     2511             CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
     2512           ENDDO !--iq
     2513           !--CO2 net fluxes
     2514           CALL histwrite_phy(o_flx_co2_land,  fco2_land)
     2515           CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
     2516           CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
     2517           CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
     2518           CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
     2519           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
     2520
     2521         ELSE IF (ANY(types_trac == 'inco')) THEN
     2522           itr = 0
     2523           DO iq = 1, nqtot
     2524             IF(.NOT.tracers(iq)%isInPhysics) CYCLE
     2525             itr = itr+1
     2526             IF(tracers(iq)%component /= 'co2i') CYCLE
     2527             !--3D fields
     2528             CALL histwrite_phy(o_trac   (itr),tr_seri(:,:,itr))
     2529             CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
     2530             CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
     2531             CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
     2532             !--2D fields
     2533             !--CO2 burden
     2534             zx_tmp_fi2d=0.
     2535             IF (vars_defined) THEN
     2536                DO k=1,klev
     2537                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
     2538                ENDDO
     2539             ENDIF
     2540             CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
     2541           ENDDO !--iq
     2542           !--CO2 net fluxes
     2543           CALL histwrite_phy(o_flx_co2_land,  fco2_land)
     2544           CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
     2545           CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
     2546           CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
     2547           CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
     2548           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
     2549
     2550         ELSE IF (ANY(types_trac=='lmdz') .OR. ANY(types_trac=='coag')) THEN
    24922551           itr = 0
    24932552           DO iq = 1, nqtot
     
    25212580           ENDDO !--iq
    25222581         ENDIF   !--type_trac
    2523 !
    2524          IF (type_trac == 'co2i') THEN
    2525            itr = 0
    2526            DO iq = 1, nqtot
    2527              IF(.NOT.tracers(iq)%isInPhysics) CYCLE
    2528              itr = itr + 1
    2529 !            write(*,*) 'phys_output_write_mod 2370: itr=',itr
    2530              !--3D fields
    2531              CALL histwrite_phy(o_trac(itr), tr_seri(:,:,itr))
    2532              CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
    2533              CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
    2534              CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
    2535              !--2D fields
    2536              !--CO2 burden
    2537              zx_tmp_fi2d=0.
    2538              IF (vars_defined) THEN
    2539                 DO k=1,klev
    2540                    zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
    2541                 ENDDO
    2542              ENDIF
    2543              CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
    2544            ENDDO !--iq
    2545            !--CO2 net fluxes
    2546            CALL histwrite_phy(o_flx_co2_land,  fco2_land)
    2547            CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
    2548            CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
    2549            CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
    2550            CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
    2551            CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
    2552          ENDIF !--type_trac co2i
    2553 
    2554          IF (type_trac == 'inco') THEN
    2555            itr = 0
    2556            DO iq = 1, nqtot
    2557              IF(.NOT.tracers(iq)%isInPhysics) CYCLE
    2558              itr = itr+1
    2559              IF(tracers(iq)%component /= 'co2i') CYCLE
    2560              !--3D fields
    2561              CALL histwrite_phy(o_trac   (itr),tr_seri(:,:,itr))
    2562              CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
    2563              CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
    2564              CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
    2565              !--2D fields
    2566              !--CO2 burden
    2567              zx_tmp_fi2d=0.
    2568              IF (vars_defined) THEN
    2569                 DO k=1,klev
    2570                    zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
    2571                 ENDDO
    2572              ENDIF
    2573              CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
    2574            ENDDO !--iq
    2575            !--CO2 net fluxes
    2576            CALL histwrite_phy(o_flx_co2_land,  fco2_land)
    2577            CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
    2578            CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
    2579            CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
    2580            CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
    2581            CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
    2582          ENDIF !--type_trac inco
    2583 
    25842582       ENDIF   !(iflag_phytrac==1)
    25852583
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4143 r4170  
    4040    USE ioipsl_getin_p_mod, ONLY : getin_p
    4141    USE indice_sol_mod
    42     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac, nqCO2
     42    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, types_trac, nqCO2
    4343    USE readTracFiles_mod, ONLY: addPhase
    4444    USE strings_mod,  ONLY: strIdx
     
    14541454       tau_overturning_th(:)=0.
    14551455
    1456        IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
     1456       IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
    14571457          ! jg : initialisation jusqu'au ces variables sont dans restart
    14581458          ccm(:,:,:) = 0.
     
    20212021       !c         ENDDO
    20222022       !
    2023        IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN                   ! ModThL
     2023       IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
    20242024#ifdef INCA
    20252025          CALL VTe(VTphysiq)
     
    20782078       ENDIF
    20792079       !
    2080        IF (type_trac == 'repr') THEN
     2080       IF (ANY(types_trac == 'repr')) THEN
    20812081#ifdef REPROBUS
    20822082          CALL chemini_rep(  &
     
    21912191
    21922192    ! Update time and other variables in Reprobus
    2193     IF (type_trac == 'repr') THEN
     2193    IF (ANY(types_trac == 'repr')) THEN
    21942194#ifdef REPROBUS
    21952195       CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     
    29822982          !
    29832983          !>jyg
    2984           IF (type_trac == 'repr') THEN
     2984          IF (ANY(types_trac == 'repr')) THEN
    29852985             nbtr_tmp=ntra
    29862986          ELSE
     
    38873887    ENDDO
    38883888
    3889     IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN      ! ModThL
     3889    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
    38903890#ifdef INCA
    38913891       CALL VTe(VTphysiq)
     
    39433943#endif
    39443944    ENDIF !type_trac = inca or inco
    3945     IF (type_trac == 'repr') THEN
     3945    IF (ANY(types_trac == 'repr')) THEN
    39463946#ifdef REPROBUS
    39473947    !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap)
     
    49204920    !
    49214921
    4922     IF (type_trac=='repr') THEN
     4922    IF (ANY(types_trac=='repr')) THEN
    49234923!MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod
    49244924!MM                               dans Reprobus
     
    50745074    ENDDO
    50755075    !
    5076     IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
     5076    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
    50775077#ifdef INCA
    50785078       CALL VTe(VTphysiq)
     
    50985098    ENDIF
    50995099
    5100     IF (type_trac == 'repr') THEN
     5100    IF (ANY(types_trac == 'repr')) THEN
    51015101#ifdef REPROBUS
    51025102        CALL coord_hyb_rep(paprs, pplay, aps, bps, ap, bp, cell_area)
     
    53605360
    53615361#ifdef INCA
    5362        if (type_trac == 'inca' ) then
     5362       if (ANY(types_trac == 'inca' )) then
    53635363          IF (is_omp_master .and. grid_type==unstructured) THEN
    53645364             CALL finalize_inca
  • LMDZ6/trunk/libf/phylmd/phytrac_mod.F90

    r4124 r4170  
    5656  SUBROUTINE phytrac_init()
    5757    USE dimphy
    58     USE infotrac_phy, ONLY: nbtr, type_trac
     58    USE infotrac_phy, ONLY: nbtr, types_trac
    5959    USE tracco2i_mod, ONLY: tracco2i_init
    6060    IMPLICIT NONE
     
    7878    !     
    7979    !===============================================================================
    80     SELECT CASE(type_trac)
    81     CASE('co2i')
    82        !   -- CO2 interactif --
    83        CALL tracco2i_init()
    84     CASE('inco')
    85        CALL tracco2i_init()
    86     END SELECT
     80    !   -- CO2 interactif --
     81    IF(ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) CALL tracco2i_init()
    8782
    8883
     
    124119    USE phys_cal_mod, only : hour
    125120    USE dimphy
    126     USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac, conv_flg, pbl_flg
     121    USE infotrac_phy, ONLY: nbtr, nqCO2, types_trac, type_trac, conv_flg, pbl_flg
    127122    USE strings_mod,  ONLY: int2str
    128123    USE mod_grid_phy_lmdz
     
    491486
    492487       ! Initialize module for specific tracers
    493        SELECT CASE(type_trac)
    494        CASE('lmdz')
    495           CALL traclmdz_init(pctsrf,xlat,xlon,ftsol,tr_seri,t_seri,pplay,sh,pdtphys,aerosol,lessivage)
    496        CASE('inca')
     488       IF(ANY(types_trac == 'inca')) THEN
    497489          source(:,:)=init_source(:,:)
    498490          CALL tracinca_init(aerosol,lessivage)
    499        CASE('repr')
     491       ELSE IF(ANY(types_trac == 'repr')) THEN
    500492          source(:,:)=0.
    501        CASE('co2i')
     493       ELSE IF(ANY(types_trac == 'co2i')) THEN
    502494          source(:,:)=0.
    503495          lessivage  = .FALSE.
     
    507499          iflag_vdf_trac= 1
    508500          iflag_con_trac= 1
    509        CASE('inco')
     501       ELSE IF(ANY(types_trac == 'inco')) THEN
    510502          source(:,1:nqCO2) = 0.                          ! from CO2i ModThL
    511503          source(:,nqCO2+1:nbtr)=init_source(:,:)         ! from INCA ModThL
     
    517509          iflag_con_trac = 1                              ! From CO2i
    518510#ifdef CPP_StratAer
    519        CASE('coag')
     511       ELSE IF(ANY(types_trac == 'coag')) THEN
    520512          source(:,:)=0.
    521513          DO it= 1, nbtr_sulgas
     
    527519          ENDDO
    528520#endif
    529        END SELECT
     521       ELSE IF(ANY(types_trac == 'lmdz')) THEN
     522          CALL traclmdz_init(pctsrf,xlat,xlon,ftsol,tr_seri,t_seri,pplay,sh,pdtphys,aerosol,lessivage)
     523       END IF
    530524
    531525       !
     
    540534          !
    541535          DO it=1, nbtr
    542              SELECT CASE(type_trac)
    543              CASE('lmdz')
    544                 IF (convscav.and.aerosol(it)) THEN
    545                    flag_cvltr(it)=.TRUE.
    546                    ccntrAA(it) =ccntrAA_in    !--a modifier par JYG a lire depuis fichier
    547                    ccntrENV(it)=ccntrENV_in
    548                    coefcoli(it)=coefcoli_in
    549                 ELSE
    550                    flag_cvltr(it)=.FALSE.
    551                 ENDIF
    552 
    553              CASE('repr')
     536             IF(ANY(types_trac == 'repr')) THEN
    554537                 flag_cvltr(it)=.FALSE.
    555 
    556              CASE('inca')
     538             ELSE IF(ANY(types_trac == 'inca')) THEN
    557539!                IF ((it.EQ.id_Rn222) .OR. ((it.GE.id_SO2) .AND. (it.LE.id_NH3)) ) THEN
    558540!                   !--gas-phase species
     
    578560                !--for now we do not scavenge in cvltr
    579561                flag_cvltr(it)=.FALSE.
    580 
    581              CASE('co2i')
     562             ELSE IF(ANY(types_trac == 'co2i')) THEN
    582563                !--co2 tracers are not scavenged
    583564                flag_cvltr(it)=.FALSE.
    584              CASE('inco')     ! Add ThL
     565             ELSE IF(ANY(types_trac == 'inco')) THEN     ! Add ThL
    585566                flag_cvltr(it)=.FALSE.
    586567#ifdef CPP_StratAer
    587              CASE('coag')
     568             ELSE IF(ANY(types_trac == 'coag')) THEN
    588569                IF (convscav.and.aerosol(it)) THEN
    589570                   flag_cvltr(it)=.TRUE.
     
    595576                ENDIF
    596577#endif
    597 
    598              END SELECT
     578             ELSE IF(ANY(types_trac == 'lmdz')) THEN
     579                IF (convscav.and.aerosol(it)) THEN
     580                   flag_cvltr(it)=.TRUE.
     581                   ccntrAA(it) =ccntrAA_in    !--a modifier par JYG a lire depuis fichier
     582                   ccntrENV(it)=ccntrENV_in
     583                   coefcoli(it)=coefcoli_in
     584                ELSE
     585                   flag_cvltr(it)=.FALSE.
     586                ENDIF
     587             END IF
    599588          ENDDO
    600589          !
     
    620609       write(lunout,*)  'flag_cvltr    = ', flag_cvltr
    621610
    622        IF (lessivage .AND. (type_trac .EQ. 'inca' .OR. type_trac .EQ. 'inco')) THEN     ! Mod ThL
     611       IF (lessivage .AND. (ANY(types_trac == 'inca') .OR. ANY(types_trac=='inco'))) THEN     ! Mod ThL
    623612          CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1)
    624613!          STOP
     
    646635    !     
    647636    !===============================================================================
    648     SELECT CASE(type_trac)
    649     CASE('lmdz')
    650        !    -- Traitement des traceurs avec traclmdz
    651        CALL traclmdz(nstep, julien, gmtime, pdtphys, t_seri, paprs, pplay, &
    652             cdragh,  coefh, yu1, yv1, ftsol, pctsrf, xlat, xlon,iflag_vdf_trac>=0,sh, &
    653             rh, pphi, ustar, wstar, ale_bl, ale_wake,  u10m, v10m, &
    654             tr_seri, source, d_tr_cl,d_tr_dec, zmasse)               !RomP
    655 
    656     CASE('inca')
     637    IF(ANY(types_trac == 'inca')) THEN
    657638       !    -- CHIMIE INCA  config_inca = aero or chem --
    658639       ! Appel fait en fin de phytrac pour avoir les emissions modifiees par
    659640       ! la couche limite et la convection avant le calcul de la chimie
    660641
    661     CASE('repr')
     642    ELSE IF(ANY(types_trac == 'repr')) THEN
    662643       !   -- CHIMIE REPROBUS --
    663644       CALL tracreprobus(pdtphys, gmtime, debutphy, julien, &
     
    666647            tr_seri)
    667648
    668     CASE('co2i')
     649    ELSE IF(ANY(types_trac == 'co2i')) THEN
    669650       !   -- CO2 interactif --
    670651       !   -- source is updated with FF and BB emissions
     
    675656            xlat, xlon, pphis, pphi, &
    676657            t_seri, pplay, paprs, tr_seri, source)
    677     CASE('inco')      ! Add ThL
     658    ELSE IF(ANY(types_trac == 'inco')) THEN      ! Add ThL
    678659       CALL tracco2i(pdtphys, debutphy, &
    679660            xlat, xlon, pphis, pphi, &
     
    681662
    682663#ifdef CPP_StratAer
    683     CASE('coag')
     664    ELSE IF(ANY(types_trac == 'coag')) THEN
    684665       !   --STRATOSPHERIC AER IN THE STRAT --
    685666       CALL traccoag(pdtphys, gmtime, debutphy, julien, &
     
    688669            tr_seri)
    689670#endif
    690 
    691     END SELECT
     671    ELSE IF(ANY(types_trac == 'lmdz')) THEN
     672       !    -- Traitement des traceurs avec traclmdz
     673       CALL traclmdz(nstep, julien, gmtime, pdtphys, t_seri, paprs, pplay, &
     674            cdragh,  coefh, yu1, yv1, ftsol, pctsrf, xlat, xlon,iflag_vdf_trac>=0,sh, &
     675            rh, pphi, ustar, wstar, ale_bl, ale_wake,  u10m, v10m, &
     676            tr_seri, source, d_tr_cl,d_tr_dec, zmasse)               !RomP
     677    END IF
    692678    !======================================================================
    693679    !       -- Calcul de l'effet de la convection --
     
    759745
    760746#ifdef CPP_StratAer
    761        IF (type_trac=='coag') THEN
     747       IF (ANY(types_trac=='coag')) THEN
    762748         ! initialize wet deposition flux of sulfur
    763749         budg_dep_wet_ocs(:)=0.0
     
    840826       !
    841827#ifdef CPP_StratAer
    842        IF (type_trac=='coag') THEN
     828       IF (ANY(types_trac=='coag')) THEN
    843829
    844830         ! initialize dry deposition flux of sulfur
     
    877863             !
    878864#ifdef CPP_StratAer
    879              IF (type_trac=='coag') THEN
     865             IF (ANY(types_trac=='coag')) THEN
    880866               ! compute dry deposition flux of sulfur (sum over gases and particles)
    881867               IF (it==id_OCS_strat) THEN
     
    962948
    963949#ifdef CPP_StratAer
    964          IF (type_trac=='coag') THEN
     950         IF (ANY(types_trac=='coag')) THEN
    965951           ! compute wet deposition flux of sulfur (sum over gases and
    966952           ! particles) and convert to kg(S)/m2/s
     
    11021088
    11031089    !    -- CHIMIE INCA  config_inca = aero or chem --
    1104     IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN  ! ModThL
     1090    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN  ! ModThL
    11051091
    11061092       CALL tracinca(&
  • LMDZ6/trunk/libf/phylmd/radiation_AR4.F90

    r3666 r4170  
    479479  USE dimphy
    480480  USE radiation_ar4_param, ONLY: rsun, rray
    481   USE infotrac_phy, ONLY: type_trac
     481  USE infotrac_phy, ONLY: types_trac
    482482#ifdef REPROBUS
    483483  USE chem_rep, ONLY: rsuntime, ok_suntime
     
    571571  ! If running with Reporbus, overwrite default values of RSUN.
    572572  ! Otherwise keep default values from radiation_AR4_param module.
    573   IF (type_trac=='repr') THEN
     573  IF (ANY(types_trac=='repr')) THEN
    574574#ifdef REPROBUS
    575575    IF (ok_suntime) THEN
     
    701701  USE dimphy
    702702  USE radiation_ar4_param, ONLY: rsun, rray
    703   USE infotrac_phy, ONLY: type_trac
     703  USE infotrac_phy, ONLY: types_trac
    704704#ifdef REPROBUS
    705705  USE chem_rep, ONLY: rsuntime, ok_suntime
     
    825825  ! If running with Reporbus, overwrite default values of RSUN.
    826826  ! Otherwise keep default values from radiation_AR4_param module.
    827   IF (type_trac=='repr') THEN
     827  IF (ANY(types_trac=='repr')) THEN
    828828#ifdef REPROBUS
    829829    IF (ok_suntime) THEN
     
    23132313  USE dimphy
    23142314  USE radiation_ar4_param, ONLY: tref, rt1, raer, at, bt, oct
    2315   USE infotrac_phy, ONLY: type_trac
     2315  USE infotrac_phy, ONLY: types_trac
    23162316#ifdef REPROBUS
    23172317  USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d
     
    26212621
    26222622
    2623         IF (type_trac=='repr') THEN
     2623        IF (ANY(types_trac=='repr')) THEN
    26242624#ifdef REPROBUS
    26252625          IF (ok_rtime2d) THEN
  • LMDZ6/trunk/libf/phylmd/radlwsw_m.F90

    r4116 r4170  
    4848  USE DIMPHY
    4949  USE assert_m, ONLY : assert
    50   USE infotrac_phy, ONLY : type_trac
     50  USE infotrac_phy, ONLY : types_trac
    5151  USE write_field_phy
    5252
     
    550550  PSCT = solaire/zdist/zdist
    551551
    552   IF (type_trac == 'repr') THEN
     552  IF (ANY(types_trac == 'repr')) THEN
    553553#ifdef REPROBUS
    554554    IF (iflag_rrtm==0) THEN
     
    634634    ENDDO
    635635
    636     IF (type_trac == 'repr') THEN
     636    IF (ANY(types_trac == 'repr')) THEN
    637637#ifdef REPROBUS
    638638       ndimozon = size(wo, 3)
  • LMDZ6/trunk/libf/phylmdiso/phyetat0.F90

    r4089 r4170  
    3131  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
    3232  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
    33   USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers
     33  USE infotrac_phy,     ONLY: nqtot, nbtr, types_trac, tracers
    3434  USE traclmdz_mod,     ONLY: traclmdz_from_restart
    3535  USE carbon_cycle_mod, ONLY: carbon_cycle_tr, carbon_cycle_cpl, co2_send
     
    468468!===========================================
    469469
    470   IF (type_trac == 'lmdz') THEN
     470!--OB now this is for co2i - ThL: and therefore also for inco
     471  IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
     472     IF (carbon_cycle_cpl) THEN
     473        ALLOCATE(co2_send(klon), stat=ierr)
     474        IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
     475        found=phyetat0_get(1,co2_send,"co2_send","co2 send",co2_ppm)
     476     ENDIF
     477  ELSE IF (ANY(types_trac == 'lmdz')) THEN
    471478     it = 0
    472479     DO iq = 1, nqtot
     
    477484     END DO
    478485     CALL traclmdz_from_restart(trs)
    479   ENDIF
    480 
    481 !--OB now this is for co2i - ThL: and therefore also for inco
    482   IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
    483      IF (carbon_cycle_cpl) THEN
    484         ALLOCATE(co2_send(klon), stat=ierr)
    485         IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
    486         found=phyetat0_get(1,co2_send,"co2_send","co2 send",co2_ppm)
    487      ENDIF
    488486  ENDIF
    489487
  • LMDZ6/trunk/libf/phylmdiso/phyredem.F90

    r4149 r4170  
    3939  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
    4040  USE traclmdz_mod, ONLY : traclmdz_to_restart
    41   USE infotrac_phy, ONLY: type_trac, nqtot, tracers, nbtr, niso
     41  USE infotrac_phy, ONLY: types_trac, nqtot, tracers, nbtr, niso
    4242#ifdef ISO
    4343#ifdef ISOVERIF
     
    345345
    346346
    347     ! trs from traclmdz_mod
    348     IF (type_trac == 'lmdz') THEN
    349        CALL traclmdz_to_restart(trs)
    350        it = 0
    351        DO iq = 1, nqtot
    352           IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
    353           it = it+1
    354           CALL put_field(pass,"trs_"//tracers(iq)%name, "", trs(:, it))
    355        END DO
    356     END IF
    357 
    358     IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
     347    IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
    359348       IF (carbon_cycle_cpl) THEN
    360349          IF (.NOT. ALLOCATED(co2_send)) THEN
     
    365354          CALL put_field(pass,"co2_send", "co2_ppm for coupling", co2_send)
    366355       END IF
     356
     357    ! trs from traclmdz_mod
     358    ELSE IF (ANY(types_trac == 'lmdz')) THEN
     359       CALL traclmdz_to_restart(trs)
     360       it = 0
     361       DO iq = 1, nqtot
     362          IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
     363          it = it+1
     364          CALL put_field(pass,"trs_"//tracers(iq)%name, "", trs(:, it))
     365       END DO
    367366    END IF
    368367
  • LMDZ6/trunk/libf/phylmdiso/phys_output_mod.F90

    r4149 r4170  
    3535    USE iophy
    3636    USE dimphy
    37     USE infotrac_phy, ONLY: nqtot, tracers, type_trac, niso, ntraciso=>ntiso
     37    USE infotrac_phy, ONLY: nqtot, tracers, niso, ntraciso=>ntiso
    3838    USE strings_mod,  ONLY: maxlen
    3939    USE ioipsl
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4143 r4170  
    3939    USE ioipsl_getin_p_mod, ONLY : getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac, nqCO2
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, types_trac, nqCO2
    4242    USE readTracFiles_mod, ONLY: addPhase
    4343    USE strings_mod,  ONLY: strIdx, strStack, int2str
     
    15391539       tau_overturning_th(:)=0.
    15401540
    1541        IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
     1541       IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
    15421542          ! jg : initialisation jusqu'au ces variables sont dans restart
    15431543          ccm(:,:,:) = 0.
     
    21512151       !c         ENDDO
    21522152       !
    2153        IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN                   ! ModThL
     2153       IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN  ! ModThL
    21542154#ifdef INCA
    21552155          CALL VTe(VTphysiq)
     
    22002200       ENDIF
    22012201       !
    2202        IF (type_trac == 'repr') THEN
     2202       IF (ANY(types_trac == 'repr')) THEN
    22032203#ifdef REPROBUS
    22042204          CALL chemini_rep(  &
     
    23162316
    23172317    ! Update time and other variables in Reprobus
    2318     IF (type_trac == 'repr') THEN
     2318    IF (ANY(types_trac == 'repr')) THEN
    23192319#ifdef REPROBUS
    23202320       CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     
    35823582          !
    35833583          !>jyg
    3584           IF (type_trac == 'repr') THEN
     3584          IF (ANY(types_trac == 'repr')) THEN
    35853585             nbtr_tmp=ntra
    35863586          ELSE
     
    51125112    ENDDO
    51135113
    5114     IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN      ! ModThL
     5114    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
    51155115#ifdef INCA
    51165116       CALL VTe(VTphysiq)
     
    51685168#endif
    51695169    ENDIF !type_trac = inca or inco
    5170     IF (type_trac == 'repr') THEN
     5170    IF (ANY(types_trac == 'repr')) THEN
    51715171#ifdef REPROBUS
    51725172    !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap)
     
    62646264    !
    62656265
    6266     IF (type_trac=='repr') THEN
     6266    IF (ANY(types_trac=='repr')) THEN
    62676267!MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod
    62686268!MM                               dans Reprobus
     
    64306430#endif
    64316431    !
    6432     IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
     6432    IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
    64336433#ifdef INCA
    64346434       CALL VTe(VTphysiq)
Note: See TracChangeset for help on using the changeset viewer.