Changeset 2785


Ignore:
Timestamp:
Aug 3, 2022, 5:07:41 PM (2 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
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/ICOSA_LMDZ/src/phystd/interface_icosa_lmdz.f90

    r2556 r2785  
    3737  INTEGER,SAVE :: nbp_phys_glo
    3838 
    39   CHARACTER(len=30),SAVE,ALLOCATABLE :: tname(:) ! tracer names
    4039  REAL,SAVE :: pday ! number of ellapsed sols since Ls=0
    4140  REAL,SAVE :: ptime ! "universal time" as fraction of sol (e.g. 0.5 for noon)
     
    204203
    205204
    206 !  INTEGER                       :: nqo, nbtr
    207205  CHARACTER(len=4)              :: type_trac
    208 !  CHARACTER(len=20),ALLOCATABLE :: tname(:)    ! tracer short name for restart and diagnostics
    209 !  CHARACTER(len=23),ALLOCATABLE :: ttext(:)     ! tracer long name for diagnostics
    210 !  INTEGER,ALLOCATABLE           :: niadv(:)    ! equivalent dyn / physique
    211 !  INTEGER,ALLOCATABLE           :: conv_flg(:) ! conv_flg(it)=0 : convection desactivated for tracer number it
    212 !  INTEGER,ALLOCATABLE           :: pbl_flg(:)  ! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
    213 !  CHARACTER(len=8),ALLOCATABLE  :: solsym(:)  ! tracer name from inca
     206
    214207  TYPE(t_field),POINTER,SAVE    :: f_ind_cell_glo(:)
    215208 
    216209  INTEGER :: iflag_phys   
    217210  INTEGER :: nq
     211  character(len=500) :: tracline ! to read traceur.def file
    218212
    219213  !! to get starting date
     
    285279     CALL getin('type_trac',type_trac)
    286280
    287 ! init model for standard lmdz case
    288 !    nqo=2
    289 !    nbtr=2
    290 !$OMP MASTER
    291     ALLOCATE(tname(nqtot))
    292 !$OMP END MASTER
    293 !$OMP BARRIER
    294 !    ALLOCATE(ttext(nqtot))
    295 !    ALLOCATE(niadv(nqtot))
    296 !    ALLOCATE(conv_flg(nbtr))
    297 !    ALLOCATE(pbl_flg(nbtr))
    298 !    ALLOCATE(solsym(nbtr))
    299    
    300 
    301 ! read tname() from traceur.def file
     281   
     282! read nq from traceur.def file
     283! We allow to read the Modern-trac-V1 as well to get nqtot
    302284    IF (is_mpi_root) THEN
    303285!$OMP MASTER
    304286    OPEN(unit=42,file="traceur.def",form="formatted",status="old",iostat=ierr)
    305287    IF (ierr==0) THEN
    306       READ(42,*) nq ! should be the same as nqtot
     288      READ(42,*) tracline
     289      if (trim(tracline) .ne. '#ModernTrac-v1') then !checking if we're using Modern-Trac or not
     290        read(tracline,*) nq !should be equal to nqtot
     291      else
     292        do !loop on lines until we find uncommented lines
     293          read(42,'(A)',iostat=ierr) tracline
     294          if (ierr==0) then
     295            if (index(tracline,"#") .ne. 1) then ! Allow for arbitrary number of commented lines in header
     296              read(tracline,*) nq !should be equal to nqtot
     297              exit
     298            endif  !index(tracline,"#") .ne. 1
     299          endif !ierr=0
     300        enddo
     301      endif !(trim(tracline) .ne. '#ModernTrac-v1')
    307302      IF (nq /= nqtot) THEN
    308303        WRITE(*,*) "Error: number of tracers in tracer.def should match nqtot!"
    309304        WRITE(*,*) "       will just use nqtot=",nqtot," tracers"
    310305      ENDIF
    311       DO i=1,nqtot
    312         READ(42,*) tname(i)
    313       ENDDO
    314306      CLOSE(42)
    315     ENDIF
     307    ENDIF !ierr==0 (1st one)
    316308!$OMP END MASTER
    317309!$OMP BARRIER
    318310    ENDIF ! of (is_mpi_root)
    319311
    320     DO i=1,nqtot
    321       CALL bcast(tname(i))
    322     ENDDO
     312
    323313
    324314!    CALL init_infotrac_phy(nqtot,nqo,nbtr,tname,ttext,type_trac,&
     
    627617!$OMP BARRIER   
    628618    CALL physiq(klon_omp, llm, nqtot, &
    629                 tname, &
    630619                debut, lafin, &
    631620                pday, ptime, dtphy, &
  • trunk/LMDZ.GENERIC/README

    r2784 r2785  
    17291729- remove top level obsolete "patch_large_domains" directory
    17301730- remove unused "watercaptag" field in the physics.
     1731
     1732== 03/08/2022 == LT + EM
     1733Further seperation between dynamics and physics concerning tracers:
     1734Tracer names are extracted from traceur.def via initracer.F90 and no
     1735longer transfered from the dynamics to the physics
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/callphysiq_mod.F90

    r1576 r2785  
    7070              llm,            & ! nlayer
    7171              nqtot,          & ! nq
    72               tname,          & ! nametrac
    7372              debut_split,    & ! firstcall
    7473              lafin_split,    & ! lastcall
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/newstart.F

    r2354 r2785  
    285285! Initialize global tracer indexes (stored in tracer.h)
    286286! ... this has to be done before phyetat0
    287       call initracer(ngridmx,nqtot,tname)
     287! and requires that "datadir" be correctly initialized
     288      call getin_p("datadir",datadir)
     289      call initracer(ngridmx,nqtot)
    288290
    289291! Initialize dimphy module (klon,klev,..)
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/start2archive.F

    r2354 r2785  
    236236     
    237237! Initialize tracer names, indexes and properties
    238       CALL initracer(ngridmx,nqtot,tname)
     238      CALL initracer(ngridmx,nqtot)
    239239
    240240      CALL phyetat0(.true.,ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
  • 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
  • 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,
  • 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
  • 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)
  • 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.