Ignore:
Timestamp:
Jan 12, 2022, 10:54:09 PM (2 years ago)
Author:
dcugnet
Message:

Most of the changes are intended to help to eventually remove the constraints about the tracers assumptions, in particular water tracers.

  • Remove index tables itr_indice and niadv, replaced by tracers(:)%isAdvected and tracers(:)%isH2OFamily. Most of the loops are now from 1 to nqtot:
    • DO iq=nqo+1,nqtot loops are replaced with: DO iq=1,nqtot

IF(tracers(iq)%isH2Ofamily) CYCLE

  • DO it=1,nbtr; iq=niadv(it+nqo)

and DO it=1,nqtottr; iq=itr_indice(it) loops are replaced with:

it = 0
DO iq = 1, nqtot

IF(.NOT.tracers(iq)%isAdvected .OR. tracers(iq)%isH2Ofamily) CYCLE
it = it+1

  • Move some StratAer? related code from infotrac to infotrac_phy
  • Remove "nqperes" variable:

DO iq=1,nqpere loops are replaced with:
DO iq=1,nqtot

IF(tracers(iq)%parent/='air') CYCLE

  • Cosmetic changes (justification, SELECT CASE instead of multiple IF...) mostly in advtrac* routines.
File:
1 edited

Legend:

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

    r4009 r4056  
    3939    USE ioipsl_getin_p_mod, ONLY : getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac, nqCO2
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac, nqCO2
     42    USE readTracFiles_mod, ONLY: phases_sep
     43    USE strings_mod,  ONLY: strIdx
    4244    USE iophy
    4345    USE limit_read_mod, ONLY : init_limit_read
     
    146148       !
    147149       d_t_vdf,d_q_vdf,d_u_vdf,d_v_vdf,d_t_diss, &
     150       d_t_vdf_x, d_t_vdf_w, &
     151       d_q_vdf_x, d_q_vdf_w, &
    148152       d_ts, &
    149153       !
     
    218222       zxfluxlat_x, zxfluxlat_w, &
    219223       !
    220        d_t_vdf_x, d_t_vdf_w, &
    221        d_q_vdf_x, d_q_vdf_w, &
    222224       pbl_tke_input, tke_dissip, l_mix, wprime,&
    223225       t_therm, q_therm, u_therm, v_therm, &
     
    356358    LOGICAL, SAVE :: ok_volcan ! pour activer les diagnostics volcaniques
    357359    !$OMP THREADPRIVATE(ok_volcan)
    358     INTEGER, SAVE :: flag_volc_surfstrat ! pour imposer le cool/heat rate à la surf ou dans la strato
     360    INTEGER, SAVE :: flag_volc_surfstrat ! pour imposer le cool/heat rate à la surf/strato
    359361    !$OMP THREADPRIVATE(flag_volc_surfstrat)
    360362    LOGICAL ok_cvl  ! pour activer le nouveau driver pour convection KE
     
    854856    real zqsat(klon,klev)
    855857    !
    856     INTEGER i, k, iq, j, nsrf, ll, l
     858    INTEGER i, k, iq, j, nsrf, ll, l, itr
    857859    !
    858860    REAL t_coup
     
    10351037
    10361038    CHARACTER (LEN=20) :: modname='physiq_mod'
    1037     CHARACTER*80 message, abort_message
     1039    CHARACTER*80 abort_message
    10381040    LOGICAL, SAVE ::  ok_sync, ok_sync_omp
    10391041    !$OMP THREADPRIVATE(ok_sync)
     
    13631365         iflag_phytrac = 1
    13641366       ENDIF
    1365 #endif 
     1367#endif
    13661368       nvm_lmdz = 13
    13671369       CALL getin_p('NVM',nvm_lmdz)
     
    22302232
    22312233    tke0(:,:)=pbl_tke(:,:,is_ave)
    2232     !CR:Nombre de traceurs de l'eau: nqo
    2233     !  IF (nqtot.GE.3) THEN
    2234     IF (nqtot.GE.(nqo+1)) THEN
    2235        !     DO iq = 3, nqtot       
    2236        DO iq = nqo+1, nqtot 
     2234    IF (nqtot > nqo) THEN
     2235       ! water isotopes are not included in tr_seri
     2236       itr = 0
     2237       DO iq = 1, nqtot
     2238         IF(tracers(iq)%isH2Ofamily) CYCLE
     2239         itr = itr+1
    22372240          DO  k = 1, klev
    22382241             DO  i = 1, klon
    2239                 !              tr_seri(i,k,iq-2) = qx(i,k,iq)
    2240                 tr_seri(i,k,iq-nqo) = qx(i,k,iq)
     2242                tr_seri(i,k,itr) = qx(i,k,iq)
    22412243             ENDDO
    22422244          ENDDO
    22432245       ENDDO
    22442246    ELSE
    2245        DO k = 1, klev
    2246           DO i = 1, klon
    2247              tr_seri(i,k,1) = 0.0
    2248           ENDDO
    2249        ENDDO
     2247! DC: make sure the final "1" index was meant for 1st H2O phase (vapor) !!!
     2248!       tr_seri(:,:,strIdx(tracers(:)%name,'H2O'//phases_sep//'g')) = 0.0
     2249       tr_seri(:,:,strIdx(tracers(:)%name,'H2Ov')) = 0.0
    22502250    ENDIF
    22512251!
     
    22542254    IF (debut) THEN
    22552255      WRITE(lunout,*)' WARNING: tr_ancien initialised to tr_seri'
    2256       DO iq = nqo+1, nqtot
    2257            tr_ancien(:,:,iq-nqo)=tr_seri(:,:,iq-nqo)
    2258       ENDDO
     2256       itr = 0
     2257       do iq = 1, nqtot
     2258         IF(tracers(iq)%isH2Ofamily) CYCLE
     2259         itr = itr+1
     2260         tr_ancien(:,:,itr)=tr_seri(:,:,itr)       
     2261       enddo
    22592262    ENDIF
    22602263    !
     
    22872290       d_qs_dyn2d(:)=(zx_tmp_fi2d(:)-prsw_ancien(:))/phys_tstep
    22882291       ! !! RomP >>>   td dyn traceur
    2289        IF (nqtot.GT.nqo) THEN     ! jyg
    2290           DO iq = nqo+1, nqtot      ! jyg
    2291               d_tr_dyn(:,:,iq-nqo)=(tr_seri(:,:,iq-nqo)-tr_ancien(:,:,iq-nqo))/phys_tstep ! jyg
    2292           ENDDO
    2293        ENDIF
     2292       IF (nqtot > nqo) d_tr_dyn(:,:,:)=(tr_seri(:,:,:)-tr_ancien(:,:,:))/phys_tstep
    22942293       ! !! RomP <<<
    22952294    ELSE
     
    23042303       d_qs_dyn2d(:) = 0.0
    23052304       ! !! RomP >>>   td dyn traceur
    2306        IF (nqtot.GT.nqo) THEN                                       ! jyg
    2307           DO iq = nqo+1, nqtot                                      ! jyg
    2308               d_tr_dyn(:,:,iq-nqo)= 0.0                             ! jyg
    2309           ENDDO
    2310        ENDIF
     2305       IF (nqtot > nqo) d_tr_dyn(:,:,:)= 0.0
    23112306       ! !! RomP <<<
    23122307       ancien_ok = .TRUE.
     
    25892584            debut,     lafin, &
    25902585            longitude_deg, latitude_deg, rugoro,  zrmu0,      &
    2591              sollwdown,    cldt,      &
     2586            sollwdown,    cldt,      &
    25922587            rain_fall, snow_fall, solsw,   solswfdiff, sollw,     &
    25932588            gustiness,                                &
     
    28572852         ENDDO
    28582853       ELSE
    2859                t_w(:,:) = t_seri(:,:)
     2854                t_w(:,:) = t_seri(:,:)
    28602855                q_w(:,:) = q_seri(:,:)
    28612856                t_x(:,:) = t_seri(:,:)
     
    30733068
    30743069       DO i = 1, klon
    3075           ema_pcb(i)  = paprs(i,ibas_con(i))
     3070          ! C Risi modif: pour éviter pb de dépassement d'indice dans les cas
     3071          ! où i n'est pas un point convectif et donc ibas_con(i)=0
     3072          ! c'est un pb indépendant des isotopes
     3073          if (ibas_con(i) > 0) then
     3074             ema_pcb(i)  = paprs(i,ibas_con(i))
     3075          else
     3076             ema_pcb(i)  = 0.0
     3077          endif
    30763078       ENDDO
    30773079       DO i = 1, klon
     
    35043506    wprime_ave(:,:)=0.
    35053507
    3506 
    35073508    DO nsrf = 1, nbsrf
    35083509       DO i = 1, klon
     
    35123513       ENDDO
    35133514    ENDDO
    3514 
    35153515
    35163516    CALL  calcratqs(klon,klev,prt_level,lunout,        &
     
    35303530       print *,'itap, ->fisrtilp ',itap
    35313531    ENDIF
     3532    !
    35323533
    35333534    picefra(:,:)=0.
     
    35563557         iflag_ice_thermo)
    35573558    ENDIF
     3559    !
    35583560    WHERE (rain_lsc < 0) rain_lsc = 0.
    35593561    WHERE (snow_lsc < 0) snow_lsc = 0.
     
    42674269 
    42684270#ifndef CPP_XIOS
    4269 
     4271          !--OB 30/05/2016 modified 21/10/2016
     4272          !--here we return swaero_diag and dryaod_diag to FALSE
     4273          !--and histdef will switch it back to TRUE if necessary
     4274          !--this is necessary to get the right swaero at first step
     4275          !--but only in the case of no XIOS as XIOS is covered elsewhere
     4276          IF (debut) swaerofree_diag = .FALSE.
     4277          IF (debut) swaero_diag = .FALSE.
     4278          IF (debut) dryaod_diag = .FALSE.
     4279          !--IM 15/09/2017 here we return ok_4xCO2atm to FALSE
     4280          !--as for swaero_diag, see above
     4281          IF (debut) ok_4xCO2atm = .FALSE.
     4282
     4283          !
    42704284          !IM 2eme calcul radiatif pour le cas perturbe ou au moins un
    42714285          !IM des taux doit etre different du taux actuel
     
    50525066    ENDDO
    50535067    !
    5054     !CR: nb de traceurs eau: nqo
    5055     !  IF (nqtot.GE.3) THEN
    5056     IF (nqtot.GE.(nqo+1)) THEN
    5057        !     DO iq = 3, nqtot
    5058        DO iq = nqo+1, nqtot
     5068    IF (nqtot > nqo+1) THEN
     5069       itr = 0
     5070       DO iq = 1, nqtot
     5071          IF(tracers(iq)%isH2Ofamily) CYCLE
     5072          itr = itr+1
    50595073          DO  k = 1, klev
    50605074             DO  i = 1, klon
    5061                 ! d_qx(i,k,iq) = ( tr_seri(i,k,iq-2) - qx(i,k,iq) ) / phys_tstep
    5062                 d_qx(i,k,iq) = ( tr_seri(i,k,iq-nqo) - qx(i,k,iq) ) / phys_tstep
     5075                d_qx(i,k,iq) = ( tr_seri(i,k,itr) - qx(i,k,iq) ) / phys_tstep
    50635076             ENDDO
    50645077          ENDDO
     
    51015114    CALL water_int(klon,klev,qs_ancien,zmasse,prsw_ancien)
    51025115    ! !! RomP >>>
    5103     !CR: nb de traceurs eau: nqo
    5104     IF (nqtot.GT.nqo) THEN
    5105        DO iq = nqo+1, nqtot
    5106           tr_ancien(:,:,iq-nqo) = tr_seri(:,:,iq-nqo)
    5107        ENDDO
    5108     ENDIF
     5116    IF (nqtot > nqo) tr_ancien(:,:,:) = tr_seri(:,:,:)
    51095117    ! !! RomP <<<
    51105118    !==========================================================================
Note: See TracChangeset for help on using the changeset viewer.