Ignore:
Timestamp:
Aug 3, 2022, 5:07:41 PM (3 years ago)
Author:
emillour
Message:

Generic PCM:
Further seperation between dynamics and physics concerning tracers:
Tracer names are extracted from traceur.def via initracer.F90 and no
longer transfered from the dynamics to the physics
LT+EM

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • TabularUnified trunk/LMDZ.GENERIC/libf/phystd/dyn1d/kcm1d.F90

    r2635 r2785  
    210210     endif
    211211
    212      call initracer(1,nq,nametrac)
     212     call initracer(1,nq)
    213213
    214214  endif
  • TabularUnified trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r2784 r2785  
    693693     &            form="formatted",iostat=ierr)
    694694                  if (ierr .eq. 0) then
    695                         read(91,*),qsurf(iq)
     695                        read(91,*)qsurf(iq)
    696696                        do ilayer=1,nlayer
    697697                              read(91,*)q(ilayer,iq)
     
    929929#ifndef MESOSCALE
    930930      if(tracer.and.photochem) then
    931            call initracer(1,nq,tname)
     931           call initracer(1,nq)
    932932           allocate(nametmp(nq))
    933933           nametmp(1:nq)=tname(1:nq)
     
    10051005
    10061006      CALL physiq (1,llm,nq,
    1007      .     tname,
    10081007     ,     firstcall,lastcall,
    10091008     ,     day,time,dtphys,
  • TabularUnified trunk/LMDZ.GENERIC/libf/phystd/initracer.F90

    r2784 r2785  
    1       SUBROUTINE initracer(ngrid,nq,nametrac)
     1      SUBROUTINE initracer(ngrid,nq)
    22
    33      use surfdat_h, ONLY: dryness
     
    2424!            Ehouarn Millour (oct. 2008) identify tracers by their names
    2525!            Y Jaziri & J. Vatant d'Ollone (2020) : Modern traceur.def
     26!            L Teinturier (2022): Tracer names are now read here instead of
     27!                                  inside interfaces
    2628!=======================================================================
    2729
    2830      integer,intent(in) :: ngrid,nq
    29       character(len=30),intent(in) :: nametrac(nq) ! name of the tracer from dynamics
    3031
    3132      character(len=500) :: tracline   ! to read traceur.def lines
    3233      ! character(len=30)  :: txt        ! to store some text
     34      integer :: blank      !to store the index of 1st blank when reading tracers names
    3335      integer iq,ig,count,ierr
    3436
     
    158160
    159161
    160 ! Initialization: copy tracer names from dynamics
    161         do iq=1,nq
    162           noms(iq)=nametrac(iq)
    163           write(*,*)"initracer: iq=",iq,"noms(iq)=",trim(noms(iq))
     162! Initialization: Read tracers names from traceur.def
     163        do iq=1,nq
     164          if (is_master) read(407,'(A)') tracline
     165          call bcast(tracline)
     166          blank = index(tracline,' ') ! Find position of 1st blank in tracline
     167          noms(iq) = tracline(1:blank) !ensure that in Modern-trac case, noms is actually the name and not all properties
    164168        enddo
    165 
    166169
    167170! Identify tracers by their names: (and set corresponding values of mmol)
     
    442445      endif
    443446
    444       ! Get data of tracers
     447      ! Get data of tracers. Need to rewind traceur.def first
     448      if (is_master) then
     449       rewind(407)
     450       do
     451        read(407,'(A)') tracline
     452        if (index(tracline,"#") .ne. 1) then
     453          exit
     454        endif
     455       enddo
     456      endif
    445457      do iq=1,nqtot
    446458        if (is_master) read(407,'(A)') tracline
  • TabularUnified trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r2784 r2785  
    66     
    77      subroutine physiq(ngrid,nlayer,nq,   &
    8                   nametrac,                &
    98                  firstcall,lastcall,      &
    109                  pday,ptime,ptimestep,    &
     
    151150!    nlayer                Number of vertical layers.
    152151!    nq                    Number of advected fields.
    153 !    nametrac              Name of corresponding advected fields.
    154152!
    155153!    firstcall             True at the first call.
     
    221219      integer,intent(in) :: nlayer            ! Number of atmospheric layers.
    222220      integer,intent(in) :: nq                ! Number of tracers.
    223       character*30,intent(in) :: nametrac(nq) ! Names of the tracers taken from dynamics.
    224221     
    225222      logical,intent(in) :: firstcall ! Signals first call to physics.
     
    508505         IF (.NOT.ALLOCATED(noms)) ALLOCATE(noms(nq)) ! (because noms is an argument of physdem1 whether or not tracer is on)
    509506         if (tracer) then
    510             call initracer(ngrid,nq,nametrac)
     507            call initracer(ngrid,nq)
    511508            if(photochem) then
    512509              call ini_conc_mod(ngrid,nlayer)
  • TabularUnified trunk/LMDZ.GENERIC/libf/phystd/tracer_h.F90

    r2725 r2785  
    77       integer, save :: nesp  ! number of species in the chemistry
    88       integer, save :: ngt   ! number of generic tracers
    9 !$OMP THREADPRIVATE(nqtot,nesp)
     9!$OMP THREADPRIVATE(nqtot,nesp,ngt)
    1010
    1111       logical :: moderntracdef=.false. ! Standard or modern traceur.def
     
    4141!$OMP THREADPRIVATE(is_recomb,is_recomb_qset,is_recomb_qotf)
    4242       integer, save, allocatable :: is_condensable(:)      ! 1 if tracer is generic, else 0 (added LT)
     43!$OMP THREADPRIVATE(is_condensable)   !also added by LT
    4344
    4445       ! Lists of constants for condensable tracers
     
    5051       integer, save, allocatable :: constants_RLVTT_generic(:)                ! Latent heat of vaporization (J/kg)
    5152       integer, save, allocatable :: constants_metallicity_coeff(:)    ! Coefficient to take into account the metallicity
     53!$OMP THREADPRIVATE(constants_mass,constants_delta_vapH,constants_Tref)
     54!$OMP THREADPRIVATE(constants_Pref,constants_epsi_generic)
     55!$OMP THREADPRIVATE(constants_RLVTT_generic,constants_metallicity_coeff)
    5256
    53 !$OMP THREADPRIVATE(is_condensable)   !also added by LT
    5457! tracer indexes: these are initialized in initracer and should be 0 if the
    5558!                 corresponding tracer does not exist
Note: See TracChangeset for help on using the changeset viewer.