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/dyn3d_common/infotrac.F90

    r4130 r4143  
    2828   PUBLIC :: isoName, isoZone, isoPhas                     !--- Isotopes and tagging zones names, phases
    2929   PUBLIC :: niso,    nzone,   nphas,   ntiso              !---  " " numbers + isotopes & tagging tracers number
    30    PUBLIC :: itZonIso, index_trac                          !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
    31    PUBLIC :: iqTraPha, iqiso                               !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
     30   PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
     31   PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
    3232   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    3333   !=== FOR BOTH TRACERS AND ISOTOPES
    3434   PUBLIC :: getKey                                        !--- Get a key from "tracers" or "isotope"
    35 
    36    !=== OLD QUANTITIES OR ALIASES FOR OLDER NAMES (TO BE REMOVED SOON)
    37    PUBLIC :: ntraciso, ntraceurs_zone
    38    PUBLIC :: ok_iso_verif, use_iso
    39    PUBLIC :: iso_num, iso_indnum, indnum_fn_num, niso_possibles
    40    PUBLIC :: qperemin, masseqmin, ratiomin
    4135
    4236   INTERFACE isoSelect; MODULE PROCEDURE isoSelectByIndex, isoSelectByName; END INTERFACE isoSelect
     
    10195!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    10296!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3  |
    103 !  | iqTraPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
     97!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    10498!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
    10599!  +-----------------+--------------------------------------------------+--------------------+-----------------+
     
    131125                                             nphas, ntiso, &    !--- NUMBER OF PHASES AND ISOTOPES + ISOTOPIC TAGGING TRACERS
    132126                                            itZonIso(:,:), &    !--- INDEX IN "isoTrac" AS f(tagging zone idx,  isotope idx)
    133                                             iqTraPha(:,:)       !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
    134 
    135    !--- Aliases for older names + quantities to be removed soon
    136    INTEGER,                 SAVE, POINTER ::  index_trac(:,:)   ! numero ixt en fn izone, indnum entre 1 et niso
    137    INTEGER,                 SAVE, POINTER ::  iqiso(:,:)        ! donne indice iq en fn de (ixt,phase)
    138    INTEGER,                 SAVE, POINTER :: ntraciso, ntraceurs_zone
    139    REAL,    SAVE :: qperemin, masseqmin, ratiomin
    140    INTEGER, SAVE :: niso_possibles
    141    LOGICAL, SAVE :: ok_iso_verif
    142    LOGICAL, SAVE, ALLOCATABLE ::       use_iso(:)
    143    INTEGER, SAVE, ALLOCATABLE ::       iso_num(:)               !--- idx in [1,niso_possibles] = f(1<=iq <=nqtot)
    144    INTEGER, SAVE, ALLOCATABLE ::    iso_indnum(:)               !--- idx in [1,niso]           = f(1<=iq <=nqtot)
    145    INTEGER, SAVE, ALLOCATABLE :: indnum_fn_num(:)               !--- idx in [1,niso]           = f(1<=idx<=niso_possibles)
     127                                            iqIsoPha(:,:)       !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
    146128
    147129   !=== VARIABLES FOR ISOTOPES INITIALIZATION AND FOR INCA
     
    359341   DEALLOCATE(tnom_0, tnom_transp)
    360342#ifdef INCA
    361    DEALLOCATE(hadv_inca, vadv_inca, solsym_inca)
     343   DEALLOCATE(hadv_inca, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
    362344#endif
    363345
     
    377359      nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    378360      IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
    379       ALLOCATE(hadv(nqtrue), conv_flg(nbtr), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    380       ALLOCATE(vadv(nqtrue),  pbl_flg(nbtr), vadv_inca(nqINCA),  pbl_flg_inca(nqINCA))
     361      ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
     362      ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA),  pbl_flg_inca(nqINCA))
    381363      CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
    382       !--- Passive CO2 tracer is at position 1 because: H2O has been removed ; nqCO2/=0 in "inco" case only
    383       conv_flg(1:nbtr) = [(1,          k=1, nqCO2), conv_flg_inca]
    384        pbl_flg(1:nbtr) = [(1,          k=1, nqCO2),  pbl_flg_inca]
    385364      ALLOCATE(ttr(nqtrue))
    386365      ttr(1:nqo+nqCO2)                    = tracers
     
    407386      lerr = getKey('hadv', hadv, ky=tracers(:)%keys)
    408387      lerr = getKey('vadv', vadv, ky=tracers(:)%keys)
    409       ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr))
    410       conv_flg(1:nbtr) = [(1, it=1, nbtr)]                           !--- Convection activated for all tracers
    411        pbl_flg(1:nbtr) = [(1, it=1, nbtr)]                           !--- Boundary layer activated for all tracers
    412388   !---------------------------------------------------------------------------------------------------------------------------
    413389   END IF
     
    531507   nbtr    = nbtr -nqo*   ntiso             !--- ISOTOPIC TAGGING TRACERS ARE NOT PASSED TO THE PHYSICS
    532508   nqtottr = nqtot-nqo*(1+ntiso)            !--- NO H2O-FAMILY    TRACER  IS      PASSED TO THE PHYSICS
    533 
    534    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr))
    535 #ifndef INCA
    536    conv_flg(1:nbtr) = 1                                              !--- Convection activated for all tracers
    537     pbl_flg(1:nbtr) = 1                                              !--- Boundary layer activated for all tracers
    538 #else
    539    !--- Passive CO2 tracer is at position 1 because: H2O has been removed ; nqCO2/=0 in "inco" case only
    540    conv_flg(1:nbtr) = [(1, ic=1, nqCO2),conv_flg_inca]
    541     pbl_flg(1:nbtr) = [(1, ic=1, nqCO2), pbl_flg_inca]
    542 #endif
    543509
    544510ELSE
     
    578544END IF
    579545
     546   !--- Convection / boundary layer activation for all tracers
     547   ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
     548   ALLOCATE( pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
     549
    580550   !--- Note: nqtottr can differ from nbtr when nmom/=0
    581551!   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
    582552!      CALL abort_gcm('infotrac_init', 'pb dans le calcul de nqtottr', 1)
    583 
    584    !--- Some aliases to be removed later
    585    ntraciso       => ntiso
    586    ntraceurs_zone => nzone
    587    qperemin       =  min_qParent
    588    masseqmin      =  min_qMass
    589    ratiomin       =  min_ratio
    590    iqiso          => iqTraPha
    591    index_trac     => itZonIso
    592553
    593554   !=== DISPLAY THE RESULTS
     
    704665   USE readTracFiles_mod, ONLY: tnom_iso => newH2OIso
    705666   IMPLICIT NONE
    706    INTEGER, ALLOCATABLE  :: nb_iso(:), nb_tiso(:), nb_zone(:), ix(:)
     667   INTEGER, ALLOCATABLE  :: nb_iso(:), nb_tiso(:), nb_zone(:), ix(:), iy(:)
    707668   INTEGER               :: ii, ip, iq, it, iz, ixt
    708669   TYPE(isot_type), POINTER :: i
     
    765726   END DO
    766727
    767    niso_possibles = SIZE(tnom_iso)
    768 !   ix = strIdx(tnom_iso, i%trac)
    769 !   tnat        = tnat0       (PACK(ix, MASK=ix/=0))
    770 !   alpha_ideal = alpha_ideal0(PACK(ix, MASK=ix/=0))
    771    tnat        = tnat0
    772    alpha_ideal = alpha_ideal0
     728   !--- Get vectors, one value each "isotope%trac" element (and in the same order)
     729   ix = strIdx(tnom_iso, i%trac)
     730   iy =   PACK(ix, MASK = ix/=0)
     731   tnat        = tnat0       (iy)
     732   alpha_ideal = alpha_ideal0(iy)
    773733
    774734   !--- Tests
     
    786746
    787747   !--- Table: index in "qx(:)" of an isotope, knowing its indices "it","ip" in "isotope%iName,%iPhase"
    788    i%iqTraPha = RESHAPE([((strIdx(t%name, TRIM(addPhase(i%trac(it),ip,i%phase))),it=1,i%ntiso),ip=1,i%nphas)],[i%ntiso,i%nphas])
     748   i%iqIsoPha = RESHAPE([((strIdx(t%name, TRIM(addPhase(i%trac(it),ip,i%phase))),it=1,i%ntiso),ip=1,i%nphas)],[i%ntiso,i%nphas])
    789749
    790750   !--- Table: index in "isotope%tracs(:)%name" of an isotopic tagging tracer, knowing its indices "iz","ip" in "isotope%iZone,%iName"
    791751   i%itZonIso = RESHAPE([((strIdx(i%trac,TRIM(i%trac(it))//'_'//TRIM(i%zone(iz))),iz=1,i%nzone),it=1,i%niso )],[i%nzone,i%niso])
    792752
    793    DO it=1,i%ntiso; CALL msg('iqTraPha('//TRIM(int2str(it))//',:) = '//strStack(int2str(i%iqTraPha(it,:))), modname); END DO
     753   DO it=1,i%ntiso; CALL msg('iqIsoPha('//TRIM(int2str(it))//',:) = '//strStack(int2str(i%iqIsoPha(it,:))), modname); END DO
    794754   DO iz=1,i%nzone; CALL msg('itZonIso('//TRIM(int2str(iz))//',:) = '//strStack(int2str(i%itZonIso(iz,:))), modname); END DO
    795 
    796    !--- Isotopic quantities (to be removed soon)
    797    ok_iso_verif  = i%check
    798    niso_possibles = SIZE(tnom_iso)
    799    iso_num       = [(strIdx(tnom_iso(:),    strHead(delPhase(tracers(iq)%name), '_')), iq=1, nqtot)]
    800    iso_indnum    = [(strIdx(i%keys(:)%name, strHead(delPhase(tracers(iq)%name), '_')), iq=1, nqtot)]
    801    indnum_fn_num = [(strIdx(i%keys(:)%name, tnom_iso(ixt)), ixt=1, niso_possibles)]
    802    use_iso       = indnum_fn_num /= 0            !--- .TRUE. for the effectively used isotopes of the possible isotopes list
    803755
    804756   !--- Finalize :
     
    845797   isoPhas  => isotope%phase;    nphas    => isotope%nphas
    846798   itZonIso => isotope%itZonIso; isoCheck => isotope%check
    847    iqTraPha => isotope%iqTraPha
     799   iqIsoPha => isotope%iqIsoPha
    848800END FUNCTION isoSelectByIndex
    849801!==============================================================================================================================
Note: See TracChangeset for help on using the changeset viewer.