Ignore:
Timestamp:
May 26, 2020, 12:17:13 PM (5 years ago)
Author:
mvals
Message:

Mars GCM:
Follow-up of the last commit for the transport of the isotopic ratio: simplification of the transmission of variables from the dynamics to the
physics:

  • libf/dynphy_lonlat/phymars/: iniphysiq_mod.F90: transmission of the content of 2 variables describing the isotopes instead of 4 (nqperes: number of tracers "peres", nqfils:

number of tracers "fils")

  • libf/phymars/: phys_state_var_init_mod.F90, tracer_mod.F: idem callsedim_mod.F: idem co2condens_mod.F: idem
  • libf/phymars/dyn1d: testphys1d.F: idem (the reading interface for traceur.def has been completed to fill the variables nqperes and nqfils).

MV

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/callsedim_mod.F

    r2323 r2332  
    2323     &                      igcm_stormdust_number,igcm_topdust_mass,
    2424     &                      igcm_topdust_number,
    25      &                      iqfils,nqfils,qperemin,masseqmin ! MVals: variables isotopes
     25     &                      nqfils,qperemin,masseqmin ! MVals: variables isotopes
    2626      USE newsedim_mod, ONLY: newsedim
    2727      USE comcstfi_h, ONLY: g
     
    536536              !MVals: Loop over the sons ("fils")
    537537              if (nqfils(iq).gt.0) then
    538                 iq2=iqfils(nqfils(iq),iq) ! for now always nqfils(iq)=1 (special case of HDO only son of H2O)
     538                if (iq.eq.igcm_h2o_ice) then
     539                 iq2=igcm_hdo_ice
     540                else
     541                 call abort_physic("callsedim_mod","invalid isotope",1)
     542                endif
    539543                !MVals: input paramters in vlz_fi for hdo
    540544                do l=1,nlay
     
    595599              !MVals: Special case of isotopes: for now only HDO
    596600              if (nqfils(iq).gt.0) then
    597                iq2=iqfils(nqfils(iq),iq)
     601                if (iq.eq.igcm_h2o_ice) then
     602                 iq2=igcm_hdo_ice
     603                else
     604                 call abort_physic("callsedim_mod","invalid isotope",1)
     605                endif
    598606               pdqsed(ig,l,iq2)=(zqi(ig,l,iq2)-
    599607     $            (pq(ig,l,iq2) + pdqfi(ig,l,iq2)*ptimestep))/ptimestep
  • trunk/LMDZ.MARS/libf/phymars/co2condens_mod.F

    r2322 r2332  
    1616     $                  zdtcloudco2,pdqsc)
    1717                                                   
    18        use tracer_mod, only: noms, igcm_h2o_ice,
     18       use tracer_mod, only: noms, igcm_h2o_ice, igcm_h2o_vap,
    1919     &                      igcm_dust_mass, igcm_dust_number,
    2020     &                      igcm_ccn_mass, igcm_ccn_number,
    21      &                      iqfils,nqperes,nqfils, ! MVals: variables isotopes
     21     &                      igcm_hdo_ice, igcm_hdo_vap,
     22     &                      nqperes,nqfils, ! MVals: variables isotopes
    2223     &                      qperemin,masseqmin
    2324       use surfdat_h, only: emissiv, phisfi
     
    557558             ! MVals: loop over the sons ("fils")
    558559             if (nqfils(iq).gt.0) then
    559               iq2=iqfils(nqfils(iq),iq) ! for now it is always nqfils(iq)=1 (special case of HDO only son of H2O)
     560              if (iq.eq.igcm_h2o_ice) then
     561                 iq2=igcm_hdo_ice
     562              else if (iq.eq.igcm_h2o_vap) then
     563                 iq2=igcm_hdo_vap
     564              else
     565                 call abort_physic("co2condens_mod","invalid isotope",1)
     566              endif
    560567              do l=1,nlayer
    561568               if (zqc(l,iq).gt.qperemin) then
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F

    r2322 r2332  
    55      use dimphy, only : init_dimphy
    66      use mod_grid_phy_lmdz, only : regular_lonlat
    7       use infotrac, only: nqtot, tname, nqperes,nqdesc,iqfils,nqfils,
    8      &                    iqpere, nqdesc_tot
     7      use infotrac, only: nqtot, tname, nqperes,nqfils
    98      use comsoil_h, only: volcapa, layer, mlayer, inertiedat, nsoilmx
    109      use comgeomfi_h, only: sinlat, ini_fillgeom
     
    268267
    269268       ! Isotopes: as in the 3D case we have to determine father/son relations for isotopes and carrying fluid
    270        ALLOCATE(nqfils(nqtot),nqdesc(nqtot))   
    271        ALLOCATE(iqfils(nqtot,nqtot))   
    272        ALLOCATE(iqpere(nqtot))
     269       ALLOCATE(nqfils(nqtot))
    273270       nqperes=0
    274        nqfils(:)=0
    275        nqdesc(:)=0
    276        iqfils(:,:)=0
    277        iqpere(:)=0
    278        nqdesc_tot=0   
     271       nqfils(:)=0 
    279272       DO iq=1,nqtot
    280273       if (tnom_transp(iq) == 'air') then
     
    283276     &          trim(tname(iq)),', est un pere'
    284277         nqperes=nqperes+1
    285          iqpere(iq)=0
    286278       else !if (tnom_transp(iq) == 'air') then
    287279         ! ceci est un fils. Qui est son père?
     
    296288     &   trim(tname(iq)),' est le fils de ',
    297289     &   ipere,'appele ',trim(tname(ipere))
    298              nqfils(ipere)=nqfils(ipere)+1 
    299              iqfils(nqfils(ipere),ipere)=iq
    300              iqpere(iq)=ipere         
     290             nqfils(ipere)=nqfils(ipere)+1         
    301291             continu=.false.
    302292           else !if (tnom_transp(iq) == tnom_0(ipere)) then
     
    314304       WRITE(*,*) 'nqperes=',nqperes   
    315305       WRITE(*,*) 'nqfils=',nqfils
    316        WRITE(*,*) 'iqpere=',iqpere
    317        WRITE(*,*) 'iqfils=',iqfils
    318        ! Calculer le nombre de descendants à partir de iqfils et de nbfils
    319        DO iq=1,nqtot   
    320        generation=0
    321        continu=.true.
    322        ifils=iq
    323        do while (continu)
    324           ipere=iqpere(ifils)
    325          if (ipere.gt.0) then
    326           nqdesc(ipere)=nqdesc(ipere)+1   
    327           nqdesc_tot=nqdesc_tot+1     
    328           iqfils(nqdesc(ipere),ipere)=iq
    329           ifils=ipere
    330           generation=generation+1
    331          else !if (ipere.gt.0) then
    332           continu=.false.
    333          endif !if (ipere.gt.0) then
    334        enddo !do while (continu)   
    335        WRITE(*,*) 'Le traceur ',iq,', appele ',trim(tname(iq)),
    336      &               ' est un traceur de generation: ',generation
    337        ENDDO !DO iq=1,nqtot
    338        WRITE(*,*) 'infotrac: nqdesc=',nqdesc
    339        WRITE(*,*) 'iqfils=',iqfils
    340        WRITE(*,*) 'nqdesc_tot=',nqdesc_tot
    341306
    342307        ! initialize tracers here:
     
    673638      call phys_state_var_init(1,llm,nq,tname,
    674639     .          day0,time,daysec,dtphys,rad,g,r,cpp,
    675      .          nqdesc,iqfils,nqperes,nqfils)! MVals: variables isotopes
     640     .          nqperes,nqfils)! MVals: variables isotopes
    676641      call ini_fillgeom(1,latitude,longitude,(/1.0/))
    677642      call conf_phys(1,llm,nq)
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r2322 r2332  
    66                                     day_ini,hour_ini,pdaysec,ptimestep, &
    77                                     prad,pg,pr,pcpp, &
    8                                      dyn_nqdesc,dyn_iqfils,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
     8                                     dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
    99
    1010!=======================================================================
     
    7171      INTEGER,INTENT(in) :: dyn_nqperes
    7272      INTEGER,INTENT(in) :: dyn_nqfils(nq)
    73       INTEGER,INTENT(in) :: dyn_nqdesc(nq)
    74       INTEGER,INTENT(in) :: dyn_iqfils(nq,nq)
    7573
    7674      ! set dimension and allocate arrays in tracer_mod
    7775      call end_tracer_mod
    78       call ini_tracer_mod(nq,tname,dyn_nqdesc,dyn_iqfils,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
     76      call ini_tracer_mod(nq,tname,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
    7977
    8078
  • trunk/LMDZ.MARS/libf/phymars/tracer_mod.F90

    r2322 r2332  
    9898      integer, save                 :: nqperes ! numbers of tracers defined as "peres"
    9999      integer, allocatable, save    :: nqfils(:) ! numbers of sons ("fils") of the considered tracer
    100       integer, allocatable, save    :: iqfils(:,:) ! indice of a son, ex: iqfils(nqfils(ipere),ipere)
    101100      real, parameter               :: qperemin=1.e-16 ! threschold for the "pere" mixing ratio qpere to calculate Ratio=qfils/qpere
    102       real, parameter               :: masseqmin=1.e-16 ! threschold for the "pere" transporting masse
    103       !integer, allocatable, save    :: nqdesc(:) ! number of sons + all gran-sons over all generations: not useful for now in the martian case as there are no gran-sons
     101      real, parameter               :: masseqmin=1.e-16 ! threschold for the "pere" transporting masse martian case as there are no gran-sons
    104102
    105103!-----------------------------------------------------------------------
     
    107105  contains
    108106 
    109     subroutine ini_tracer_mod(nq,tname,dyn_nqdesc,dyn_iqfils,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
     107    subroutine ini_tracer_mod(nq,tname,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
    110108      implicit none
    111109     
     
    115113      integer,intent(in) :: dyn_nqperes
    116114      integer,intent(in) :: dyn_nqfils(nq)
    117       integer,intent(in) :: dyn_nqdesc(nq)
    118       integer,intent(in) :: dyn_iqfils(nq,nq)
    119115     
    120116      integer :: iq, count
     
    130126
    131127      !MVals: isotopes variables initialisation
    132       do iq=1,nq
    133         if (dyn_nqfils(iq).ne.dyn_nqdesc(iq)) then
    134           write(*,*) ' for now all descendants must be sons: check the', &
    135                      '  relations between tracers in traceur.def !'
    136           call abort_physic("ini_tracer_mod","relatives pattern between tracers not accepted",1)
    137         endif
    138       enddo
    139       allocate(nqfils(nq))!,nqdesc(nq))   
    140       allocate(iqfils(nq,nq))
     128      allocate(nqfils(nq))
    141129      nqperes=dyn_nqperes   
    142130      nqfils(:)=dyn_nqfils(:)
    143       iqfils(:,:)=dyn_iqfils(:,:)
    144131     
    145132#ifndef MESOSCALE
Note: See TracChangeset for help on using the changeset viewer.