Ignore:
Timestamp:
May 9, 2022, 12:35:40 PM (3 years ago)
Author:
dcugnet
Message:
  • Some variables are renamed or replaced by direct equivalents:
    • iso_indnum -> tracers(:)%iso_iName
    • niso_possibles -> niso
    • iqiso -> iqIsoPha ; index_trac -> itZonIso
    • ok_iso_verif -> isoCheck
    • ntraceurs_zone -> nzone ; ntraciso -> ntiso
    • qperemin -> min_qparent ; masseqmin -> min_qmass ; ratiomin -> min_ratio
  • Some renamed variables are only aliased with the older name (using USE <module>, ONLY: <oldName> => <newName>) in routines where they are repeated many times.
  • Few hard-coded indexes are now computed (examples: ilic, iso, ivap, irneb, iq_vap, iq_liq, iso_H2O, iso_HDO, iso_HTO, iso_O17, iso_O18).
  • The IF(isoCheck) test is now embedded in the check_isotopes_seq and check_isotopes_loc routines (lighter calling).
Location:
LMDZ6/trunk/libf/phylmd
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/calltherm.F90

    r4089 r4143  
    3030      USE print_control_mod, ONLY: prt_level,lunout
    3131#ifdef ISO
    32       use infotrac_phy, ONLY: ntraciso
     32      use infotrac_phy, ONLY: ntiso
    3333#ifdef ISOVERIF
    3434      USE isotopes_mod, ONLY: iso_eau,iso_HDO
     
    145145
    146146#ifdef ISO
    147       REAL xt_seri(ntraciso,klon,klev),xtmemoire(ntraciso,klon,klev)
    148       REAL d_xt_ajs(ntraciso,klon,klev)
    149       real d_xt_the(ntraciso,klon,klev)
     147      REAL xt_seri(ntiso,klon,klev),xtmemoire(ntiso,klon,klev)
     148      REAL d_xt_ajs(ntiso,klon,klev)
     149      real d_xt_the(ntiso,klon,klev)
    150150#ifdef DIAGISO
    151151      real q_the(klon,klev)
    152       real xt_the(ntraciso,klon,klev)
     152      real xt_the(ntiso,klon,klev)
    153153#endif
    154154      real qprec(klon,klev)
     
    205205                nbptspb=nbptspb+1
    206206#ifdef ISO
    207                 do ixt=1,ntraciso
     207                do ixt=1,ntiso
    208208                  xt_seri(ixt,i,k)=1.e-15*(xt_seri(ixt,i,k)/qprec(i,k))
    209209                  ! xt_seri(ixt,i,k)=1.e-15*(Rdefault(index_iso(ixt)))
     
    228228       call iso_verif_egalite_vect2D( &
    229229     &           xt_seri,q_seri, &
    230      &           'calltherm 174',ntraciso,klon,klev)
     230     &           'calltherm 174',ntiso,klon,klev)
    231231      endif !if (iso_eau.gt.0) then
    232232#endif   
     
    360360     &       +zdetr_therm(:,k)*fact(:)
    361361#ifdef ISO
    362             do ixt=1,ntraciso
     362            do ixt=1,ntiso
    363363              d_xt_the(ixt,:,k)=d_xt_the(ixt,:,k)*dtime*fact(:)
    364364            enddo
     
    398398      call iso_verif_aberrant_enc_vect2D( &
    399399     &        xt_seri,q_seri, &
    400      &        'calltherm 353, apres ajout d_xt_the',ntraciso,klon,klev)
     400     &        'calltherm 353, apres ajout d_xt_the',ntiso,klon,klev)
    401401      endif     
    402402#endif
     
    424424                nbptspb=nbptspb+1
    425425#ifdef ISO
    426                 do ixt=1,ntraciso
     426                do ixt=1,ntiso
    427427                  xt_seri(ixt,i,k)=1.e-15*(xtmemoire(ixt,i,k)/qmemoire(i,k))
    428428                enddo
     
    440440      call iso_verif_aberrant_enc_vect2D( &
    441441     &        xt_seri,q_seri, &
    442      &        'calltherm 393, apres bidouille q<0',ntraciso,klon,klev)
     442     &        'calltherm 393, apres bidouille q<0',ntiso,klon,klev)
    443443      endif     
    444444#endif
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r4138 r4143  
    2727   PUBLIC :: niso,    nzone,   nphas,   ntiso              !---  " " numbers + isotopes & tagging tracers number
    2828   PUBLIC :: itZonIso                                      !--- iq = function(tagging zone idx, isotope idx)
    29    PUBLIC :: iqTraPha                                      !--- idx of tagging tracer in iName = function(isotope idx, phase idx)
     29   PUBLIC :: iqIsoPha                                      !--- idx of tagging tracer in iName = function(isotope idx, phase idx)
    3030   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    3131   !=== FOR BOTH TRACERS AND ISOTOPES
    3232   PUBLIC :: getKey                                        !--- Get a key from "tracers" or "isotope"
    33 
    34    PUBLIC :: ntraciso, ntraceurs_zone, indnum_fn_num, use_iso, index_trac, iqiso
    35    PUBLIC :: niso_possibles, ok_iso_verif
    3633
    3734   INTERFACE isoSelect; MODULE PROCEDURE isoSelectByIndex, isoSelectByName; END INTERFACE isoSelect
     
    9693!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    9794!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3  |
    98 !  | iqTraPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
     95!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    9996!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
    10097!  +-----------------+--------------------------------------------------+--------------------+-----------------+
     
    126123                                             nphas, ntiso, &    !--- NUMBER OF PHASES AND ISOTOPES + ISOTOPIC TAGGING TRACERS
    127124                                            itZonIso(:,:), &    !--- INDEX IN "isoTrac" AS f(tagging zone idx,  isotope idx)
    128                                             iqTraPha(:,:)       !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
    129 !$OMP THREADPRIVATE(isotope, ixIso,iH2O, isoCheck, isoKeys, isoName,isoZone,isoPhas, niso,nzone,nphas,ntiso, itZonIso,iqTraPha)
     125                                            iqIsoPha(:,:)       !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
     126!$OMP THREADPRIVATE(isotope, ixIso,iH2O, isoCheck, isoKeys, isoName,isoZone,isoPhas, niso,nzone,nphas,ntiso, itZonIso,iqIsoPha)
    130127
    131128   !=== VARIABLES FOR ISOTOPES INITIALIZATION AND FOR INCA
     
    133130                                             pbl_flg(:)         !--- Boundary layer activation ; needed for INCA        (nbtr)
    134131!$OMP THREADPRIVATE(conv_flg, pbl_flg)
    135 
    136    !--- Aliases for older names + quantities to be removed             (will be replaced by:)
    137    INTEGER, POINTER, SAVE :: ntraciso, ntraceurs_zone           !--- -> ntiso, nzone
    138 !$OMP THREADPRIVATE         (ntraciso, ntraceurs_zone)   
    139    INTEGER, POINTER, SAVE :: index_trac(:,:), iqiso(:,:)        !--- -> itZonIso, iqTraPha
    140 !$OMP THREADPRIVATE         (index_trac,      iqiso)
    141    INTEGER, SAVE :: niso_possibles                              !--- suppressed (use effective niso instead)
    142 !$OMP THREADPRIVATE(niso_possibles)
    143    LOGICAL, SAVE :: ok_iso_verif                                !--- -> isoCheck
    144 !$OMP THREADPRIVATE(ok_iso_verif)
    145    LOGICAL, SAVE, ALLOCATABLE :: use_iso(:)                     !--- suppressed
    146 !$OMP THREADPRIVATE             (use_iso)
    147    INTEGER, SAVE, ALLOCATABLE :: indnum_fn_num(:)
    148 !$OMP THREADPRIVATE             (indnum_fn_num)
    149132
    150133#ifdef CPP_StratAer
     
    190173
    191174   !=== Determine selected isotopes class related quantities:
    192    !    ixIso, isotope, niso,isoKeys, ntiso,isoName, nzone,isoZone, nphas,isoPhas, itZonIso, iqTraPha, isoCheck
     175   !    ixIso, isotope, niso,isoKeys, ntiso,isoName, nzone,isoZone, nphas,isoPhas, itZonIso, iqIsoPha, isoCheck
    193176   IF(.NOT.isoSelect('H2O')) iH2O = ixIso
    194177   IF(prt_level > 1) THEN
     
    221204   END IF
    222205#endif
    223 
    224    !--- Isotopic quantities (to be removed soon)
    225    ntraciso       => ntiso
    226    ntraceurs_zone => nzone
    227    iqiso          => iqTraPha
    228    index_trac     => itZonIso
    229    ok_iso_verif   = isoCheck
    230    niso_possibles = SIZE(tnom_iso)
    231    indnum_fn_num  = [(strIdx(isotope%keys(:)%name, tnom_iso(ixt)), ixt=1, niso_possibles)]
    232    use_iso        = indnum_fn_num /= 0
    233206#ifdef ISOVERIF
    234207   CALL msg('iso_iName = '//strStack(int2str(PACK(tracers(:)%iso_iName, MASK=tracers(:)%iso_iGroup==iH2O))), modname)
     
    275248   isoPhas  => isotope%phase;    nphas    => isotope%nphas
    276249   itZonIso => isotope%itZonIso; isoCheck => isotope%check
    277    iqTraPha => isotope%iqTraPha
     250   iqIsoPha => isotope%iqIsoPha
    278251END FUNCTION isoSelectByIndex
    279252!==============================================================================================================================
  • LMDZ6/trunk/libf/phylmd/phys_output_mod.F90

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

    r4120 r4143  
    2525
    2626    USE dimphy, ONLY: klon, klev, klevp1
    27     USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, tracers, niso, ntraciso
     27    USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_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
     
    25982598
    25992599#ifdef ISO
    2600     do ixt=1,ntraciso
     2600    do ixt=1,ntiso
    26012601!        write(*,*) 'ixt'
    26022602        IF (vars_defined) zx_tmp_fi2d(:) = xtrain_fall(ixt,:) + xtsnow_fall(ixt,:)
     
    26522652
    26532653    !write(*,*) 'phys_output_write_mod 2531'
    2654     enddo !do ixt=1,ntraciso   
     2654    enddo
    26552655#endif
    26562656
  • LMDZ6/trunk/libf/phylmd/phys_state_var_mod.F90

    r4088 r4143  
    499499USE infotrac_phy, ONLY : nbtr
    500500#ifdef ISO
    501 USE infotrac_phy, ONLY : ntraciso,niso
     501USE infotrac_phy, ONLY : ntraciso=>ntiso,niso
    502502#endif
    503503USE indice_sol_mod
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4140 r4143  
    444444    !======================================================================
    445445    !
    446     INTEGER ivap          ! indice de traceurs pour vapeur d'eau
    447     PARAMETER (ivap=1)
    448     INTEGER iliq          ! indice de traceurs pour eau liquide
    449     PARAMETER (iliq=2)
    450     INTEGER isol          ! indice de traceurs pour eau glace
    451     PARAMETER (isol=3)
    452     INTEGER irneb         ! indice de traceurs pour fraction nuageuse LS (optional)
    453     PARAMETER (irneb=4)   
     446    ! indices de traceurs eau vapeur, liquide, glace, fraction nuageuse LS (optional)
     447    INTEGER,SAVE :: ivap, iliq, isol, irneb
     448!$OMP THREADPRIVATE(ivap, iliq, isol, irneb)
    454449    !
    455450    !
     
    12551250
    12561251    IF (first) THEN
     1252       ivap = strIdx(tracers(:)%name, addPhase('H2O', 'g'))
     1253       iliq = strIdx(tracers(:)%name, addPhase('H2O', 'l'))
     1254       isol = strIdx(tracers(:)%name, addPhase('H2O', 's'))
     1255       irneb= strIdx(tracers(:)%name, addPhase('H2O', 'r'))
    12571256       CALL init_etat0_limit_unstruct
    12581257       IF (.NOT. create_etat0_limit) CALL init_limit_read(days_elapsed)
  • LMDZ6/trunk/libf/phylmd/thermcell_main.F90

    r4133 r4143  
    2222
    2323#ifdef ISO
    24   USE infotrac_phy, ONLY : ntraciso
     24  USE infotrac_phy, ONLY : ntiso
    2525#ifdef ISOVERIF
    2626  USE isotopes_mod, ONLY : iso_eau,iso_HDO
     
    140140
    141141#ifdef ISO
    142       REAL xtpo(ntraciso,ngrid,nlay),xtpdoadj(ntraciso,ngrid,nlay)
    143       REAL xtzo(ntraciso,ngrid,nlay)
     142      REAL xtpo(ntiso,ngrid,nlay),xtpdoadj(ntiso,ngrid,nlay)
     143      REAL xtzo(ntiso,ngrid,nlay)
    144144      REAL xtpdoadj_tmp(ngrid,nlay)
    145145      REAL xtpo_tmp(ngrid,nlay)
     
    368368     &           zlev,lmax,zmax,zmax0,zmix,wmax)
    369369! Attention, w2 est transforme en sa racine carree dans cette routine
    370 ! Le probleme vient du fait que linter et lmix sont souvent égaux à 1.
     370! Le probleme vient du fait que linter et lmix sont souvent egaux a 1.
    371371      wmax_tmp=0.
    372372      do  l=1,nlay
     
    488488
    489489#ifdef ISO
    490         ! C Risi: on utilise directement la même routine
    491         do ixt=1,ntraciso
     490        ! C Risi: on utilise directement la meme routine
     491        do ixt=1,ntiso
    492492          do ll=1,nlay
    493493            DO ig=1,ngrid
     
    503503            enddo
    504504          enddo
    505         enddo !do ixt=1,ntraciso
     505        enddo
    506506#endif
    507507
     
    749749! nrlmd le 10/04/2012   Transport de la TKE par le thermique moyen pour la fermeture en ALP
    750750!                       On transporte pbl_tke pour donner therm_tke
    751 !                       Copie conforme de la subroutine DTKE dans physiq.F écrite par Frederic Hourdin
     751!                       Copie conforme de la subroutine DTKE dans physiq.F ecrite par Frederic Hourdin
    752752
    753753!=======================================================================
Note: See TracChangeset for help on using the changeset viewer.