Ignore:
Timestamp:
Dec 23, 2021, 6:54:17 PM (4 years ago)
Author:
dcugnet
Message:

Second commit for new tracers.

  • include most of the keys in the tracers descriptor vector "tracers(:)".
  • fix in phylmdiso/cv3_routines: fq_* variables were used where their fxt_* counterparts were expected.
  • multiple IF(nqdesc(iq)>0) and IF(nqfils(iq)>0) tests suppressed, because they are not needed: "do ... enddo" loops with 0 upper bound are not executed.
  • remove French accents from comments (encoding problem) in phylmdiso/cv3_routines and phylmdiso/cv30_routines.
  • modifications in "isotopes_verif_mod", where the call to function "iso_verif_tag17_q_deltad_chn" in "iso_verif_tag17_q_deltad_chn" was not detected at linking stage, although defined in the same module (?).
Location:
LMDZ6/trunk/libf/phylmd
Files:
4 edited

Legend:

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

    r4046 r4050  
    5151  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
    5252!$OMP THREADPRIVATE(niadv)
    53 
    54 ! CRisi: tableaux de fils
    55   INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqfils
    56   INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les générations
    57   INTEGER, SAVE :: nqdesc_tot
    58   INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE    :: iqfils
    59   INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iqpere
    60 !$OMP THREADPRIVATE(nqfils,nqdesc,nqdesc_tot,iqfils,iqpere)
    6153
    6254! conv_flg(it)=0 : convection desactivated for tracer number it
     
    8476    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
    8577!$OMP THREADPRIVATE(iqiso)
    86     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
    87 !$OMP THREADPRIVATE(iso_num)
    8878    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
    8979!$OMP THREADPRIVATE(iso_indnum)
    90     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  zone_num ! donne numéro de la zone de tracage en fn de nqtot
    91 !$OMP THREADPRIVATE(zone_num)
    92     INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  phase_num ! donne numéro de la zone de tracage en fn de nqtot
    93 !$OMP THREADPRIVATE(phase_num)
    9480    INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numéro d isotope entre 1 et niso_possibles
    9581!$OMP THREADPRIVATE(indnum_fn_num)
     
    10692  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqtottr_,nqCO2_,tracers_,type_trac_,&
    10793                               niadv_,conv_flg_,pbl_flg_,solsym_,&
    108                                nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
    10994                               ok_isotopes_,ok_iso_verif_,ok_isotrac_,&
    11095                               ok_init_iso_,niso_possibles_,tnat_,&
    111                                alpha_ideal_,use_iso_,iqiso_,iso_num_,&
    112                                iso_indnum_,zone_num_,phase_num_,&
     96                               alpha_ideal_,use_iso_,iqiso_,iso_indnum_,&
    11397                               indnum_fn_num_,index_trac_,&
    11498                               niso_,ntraceurs_zone_,ntraciso_,itr_indice_&
     
    143127    CHARACTER(len=*),INTENT(IN) :: solsym_(nbtr_)
    144128    ! Isotopes:
    145     INTEGER,INTENT(IN) :: nqfils_(nqtot_)
    146     INTEGER,INTENT(IN) :: nqdesc_(nqtot_)
    147     INTEGER,INTENT(IN) :: nqdesc_tot_
    148     INTEGER,INTENT(IN) :: iqfils_(nqtot_,nqtot_)
    149     INTEGER,INTENT(IN) :: iqpere_(nqtot_)
    150129    LOGICAL,INTENT(IN) :: ok_isotopes_
    151130    LOGICAL,INTENT(IN) :: ok_iso_verif_
     
    157136    LOGICAL,INTENT(IN) :: use_iso_(niso_possibles_)
    158137    INTEGER,INTENT(IN) :: iqiso_(ntraciso_,nqo_)
    159     INTEGER,INTENT(IN) :: iso_num_(nqtot_)
    160138    INTEGER,INTENT(IN) :: iso_indnum_(nqtot_)
    161     INTEGER,INTENT(IN) :: zone_num_(nqtot_)
    162     INTEGER,INTENT(IN) :: phase_num_(nqtot_)
    163139    INTEGER,INTENT(IN) :: indnum_fn_num_(niso_possibles_)
    164140    INTEGER,INTENT(IN) :: index_trac_(ntraceurs_zone_,niso_)
     
    169145
    170146    CHARACTER(LEN=30) :: modname="init_infotrac_phy"
     147    INTEGER :: iq
    171148
    172149    nqtot=nqtot_
     
    176153    nqtottr=nqtottr_
    177154    ALLOCATE(tracers(nqtot)); tracers(:) = tracers_(:)
     155    tracers(:)%isAdvected = tracers(:)%iadv  >   0
     156!    tracers(:)%isH2Ofamily = delPhase(tracers(:)%gen0Name) == 'H2O'
     157    tracers(:)%isH2Ofamily = [(tracers(iq)%gen0Name(1:3) == 'H2O', iq=1, nqtot)]
    178158#ifdef CPP_StratAer
    179159    nbtr_bin=nbtr_bin_
     
    216196   
    217197    IF (ok_isotopes) THEN
    218       ALLOCATE(nqfils(nqtot))
    219       nqfils(:)=nqfils_(:)
    220       ALLOCATE(nqdesc(nqtot))
    221       nqdesc(:)=nqdesc_(:)
    222       nqdesc_tot=nqdesc_tot_
    223       ALLOCATE(iqfils(nqtot,nqtot))
    224       iqfils(:,:)=iqfils_(:,:)
    225       ALLOCATE(iqpere(nqtot))
    226       iqpere(:)=iqpere_(:)
    227    
    228198      tnat(:)=tnat_(:)
    229199      alpha_ideal(:)=alpha_ideal_(:)
     
    232202      ALLOCATE(iqiso(ntraciso,nqo))
    233203      iqiso(:,:)=iqiso_(:,:)
    234       ALLOCATE(iso_num(nqtot))
    235       iso_num(:)=iso_num_(:)
    236204      ALLOCATE(iso_indnum(nqtot))
    237205      iso_indnum(:)=iso_indnum_(:)
    238       ALLOCATE(zone_num(nqtot))
    239       zone_num(:)=zone_num_(:)
    240       ALLOCATE(phase_num(nqtot))
    241       phase_num(:)=phase_num_(:)
    242206     
    243207      indnum_fn_num(:)=indnum_fn_num_(:)
  • LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90

    r3857 r4050  
    3030
    3131    USE dimphy
    32     USE infotrac_phy
     32    USE infotrac_phy, ONLY: nbtr
    3333    USE geometry_mod, ONLY: cell_area
    3434    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
     
    336336
    337337    USE dimphy
    338     USE infotrac_phy
     338!    USE infotrac_phy
    339339    USE geometry_mod, ONLY : cell_area
    340340    USE mod_grid_phy_lmdz
  • LMDZ6/trunk/libf/phylmd/traclmdz_mod.F90

    r4046 r4050  
    6767   
    6868    USE dimphy
    69     USE infotrac_phy
     69    USE infotrac_phy, ONLY: nbtr, tracers, niadv, solsym
    7070   
    7171    ! Input argument
     
    8989    ! Initialization of the tracers should be done here only for those not found in the restart file.
    9090    USE dimphy
    91     USE infotrac_phy
     91    USE infotrac_phy, ONLY: nbtr, nqo, tracers, pbl_flg, conv_flg, niadv
    9292    USE regr_pr_comb_coefoz_m, ONLY: alloc_coefoz
    9393    USE press_coefoz_m, ONLY: press_coefoz
     
    176176!!       iiq=niadv(it+2)                                                            ! jyg
    177177       iiq=niadv(it+nqo)                                                            ! jyg
    178 print*,'###'//TRIM(tracers(iiq)%name)//'###'
    179 print*,'###'//TRIM(strLower(tracers(iiq)%name))//'###'
    180178       SELECT CASE(strLower(tracers(iiq)%name))
    181179         CASE("rn");      id_rn     = it ! radon
     
    311309   
    312310    USE dimphy
    313     USE infotrac_phy
     311    USE infotrac_phy, ONLY: nbtr, pbl_flg, solsym
    314312    USE regr_pr_comb_coefoz_m, ONLY: regr_pr_comb_coefoz
    315313    USE o3_chem_m, ONLY: o3_chem
     
    586584    ! variable trs is written to restart file (restartphy.nc)
    587585    USE dimphy
    588     USE infotrac_phy
     586    USE infotrac_phy, ONLY: nbtr
    589587   
    590588    REAL,DIMENSION(klon,nbtr), INTENT(OUT) :: trs_out
  • LMDZ6/trunk/libf/phylmd/tracreprobus_mod.F90

    r3666 r4050  
    1212
    1313    USE dimphy
    14     USE infotrac_phy
     14    USE infotrac_phy, ONLY: nbtr, solsym
    1515#ifdef REPROBUS
    1616    USE CHEM_REP, ONLY : pdt_rep, &  ! pas de temps reprobus
Note: See TracChangeset for help on using the changeset viewer.