Ignore:
Timestamp:
May 13, 2020, 5:14:02 PM (5 years ago)
Author:
mvals
Message:

Mars GCM:
Extent of the transport of the isotopic ratio implemented in the dynamics to all the Van Leer transport schemes used in the physics (for now it only
concerns the tracer HDO).

  • libf/dynphy_lonlat/phymars/: iniphysiq_mod.F90: transmission of the content of variables describing the isotopes defined in the dynamics (precisely by dyn3d_common/infotrac.F90,

which reads traceur.def) to the physics

  • libf/phymars/: phys_state_var_init_mod.F90, tracer_mod.F : initialisation of the variables describing the isotopes in the physics callsedim_mod.F: implementation of the transport of the isotopic ratio in the Van Leer scheme used for sedimentation (applies to hdo ice) co2condens_mod.F: implementation of the transport of the isotopic ratio in the Van Leer scheme used for condensation of CO2 (applies to hdo ice and

vapour)
MV

File:
1 edited

Legend:

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

    r2312 r2322  
    55      use dimphy, only : init_dimphy
    66      use mod_grid_phy_lmdz, only : regular_lonlat
    7       use infotrac, only: nqtot, tname
     7      use infotrac, only: nqtot, tname, nqperes,nqdesc,iqfils,nqfils,
     8     &                    iqpere, nqdesc_tot
    89      use comsoil_h, only: volcapa, layer, mlayer, inertiedat, nsoilmx
    910      use comgeomfi_h, only: sinlat, ini_fillgeom
     
    127128      REAL halfaxe, excentric, Lsperi
    128129      Logical paleomars
     130
     131c   MVals: isotopes as in the dynamics (CRisi)
     132      INTEGER :: ifils,ipere,generation
     133      CHARACTER(len=30), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name
     134      CHARACTER(len=80) :: line ! to store a line of text     
     135      INTEGER ierr0
     136      LOGICAL :: continu
    129137
    130138c=======================================================================
     
    240248        allocate(dqdyn(nlayer,nq))
    241249        allocate(mqtot(nq))
     250        allocate(tnom_transp(nq))
    242251       
    243252        ! read tracer names from file traceur.def
    244253        do iq=1,nq
    245           read(90,*,iostat=ierr) tname(iq)
     254          read(90,'(80a)',iostat=ierr) line ! store the line from traceur.def
    246255          if (ierr.ne.0) then
    247256            write(*,*) 'testphys1d: error reading tracer names...'
    248257            stop
    249258          endif
     259          ! if format is tnom_0, tnom_transp (isotopes)
     260          read(line,*,iostat=ierr0) tname(iq),tnom_transp(iq)
     261          if (ierr0.ne.0) then
     262            read(line,*) tname(iq)
     263            tnom_transp(iq)='air'
     264          endif
     265
    250266        enddo
    251267        close(90)
     268
     269       ! 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))
     273       nqperes=0
     274       nqfils(:)=0
     275       nqdesc(:)=0
     276       iqfils(:,:)=0
     277       iqpere(:)=0
     278       nqdesc_tot=0   
     279       DO iq=1,nqtot
     280       if (tnom_transp(iq) == 'air') then
     281         ! ceci est un traceur père
     282         WRITE(*,*) 'Le traceur',iq,', appele ',
     283     &          trim(tname(iq)),', est un pere'
     284         nqperes=nqperes+1
     285         iqpere(iq)=0
     286       else !if (tnom_transp(iq) == 'air') then
     287         ! ceci est un fils. Qui est son père?
     288         WRITE(*,*) 'Le traceur',iq,', appele ',
     289     &                trim(tname(iq)),', est un fils'
     290         continu=.true.
     291         ipere=1
     292         do while (continu)           
     293           if (tnom_transp(iq) .eq. tname(ipere)) then
     294             ! Son père est ipere
     295             WRITE(*,*) 'Le traceur',iq,'appele ',
     296     &   trim(tname(iq)),' est le fils de ',
     297     &   ipere,'appele ',trim(tname(ipere))
     298             nqfils(ipere)=nqfils(ipere)+1 
     299             iqfils(nqfils(ipere),ipere)=iq
     300             iqpere(iq)=ipere         
     301             continu=.false.
     302           else !if (tnom_transp(iq) == tnom_0(ipere)) then
     303             ipere=ipere+1
     304             if (ipere.gt.nqtot) then
     305                 WRITE(*,*) 'Le traceur',iq,'appele ',
     306     &           trim(tname(iq)),', est orpelin.'
     307                 CALL abort_gcm('infotrac_init',
     308     &                  'Un traceur est orphelin',1)
     309             endif !if (ipere.gt.nqtot) then
     310           endif !if (tnom_transp(iq) == tnom_0(ipere)) then
     311         enddo !do while (continu)
     312       endif !if (tnom_transp(iq) == 'air') then
     313       enddo !DO iq=1,nqtot
     314       WRITE(*,*) 'nqperes=',nqperes   
     315       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
    252341
    253342        ! initialize tracers here:
     
    583672      call init_dimphy(1,nlayer) ! Initialize dimphy module
    584673      call phys_state_var_init(1,llm,nq,tname,
    585      .          day0,time,daysec,dtphys,rad,g,r,cpp)
     674     .          day0,time,daysec,dtphys,rad,g,r,cpp,
     675     .          nqdesc,iqfils,nqperes,nqfils)! MVals: variables isotopes
    586676      call ini_fillgeom(1,latitude,longitude,(/1.0/))
    587677      call conf_phys(1,llm,nq)
Note: See TracChangeset for help on using the changeset viewer.