Ignore:
Timestamp:
Dec 6, 2017, 4:13:14 PM (7 years ago)
Author:
jvatant
Message:

Enable tracers management in 1D
--JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/dyn1d/rcm1d.F

    r1826 r1843  
    66      use mod_grid_phy_lmdz, only : regular_lonlat
    77      use infotrac, only: nqtot, tname
     8      use tracer_h, only: initracer2
    89      use surfdat_h, only: albedodat, phisfi,
    910     &                     zmea, zstd, zsig, zgam, zthe,
     
    727728! -------------------------------
    728729      tankCH4=2. ! default value for tankCH4
     730     
     731! Initialize tracers
     732! ------------------
     733      if(tracer) then
     734        call initracer2(nq,tname) ! We need tracers infos in physdem1
     735      endif
    729736
    730737c  Write a "startfi" file
  • trunk/LMDZ.TITAN/libf/phytitan/inifis_mod.F90

    r1822 r1843  
    5858!   declarations:
    5959!   -------------
    60   use datafile_mod, only: datadir
    6160  use ioipsl_getin_p_mod, only: getin_p
    6261  IMPLICIT NONE
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1822 r1843  
    366366      real ctimestep ! Chemistry timestep (s)
    367367 
    368       ! Grandeurs en moyennes zonales ------------------------
    369       real temp_eq(nlayer), press_eq(nlayer)
    370       real zplev(ngrid,nlayer+1),zplay(ngrid,nlayer)
    371       real ztemp(ngrid,nlayer)
     368      real temp_eq(nlayer), press_eq(nlayer) ! Moyennes planétaires
    372369     
    373370      real , allocatable, dimension(:,:,:),save :: ychim
     
    599596         endif
    600597
    601          if (ngrid.ne.1) then ! Note : no need to create a restart file in 1d.
     598         if (ngrid.ne.1) then
     599            ! Note : no need to create a restart file in 1d.
    602600            call physdem0("restartfi.nc",longitude,latitude,nsoilmx,ngrid,nlayer,nq, &
    603601                          ptimestep,pday+nday,time_phys,cell_area,          &
    604602                          albedo_bareground,inertiedat,zmea,zstd,zsig,zgam,zthe)
    605          endif
    606 
    607          ! Sanity check for microphysics
    608          if ( ((.not.moyzon_mu).and.(callmufi)) ) then
    609             print *, "moyzon_mu=",moyzon_mu," and callmufi=",callmufi
    610             print *, "Please activate zonal mean to run microphysics (for now) !"
    611             stop
    612          endif
    613 
    614          ! Sanity check for chemistry
    615          if ( (.not.moyzon_ch) .and. (callchim) ) then
    616             print *, "moyzon_ch=",moyzon_ch," and callchim=",callchim
    617             print *, "Please activate zonal mean to run chemistry !"
    618             stop
    619          endif
    620 
     603         
     604            ! Sanity check for microphysics - useless in 1D
     605            if ( ((.not.moyzon_mu).and.(callmufi)) ) then
     606               print *, "moyzon_mu=",moyzon_mu," and callmufi=",callmufi
     607               print *, "Please activate zonal mean to run microphysics (for now) !"
     608               stop
     609            endif
     610
     611            ! Sanity check for chemistry - useless in 1D
     612            if ( (.not.moyzon_ch) .and. (callchim) ) then
     613               print *, "moyzon_ch=",moyzon_ch," and callchim=",callchim
     614               print *, "Please activate zonal mean to run chemistry !"
     615               stop
     616            endif
     617
     618        endif ! of ngrid.ne.1
    621619         
    622620         ! XIOS outputs
     
    705703      enddo     
    706704
    707       ! -------------------------------Taken from old Titan --------------------------
    708       ! zonal averages needed
     705      ! Zonal averages needed for chemistry and microphysics
     706      ! ~~~~~~~~~~~~~ Taken from old Titan ~~~~~~~~~~~~~~~~~
    709707      if (moyzon_ch .or. moyzon_mu) then
    710708         
     
    10441042         if (callchim) then
    10451043
    1046             ! Using zonal mean for calchim
    1047             zplev(:,:) = zplevbar(:,:)
    1048             zplay(:,:) = zplaybar(:,:)
    1049             zzlev(:,:) = zzlevbar(:,:)
    1050             zzlay(:,:) = zzlaybar(:,:)
    1051             ztemp(:,:) = ztfibar(:,:)
    1052 
    10531044            if (nq.gt.nmicro) then
    10541045               do iq = nmicro+1,nq
     
    10731064               
    10741065               print *, "We enter in the chemistry ..."
    1075                call calchim(ngrid,nq-nmicro,ychim,nomqy,declin,zls,ctimestep, &
    1076                            ztemp,zplay,zplev,zzlay,zzlev,dycchi,nlayer+70)
    1077 
    1078             ! JVO 2017 : NLEV = nlayer+70, en accord avec le C. Quid si nlay=/ 55 ?
    1079                
     1066
     1067               if (ngrid.eq.1) then ! We obviously don't have access to (and don't need) zonal means in 1D
     1068                 call calchim(ngrid,nq-nmicro,ychim,nomqy,declin,zls,ctimestep, &
     1069                           pt,pplay,pplev,zzlay,zzlev,dycchi,nlayer+70)
     1070               else
     1071                 call calchim(ngrid,nq-nmicro,ychim,nomqy,declin,zls,ctimestep, &
     1072                           ztfibar,zplaybar,zplevbar,zzlaybar,zzlevbar,dycchi,nlayer+70)
     1073                 ! JVO 2017 : NLEV = nlayer+70, en accord avec le C. Quid si nlay=/ 55 ?
     1074               endif
     1075
    10801076            endif
    10811077           
     
    11041100         if (callmufi) then
    11051101
    1106             ! Using zonal mean for microphysics
    1107             zplev(:,:) = zplevbar(:,:)
    1108             zplay(:,:) = zplaybar(:,:)
    1109             zzlev(:,:) = zzlevbar(:,:)
    1110             zzlay(:,:) = zzlaybar(:,:)
    1111             ztemp(:,:) = ztfibar(:,:)
    1112 
    11131102            ! Inside this routine we will split 2D->1D, intensive->extensive and separate different types of tracers
    11141103            ! Should be put in phytrac
    11151104
    1116             call calmufi(zplev,zzlev,zplay,zzlay,ztemp,pq,zdqmufi)
     1105               if (ngrid.eq.1) then ! We obviously don't have access to (and don't need) zonal means in 1D
     1106                  call calmufi(pplev,zzlev,pplay,zzlay,pt,pq,zdqmufi)
     1107               else
     1108                  call calmufi(zplevbar,zzlevbar,zplaybar,zzlaybar,ztfibar,pq,zdqmufi)
     1109               endif
    11171110
    11181111            pdq(1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + zdqmufi(1:ngrid,1:nlayer,1:nq)   
  • trunk/LMDZ.TITAN/libf/phytitan/tracer_h.F90

    r1815 r1843  
    103103    noms(:)=nametrac(:)
    104104
    105     ALLOCATE(rho_q(nq)) ! Defined for all tracers, currently initialized to 0.0
     105    IF (.NOT.ALLOCATED(rho_q)) ALLOCATE(rho_q(nq)) ! Defined for all tracers, currently initialized to 0.0
    106106    rho_q(:) = 0.0
    107107
    108     ALLOCATE(mmol(nq),rat_mmol(nq))  ! Defined for all tracers, (actually) initialized only for chemical tracers
     108    ! Defined for all tracers, (actually) initialized only for chemical tracers
     109    IF (.NOT.ALLOCATED(mmol)) ALLOCATE(mmol(nq))
     110    IF (.NOT.ALLOCATED(rat_mmol)) ALLOCATE(rat_mmol(nq))
    109111    mmol(:)  = 0.0
    110112    rat_mmol(:) = 1.0
     
    138140      ENDIF
    139141      ! microphysics indexes share the same values than original tracname.
    140       ALLOCATE(micro_indx(nmicro))
     142      IF (.NOT.ALLOCATED(micro_indx)) ALLOCATE(micro_indx(nmicro))
    141143      j = 1
    142144      DO i=1,nq
     
    148150      ENDDO
    149151    ELSE
    150       ALLOCATE(micro_indx(nmicro))
     152      IF (.NOT.ALLOCATED(micro_indx)) ALLOCATE(micro_indx(nmicro))
    151153    ENDIF
    152154
     
    163165        CALL abort_gcm("initracer2", "inconsistent number of tracers", 42)
    164166      ENDIF
    165       ALLOCATE(chimi_indx(nchimi))
     167      IF (.NOT.ALLOCATED(chimi_indx)) ALLOCATE(chimi_indx(nchimi))
    166168      n = 0 ! counter on chimi_indx
    167169      DO j=1,SIZE(cnames)
     
    186188      ENDIF
    187189    ELSE
    188       ALLOCATE(chimi_indx(0))
     190      IF (.NOT.ALLOCATED(chimi_indx)) ALLOCATE(chimi_indx(0))
    189191    ENDIF
    190192    IF (verb) THEN
Note: See TracChangeset for help on using the changeset viewer.