Ignore:
Timestamp:
May 9, 2022, 12:35:40 PM (2 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).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/cv30_routines.F90

    r4050 r4143  
    165165    )
    166166#ifdef ISO
    167     USE infotrac_phy, ONLY: ntraciso   
     167    USE infotrac_phy, ONLY: ntraciso=>ntiso
    168168#endif
    169169  IMPLICIT NONE
     
    370370
    371371#ifdef ISO
    372 USE infotrac_phy, ONLY: ntraciso
     372USE infotrac_phy, ONLY: ntraciso=>ntiso
    373373USE isotopes_mod, ONLY: pxtmelt,pxtice,pxtmin,pxtmax,cond_temp_env, &
    374374        iso_eau,iso_HDO, ridicule
     
    947947  USE print_control_mod, ONLY: lunout
    948948#ifdef ISO
    949     use infotrac_phy, ONLY: ntraciso
     949    use infotrac_phy, ONLY: ntraciso=>ntiso
    950950    use isotopes_mod, ONLY: essai_convergence, iso_eau,iso_HDO
    951951#ifdef ISOVERIF
     
    11331133    ! epmax_cape: ajout arguments
    11341134#ifdef ISO
    1135 use infotrac_phy, ONLY: ntraciso
     1135use infotrac_phy, ONLY: ntraciso=>ntiso
    11361136USE isotopes_mod, ONLY: pxtmelt,pxtice,pxtmin,pxtmax,cond_temp_env, iso_eau,iso_HDO
    11371137USE isotopes_routines_mod, ONLY: condiso_liq_ice_vectall
     
    18281828
    18291829#ifdef ISO
    1830 use infotrac_phy, ONLY: ntraciso,niso,index_trac
     1830use infotrac_phy, ONLY: ntraciso=>ntiso,niso,itZonIso
    18311831USE isotopes_mod, ONLY: pxtmelt,pxtice,pxtmin,pxtmax, iso_eau,iso_HDO, &
    18321832        ridicule
     
    26162616        call iso_verif_traceur(xtclw(1,il,im), &
    26172617     &          'condiso_liq_ice_vectiso_trac 358')
    2618         if (iso_verif_positif_nostop(xtclw(index_trac( &
     2618        if (iso_verif_positif_nostop(xtclw(itZonIso( &
    26192619     &           izone_cond,iso_eau),i,k)-xtclw(iso_eau,i,k) &
    26202620     &           ,'cv30_routines 909').eq.1) then
     
    26242624     &             niso,ntraciso,index_zone,izone_cond       
    26252625               stop
    2626          endif !if (iso_verif_positif_nostop(xtclw(index_trac(
     2626         endif !if (iso_verif_positif_nostop(xtclw(itZonIso(
    26272627#endif             
    26282628         enddo !do il = 1, ncum   
     
    26472647     &          )
    26482648#ifdef ISO
    2649     use infotrac_phy, ONLY: ntraciso
     2649    use infotrac_phy, ONLY: ntraciso=>ntiso
    26502650    use isotopes_mod, ONLY: essai_convergence, iso_eau,iso_HDO,ridicule
    26512651    use isotopes_routines_mod, ONLY: appel_stewart_vectall
     
    26592659#ifdef ISOTRAC
    26602660    use isotrac_mod, only: option_cond,izone_cond
    2661     use infotrac_phy, ONLY: index_trac
     2661    use infotrac_phy, ONLY: itZonIso
    26622662#ifdef ISOVERIF
    26632663    use isotopes_verif_mod, ONLY: iso_verif_traceur_justmass, &
     
    29382938           ! on verifie que tout le detrainement est tagge condensat
    29392939           if (iso_verif_positif_nostop( &
    2940      &          xtwdtrain(index_trac(izone_cond,iso_eau),il) &
     2940     &          xtwdtrain(itZonIso(izone_cond,iso_eau),il) &
    29412941     &          -xtwdtrain(iso_eau,il), &
    29422942     &          'cv30_routines 2795').eq.1) then
     
    32003200!        if (option_tmin.ge.1) then
    32013201!           call iso_verif_positif(xtwater(
    3202 !     :           index_trac(izone_cond,iso_eau),il,i+1)
     3202!     :           itZonIso(izone_cond,iso_eau),il,i+1)
    32033203!     :           -xtwater(iso_eau,il,i+1),
    32043204!     :          'cv30_routines 3083')
     
    32593259!        if (option_tmin.ge.1) then
    32603260!         call iso_verif_positif(xtwater(
    3261 !     :           index_trac(izone_cond,iso_eau),il,i)
     3261!     :           itZonIso(izone_cond,iso_eau),il,i)
    32623262!     :           -xtwater(iso_eau,il,i),
    32633263!     :          'cv30_routines 3143')
     
    33693369     &                    )
    33703370#ifdef ISO
    3371     use infotrac_phy, ONLY: ntraciso,niso, &
    3372 &       ntraceurs_zone,index_trac
     3371    use infotrac_phy, ONLY: ntraciso=>ntiso, niso, nzone, itZonIso
    33733372    use isotopes_mod, ONLY: essai_convergence,ridicule,iso_eau,iso_HDO,iso_O18
    33743373#ifdef ISOVERIF
     
    50035002          do iiso = 1, niso
    50045003             
    5005              ixt_ddft=index_trac(izone_ddft,iiso) 
     5004             ixt_ddft=itZonIso(izone_ddft,iiso) 
    50065005             if (mp(il,i).gt.mp(il,i+1)) then
    50075006                fxtYe(iiso)=0.01*grav*dpinv*mp(il,i) &
     
    50165015     &              -mp(il,i)*(xtp(iiso,il,i)-xt(iiso,il,i-1)))
    50175016       
    5018              ixt_poubelle=index_trac(izone_poubelle,iiso)
     5017             ixt_poubelle=itZonIso(izone_poubelle,iiso)
    50195018             fxt(ixt_ddft,il,i)=fxt(ixt_ddft,il,i)+fxtYe(iiso)
    50205019             fxt(ixt_poubelle,il,i)=fxt(ixt_poubelle,il,i) &
     
    50335032     &              -mp(il,i)*(xtp(iiso,il,i)-xt(iiso,il,i-1)))
    50345033
    5035                 ixt_ddft=index_trac(izone_ddft,iiso)
     5034                ixt_ddft=itZonIso(izone_ddft,iiso)
    50365035                fxtYe(iiso)=0.01*grav*dpinv*mp(il,i) &
    50375036     &           *(xt(ixt_ddft,il,i-1)-xt(ixt_ddft,il,i))
    50385037                fxt(ixt_ddft,il,i)=fxt(ixt_ddft,il,i)+fxtYe(iiso) 
    50395038
    5040                ixt_revap=index_trac(izone_revap,iiso) 
     5039               ixt_revap=itZonIso(izone_revap,iiso) 
    50415040               fxt_revap(iiso)=0.01*grav*dpinv*(mp(il,i+1)* &
    50425041     &                  (xtp(ixt_revap,il,i+1)-xt(ixt_revap,il,i)) &
     
    50495048     &                   -xt(ixt_ddft,il,i)-xt(ixt_revap,il,i)
    50505049                if (Xe(iiso).gt.ridicule) then
    5051                   do izone=1,ntraceurs_zone
     5050                  do izone=1,nzone
    50525051                   if ((izone.ne.izone_revap).and. &
    50535052     &                   (izone.ne.izone_ddft)) then
    5054                     ixt=index_trac(izone,iiso)
     5053                    ixt=itZonIso(izone,iiso)
    50555054                    fxt(ixt,il,i)=fxt(ixt,il,i) &
    50565055     &                   +xt(ixt,il,i)/Xe(iiso)*fxtXe(iiso)
    50575056                   endif !if ((izone.ne.izone_revap).and.
    5058                   enddo !do izone=1,ntraceurs_zone   
     5057                  enddo !do izone=1,nzone   
    50595058#ifdef ISOVERIF
    50605059!                write(*,*) 'iiso=',iiso
     
    50785077                endif
    50795078#endif                   
    5080                 do izone=1,ntraceurs_zone
     5079                do izone=1,nzone
    50815080                   if ((izone.ne.izone_revap).and. &
    50825081     &                   (izone.ne.izone_ddft)) then                   
    5083                     ixt=index_trac(izone,iiso)
     5082                    ixt=itZonIso(izone,iiso)
    50845083                    if (izone.eq.izone_poubelle) then
    50855084                      fxt(ixt,il,i)=fxt(ixt,il,i)+fxtXe(iiso)
     
    50885087                    endif !if (izone.eq.izone_poubelle) then
    50895088                   endif !if ((izone.ne.izone_revap).and.
    5090                 enddo !do izone=1,ntraceurs_zone
     5089                enddo !do izone=1,nzone
    50915090#ifdef ISOVERIF
    50925091                  call iso_verif_traceur_justmass(fxt(1,il,i), &
     
    52375236        enddo !do ixt = 1+niso,ntraciso
    52385237!        write(*,*) 'tmp cv3_yield 4165: i,il=',i,il
    5239 !        ixt_poubelle=index_trac(izone_poubelle,iso_eau)
    5240 !        ixt_ddft=index_trac(izone_ddft,iso_eau)
     5238!        ixt_poubelle=itZonIso(izone_poubelle,iso_eau)
     5239!        ixt_ddft=itZonIso(izone_ddft,iso_eau)
    52415240!        write(*,*) 'delt*fxt(ixt_poubelle,il,i)=',
    52425241!     :           delt*fxt(ixt_poubelle,il,i)
     
    52445243!        write(*,*) 'xt(iso_eau,il,i)=',xt(iso_eau,il,i)
    52455244          do iiso = 1, niso
    5246              ixt_poubelle=index_trac(izone_poubelle,iiso)
    5247              ixt_ddft=index_trac(izone_ddft,iiso) 
     5245             ixt_poubelle=itZonIso(izone_poubelle,iiso)
     5246             ixt_ddft=itZonIso(izone_ddft,iiso) 
    52485247             if (mp(il,i).gt.mp(il,i+1)) then
    52495248                fxtYe(iiso)=0.01*grav*dpinv*mp(il,i) &
     
    61116110
    61126111#ifdef ISO
    6113     use infotrac_phy, ONLY: ntraciso
     6112    use infotrac_phy, ONLY: ntraciso=>ntiso
    61146113#ifdef ISOVERIF
    61156114    use isotopes_verif_mod, ONLY: Tmin_verif,iso_verif_aberrant, &
Note: See TracChangeset for help on using the changeset viewer.