Ignore:
Timestamp:
Dec 23, 2021, 6:54:17 PM (2 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 (?).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3dmem/vlspltgen_loc.F

    r2603 r4050  
    22! $Header$
    33!
    4        SUBROUTINE vlspltgen_loc( q,iadv,pente_max,masse,w,pbaru,pbarv,
     4       SUBROUTINE vlspltgen_loc( q,pente_max,masse,w,pbaru,pbarv,
    55     &                           pdt, p,pk,teta                 )
    66     
     
    2828      USE VAMPIR
    2929      ! CRisi: on rajoute variables utiles d'infotrac 
    30       USE infotrac, ONLY : nqtot,nqperes,nqdesc,nqfils,iqfils,
    31      &    ok_iso_verif
     30      USE infotrac, ONLY : nqtot,nqperes, tracers,ok_iso_verif
    3231      USE vlspltgen_mod
    3332      USE comconst_mod, ONLY: cpp
     
    4140c   Arguments:
    4241c   ----------
    43       INTEGER iadv(nqtot)
    4442      REAL masse(ijb_u:ije_u,llm),pente_max
    4543      REAL pbaru( ijb_u:ije_u,llm ),pbarv( ijb_v:ije_v,llm)
     
    200198!      DO iq=1,nqtot
    201199      DO iq=1,nqperes ! CRisi: on ne boucle que sur les pères= ceux qui sont transportés directement par l'air
    202        !write(*,*) 'vlspltgen 192: iq,iadv=',iq,iadv(iq)
     200       !write(*,*) 'vlspltgen 192: iq,iadv=',iq,tracers(iq)%iadv
    203201#ifdef DEBUG_IO   
    204202       CALL WriteField_u('zq',zq(:,:,iq))
    205203       CALL WriteField_u('zm',zm(:,:,iq))
    206204#endif
    207         if(iadv(iq) == 0) then
    208        
    209           cycle
    210        
    211         else if (iadv(iq)==10) then
    212 
     205        SELECT CASE(tracers(iq)%iadv)
     206          CASE(0); CYCLE
     207          CASE(10)
    213208#ifdef _ADV_HALO       
    214209! CRisi: on ajoute les nombres de fils et tableaux des fils
     
    229224          call Register_Hallo_u(zm(:,:,iq),llm,1,1,1,1,MyRequest1)
    230225! CRisi
    231           do ifils=1,nqdesc(iq)
    232             iq2=iqfils(ifils,iq)
     226          do ifils=1,tracers(iq)%nqDescen
     227            iq2=tracers(iq)%iqDescen(ifils)
    233228            call Register_Hallo_u(zq(:,:,iq2),llm,2,2,2,2,MyRequest1)
    234229            call Register_Hallo_u(zm(:,:,iq2),llm,1,1,1,1,MyRequest1)
     
    238233          call VTe(VTHallo)
    239234c$OMP END MASTER
    240         else if (iadv(iq)==14) then
    241 
     235          CASE(14)
    242236#ifdef _ADV_HALO           
    243237          call vlxqs_loc(zq,pente_max,zm,mu,
     
    256250          call Register_Hallo_u(zq(:,:,iq),llm,2,2,2,2,MyRequest1)
    257251          call Register_Hallo_u(zm(:,:,iq),llm,1,1,1,1,MyRequest1)
    258           do ifils=1,nqdesc(iq)
    259             iq2=iqfils(ifils,iq)
     252          do ifils=1,tracers(iq)%nqDescen
     253            iq2=tracers(iq)%iqDescen(ifils)
    260254            call Register_Hallo_u(zq(:,:,iq2),llm,2,2,2,2,MyRequest1)
    261255            call Register_Hallo_u(zm(:,:,iq2),llm,1,1,1,1,MyRequest1)
     
    265259          call VTe(VTHallo)
    266260c$OMP END MASTER
    267         else
    268        
     261          CASE DEFAULT
    269262          stop 'vlspltgen_p : schema non parallelise'
    270263     
    271         endif
     264        END SELECT
    272265     
    273266      enddo !DO iq=1,nqperes
     
    298291        !write(*,*) 'vlspltgen 279: iq=',iq
    299292
    300         if(iadv(iq) == 0) then
    301        
    302           cycle
    303        
    304         else if (iadv(iq)==10) then
    305 
     293        SELECT CASE(tracers(iq)%iadv)
     294          CASE(0); CYCLE
     295          CASE(10)
    306296#ifdef _ADV_HALLO
    307297          call vlx_loc(zq,pente_max,zm,mu,
    308298     &                 ij_begin+2*iip1,ij_end-2*iip1,iq)
    309299#endif       
    310         else if (iadv(iq)==14) then
     300          CASE(14)
    311301#ifdef _ADV_HALLO
    312302          call vlxqs_loc(zq,pente_max,zm,mu,
    313303     &                    qsat,ij_begin+2*iip1,ij_end-2*iip1,iq)
    314304#endif   
    315         else
    316        
     305          CASE DEFAULT
    317306          stop 'vlspltgen_p : schema non parallelise'
    318307     
    319         endif
     308        END SELECT
    320309     
    321310      enddo
     
    355344#endif
    356345
    357         if(iadv(iq) == 0) then
    358        
    359           cycle
    360        
    361         else if (iadv(iq)==10) then
    362        
    363           call vly_loc(zq,pente_max,zm,mv,iq)
    364  
    365         else if (iadv(iq)==14) then
    366      
    367           call vlyqs_loc(zq,pente_max,zm,mv,
    368      &                   qsat,iq)
    369  
    370         else
    371        
     346        SELECT CASE(tracers(iq)%iadv)
     347          CASE(0); CYCLE
     348          CASE(10); call vly_loc(zq,pente_max,zm,mv,iq)
     349          CASE(14); call vlyqs_loc(zq,pente_max,zm,mv,qsat,iq)
     350          CASE DEFAULT
    372351          stop 'vlspltgen_p : schema non parallelise'
    373      
    374         endif
     352        END SELECT
    375353       
    376354       enddo
     
    386364       CALL WriteField_u('zm',zm(:,:,iq))
    387365#endif
    388         if(iadv(iq) == 0) then
    389          
    390           cycle
    391        
    392         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    393 
     366        SELECT CASE(tracers(iq)%iadv)
     367          CASE(0); CYCLE
     368          CASE(10,14)
    394369c$OMP BARRIER       
    395370#ifdef _ADV_HALLO
     
    411386          call Register_Hallo_u(zm(:,:,iq),llm,1,1,1,1,MyRequest2)
    412387          ! CRisi
    413           do ifils=1,nqdesc(iq)
    414             iq2=iqfils(ifils,iq)
     388          do ifils=1,tracers(iq)%nqDescen
     389            iq2=tracers(iq)%iqDescen(ifils)
    415390            call Register_Hallo_u(zq(:,:,iq2),llm,2,2,2,2,MyRequest2)
    416391            call Register_Hallo_u(zm(:,:,iq2),llm,1,1,1,1,MyRequest2)
     
    420395c$OMP END MASTER       
    421396c$OMP BARRIER
    422         else
    423        
     397          CASE DEFAULT
    424398          stop 'vlspltgen_p : schema non parallelise'
    425399     
    426         endif
     400        END SELECT
    427401     
    428402      enddo
     
    448422      !write(*,*) 'vlspltgen 409: iq=',iq
    449423
    450         if(iadv(iq) == 0) then
    451          
    452           cycle
    453        
    454         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     424        SELECT CASE(tracers(iq)%iadv)
     425          CASE(0); CYCLE
     426          CASE(10,14)
    455427c$OMP BARRIER       
    456428
     
    461433
    462434c$OMP BARRIER       
    463         else
    464        
     435          CASE DEFAULT
    465436          stop 'vlspltgen_p : schema non parallelise'
    466      
    467         endif
     437        END SELECT
    468438     
    469439      enddo
     
    498468       CALL WriteField_u('zm',zm(:,:,iq))
    499469#endif
    500         if(iadv(iq) == 0) then
    501        
    502           cycle
    503        
    504         else if (iadv(iq)==10) then
    505        
    506           call vly_loc(zq,pente_max,zm,mv,iq)
    507  
    508         else if (iadv(iq)==14) then
    509      
    510           call vlyqs_loc(zq,pente_max,zm,mv,
    511      &                   qsat,iq)
    512  
    513         else
    514        
    515           stop 'vlspltgen_p : schema non parallelise'
    516      
    517         endif
     470        SELECT CASE(tracers(iq)%iadv)
     471          CASE(0); CYCLE
     472          CASE(10); call   vly_loc(zq,pente_max,zm,mv,     iq)
     473          CASE(14); call vlyqs_loc(zq,pente_max,zm,mv,qsat,iq)
     474          CASE DEFAULT; stop 'vlspltgen_p : schema non parallelise'
     475        END SELECT
    518476       
    519477       enddo !do iq=1,nqperes
     
    529487       CALL WriteField_u('zm',zm(:,:,iq))
    530488#endif
    531         if(iadv(iq) == 0) then
    532          
    533           cycle
    534        
    535         else if (iadv(iq)==10) then
    536        
    537           call vlx_loc(zq,pente_max,zm,mu,
     489        SELECT CASE(tracers(iq)%iadv)
     490          CASE(0); CYCLE
     491          CASE(10); call   vlx_loc(zq,pente_max,zm,mu,
    538492     &               ij_begin,ij_end,iq)
    539  
    540         else if (iadv(iq)==14) then
    541      
    542           call vlxqs_loc(zq,pente_max,zm,mu,
     493          CASE(14); call vlxqs_loc(zq,pente_max,zm,mu,
    543494     &                 qsat, ij_begin,ij_end,iq)
    544  
    545         else
    546        
    547           stop 'vlspltgen_p : schema non parallelise'
    548      
    549         endif
     495          CASE DEFAULT; stop 'vlspltgen_p : schema non parallelise'
     496        END SELECT
    550497       
    551498       enddo !do iq=1,nqperes
Note: See TracChangeset for help on using the changeset viewer.