Changeset 3661


Ignore:
Timestamp:
Feb 27, 2025, 2:53:11 PM (5 months ago)
Author:
emoisan
Message:

Titan CRM:
Add Titan interface in INTERFACES_V4
Adapt module_model_constants.F to Titan
Add new tracer_mode for Titan (CH4 scalar)
Add new communication of variables between LMDZ.TITAN and WRF
Allow microphysics for Mesoscale in physiq_mod.F90
EMo

Location:
trunk
Files:
6 added
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/comm_wrf.F90

    r2291 r3661  
    1818  REAL,SAVE,ALLOCATABLE :: comm_FLUXSURF_LW(:)
    1919  REAL,SAVE,ALLOCATABLE :: comm_FLXGRD(:)
     20  REAL,SAVE,ALLOCATABLE :: comm_zqfi_omp(:,:,:)
     21  REAL,SAVE,ALLOCATABLE :: comm_zdtlc(:,:)
    2022
    2123contains
    2224
    23   subroutine allocate_comm_wrf(ngrid,nlayer)
     25  subroutine allocate_comm_wrf(ngrid,nlayer,nq)
    2426  implicit none
    25   integer,intent(in) :: ngrid ! number of atmospheric columns
     27  integer,intent(in) :: ngrid  ! number of atmospheric columns
    2628  integer,intent(in) :: nlayer ! number of atmospheric layers
     29  integer,intent(in) :: nq     ! number of tracers
    2730  allocate(comm_HR_SW(ngrid,nlayer))
    2831  allocate(comm_HR_LW(ngrid,nlayer))
     
    3841  allocate(comm_FLUXSURF_LW(ngrid))
    3942  allocate(comm_FLXGRD(ngrid))
     43  allocate(comm_zqfi_omp(ngrid,nlayer,nq))
     44  allocate(comm_zdtlc(ngrid,nlayer))
    4045
    4146  end subroutine allocate_comm_wrf
     
    5661  deallocate(comm_FLUXSURF_LW)
    5762  deallocate(comm_FLXGRD)
     63  deallocate(comm_zqfi_omp)
     64  deallocate(comm_zdtlc)
    5865
    5966  end subroutine deallocate_comm_wrf
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r3497 r3661  
    4646#else
    4747use comm_wrf, only : comm_HR_SW, comm_HR_LW, &
    48                      comm_FLUXTOP_DN,comm_FLUXABS_SW,&
    49                      comm_FLUXTOP_LW,comm_FLUXSURF_SW,&
    50                      comm_FLUXSURF_LW,comm_FLXGRD
     48                     comm_FLUXTOP_DN, comm_FLUXABS_SW,&
     49                     comm_FLUXTOP_LW, comm_FLUXSURF_SW,&
     50                     comm_FLUXSURF_LW, comm_FLXGRD,&
     51                     comm_zqfi_omp, comm_zdtlc
    5152#endif
    5253#ifdef CPP_XIOS     
     
    138139!    pdv(ngrid,nlayer)         \  Temporal derivative of the corresponding
    139140!    pdt(ngrid,nlayer)         /  variables due to physical processes.
    140 !    pdq(ngrid,nlayer)        /
     141!    pdq(ngrid,nlayer,nq)     /
    141142!    pdpsrf(ngrid)           /
    142143!
     
    331332      character*2 :: str2
    332333
    333 #ifndef MESOSCALE
     334!#ifndef MESOSCALE
    334335
    335336! Local variables for Titan chemistry and microphysics
     
    363364#endif
    364365
    365       logical file_ok
     366#ifdef MESOSCALE
     367      LOGICAL, SAVE ::  moyzon_ch ! used for zonal averages in Titan
     368      REAL, ALLOCATABLE :: zplevbar(:,:)
     369      REAL, ALLOCATABLE :: zplaybar(:,:)
     370      REAL, ALLOCATABLE :: ztfibar(:,:)
     371      REAL, ALLOCATABLE :: zqfibar(:,:,:)
     372      REAL, ALLOCATABLE :: zphibar(:,:)
     373      REAL, ALLOCATABLE :: zphisbar(:)
     374      REAL, ALLOCATABLE :: zzlevbar(:,:)
     375      REAL, ALLOCATABLE :: zzlaybar(:,:)
     376!     REAL, DIMENSION(:,:)   :: zplevbar(:,:)
     377!     REAL, DIMENSION(:,:)   :: zplaybar(:,:)
     378!     REAL, DIMENSION(:,:)   :: ztfibar(:,:)
     379!     REAL, DIMENSION(:,:,:) :: zqfibar(:,:,:)
     380!     REAL, DIMENSION(:,:)   :: zphibar(:,:)
     381!     REAL, DIMENSION(:)     :: zphisbar(:)
     382!     REAL, DIMENSION(:,:)   :: zzlevbar(:,:)
     383!     REAL, DIMENSION(:,:)   :: zzlaybar(:,:)
     384#endif
    366385
    367386!-----------------------------------------------------------------------------
     
    385404    END INTERFACE
    386405
    387 #endif
    388      
     406!#endif
     407     
     408      logical file_ok
     409
    389410!==================================================================================================
    390411
     
    447468           int_dtauv(:,:,:) = 0.D0
    448469         
    449 #ifndef MESOSCALE
     470!#ifndef MESOSCALE
    450471           IF (callmufi .AND. (.NOT. uncoupl_optic_haze)) THEN
    451472             haze_opt_file=trim(datadir)//'/optical_tables/HAZE_OPTIC_'//trim(adjustl(tmp1))//'x'//trim(adjustl(tmp2))//'.DAT'
     
    459480              endif
    460481           ENDIF
    461 #endif           
     482!#endif           
    462483
    463484         endif
     485
     486#ifdef MESOSCALE
     487         moyzon_ch = .false. !no zonal mean for mesoscale
     488#endif
    464489
    465490#ifndef MESOSCALE
    466491!        Initialize names and timestep for chemistry
    467492!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    468 
    469493         if (callchim) then
    470494
     
    479503
    480504         endif
     505#endif
    481506
    482507!        Initialize microphysics.
     
    491516
    492517         ENDIF
    493 #endif
    494518
    495519#ifdef CPP_XIOS
     
    717741      ! JVO 19 : We shall always have correct altitudes in chemistry no matter what's in physics
    718742      ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    719 #ifndef MESOSCALE
     743!#ifndef MESOSCALE
    720744      if (moyzon_ch) then ! Zonal averages
    721745         
     
    748772
    749773      else !  if not moyzon
    750 #endif
     774!#endif
    751775     
    752776        DO ig=1,ngrid
     
    763787        ENDDO
    764788
    765 #ifndef MESOSCALE
     789!#ifndef MESOSCALE
    766790      endif  ! moyzon
    767 #endif
     791!#endif
    768792
    769793      ! -------------------------------------------------------------------------------------
     
    10651089      if (tracer) then
    10661090
    1067 #ifndef MESOSCALE
    10681091   ! -------------------
    10691092   !   V.1 Microphysics
     
    10721095         ! We must call microphysics before chemistry, for condensation !
    10731096         if (callmufi) then
    1074 
    10751097            zzlev(:,nlayer+1)=zzlay(:,nlayer)+(zzlay(:,nlayer)-zzlev(:,nlayer)) ! JVO 19 : We assume zzlev isn't reused later on (could be done cleaner)
    10761098
     
    11481170         endif ! callmufi
    11491171     
     1172#ifndef MESOSCALE
    11501173  ! -----------------
    11511174  !   V.2. Chemistry
     
    12921315         endif ! end of 'callchim'
    12931316
    1294 ! END MESOSCALE
     1317!! END ifndef MESOSCALE
    12951318#endif
    12961319
     
    20102033      comm_FLXGRD(1:ngrid)=fluxgrd(1:ngrid)
    20112034      sensibFlux(1:ngrid) = zflubid(1:ngrid) - capcal(1:ngrid)*zdtsdif(1:ngrid)
     2035      comm_zqfi_omp(1:ngrid,1:nlayer,1:nq) = zq(1:ngrid,1:nlayer,1:nq)
     2036      comm_zdtlc(1:ngrid,1:nlayer) = zdtlc(1:ngrid,1:nlayer)
    20122037#endif     
    20132038
  • trunk/WRF.COMMON/INTERFACES_V4/module_lmd_driver.F

    r2874 r3661  
    4848        HFMAX,ZMAX,&
    4949        USTM,HFX,&
    50         SLPX,SLPY,RESTART)
     50        SLPX,SLPY,RESTART,&
     51        DT_COND)
    5152! NB: module_lmd_driver_output1.inc : output arguments generated from Registry
    5253
     
    114115     RTHPLATEN,RUPLATEN,RVPLATEN, &
    115116     HR_SW,HR_LW,HR_DYN,DT_RAD,&
    116      CLOUDFRAC,RH,DQICE,DQVAP,DTLSC,DTRAIN,DT_MOIST,H2OICE_REFF
     117     CLOUDFRAC,RH,DQICE,DQVAP,DTLSC,DTRAIN,DT_MOIST,H2OICE_REFF,&
     118     DT_COND
    117119REAL, DIMENSION( ims:ime, kms:kme+1, jms:jme ), INTENT(INOUT ) :: &
    118120     P_Q2
     
    445447    q_prof(:,2) = moist(i,kps:kpe,j,P_QC) / (1.d0 + moist(i,kps:kpe,j,P_QV))
    446448    ! conversion from mass mixing ratio in WRF to specific concentration in Physiq
     449ELSE IF (TRACER_MODE == 61) THEN
     450    ! to be clean we should have an automatized process that makes sure that moist is sent to igcm_h2o_vap and etc.
     451    q_prof(:,1) = SCALAR(i,kps:kpe,j,P_mu_m0as) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     452    q_prof(:,2) = SCALAR(i,kps:kpe,j,P_mu_m3as) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     453    q_prof(:,3) = SCALAR(i,kps:kpe,j,P_mu_m0af) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     454    q_prof(:,4) = SCALAR(i,kps:kpe,j,P_mu_m3af) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     455    q_prof(:,5) = SCALAR(i,kps:kpe,j,P_mu_m0n) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     456    q_prof(:,6) = SCALAR(i,kps:kpe,j,P_mu_m3n) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     457    q_prof(:,7) = SCALAR(i,kps:kpe,j,P_mu_m3CH4) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
     458    q_prof(:,8) = SCALAR(i,kps:kpe,j,P_CH4) / (1.d0 + SCALAR(i,kps:kpe,j,P_CH4))
    447459ELSE
    448460    q_prof(:,1:nq) = SCALAR(i,kps:kpe,j,2:nq+1)  !! the names were set above !! one dummy tracer in WRF
     
    651663            DQICE,DQVAP,REEVAP,SURFRAIN,&
    652664            ALBEQ,FLUXTOP_DN,FLUXABS_SW,FLUXTOP_LW,FLUXSURF_SW,&
    653             FLUXSURF_LW,FLXGRD,DTLSC,DTRAIN,DT_MOIST,H2OICE_REFF,LATENT_HF)
     665            FLUXSURF_LW,FLXGRD,DTLSC,DTRAIN,DT_MOIST,H2OICE_REFF,LATENT_HF,&
     666            DT_COND)
    654667!!!
    655668!print *, '** ',planet_type,'** OUTPUT PHYSICS DONE'
     
    739752      SCALAR(i,kps:kpe,j,P_MARKER) = SCALAR(i,kps:kpe,j,P_MARKER)*exp(-dt/tau_decay)
    740753      SCALAR(i,1,j,P_MARKER) = 1. !! this tracer is emitted in the surface layer
     754    CASE(61) !emoisan tobechecked
     755      scalar(i,kps:kpe,j,P_mu_m0as)=scalar(i,kps:kpe,j,P_mu_m0as) &
     756           +zdqfi_omp(subs,kps:kpe,1)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     757      scalar(i,kps:kpe,j,P_mu_m3as)=scalar(i,kps:kpe,j,P_mu_m3as) &
     758           +zdqfi_omp(subs,kps:kpe,2)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     759      scalar(i,kps:kpe,j,P_mu_m0af)=scalar(i,kps:kpe,j,P_mu_m0af) &
     760           +zdqfi_omp(subs,kps:kpe,3)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     761      scalar(i,kps:kpe,j,P_mu_m3af)=scalar(i,kps:kpe,j,P_mu_m3af) &
     762           +zdqfi_omp(subs,kps:kpe,4)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     763      scalar(i,kps:kpe,j,P_mu_m0n)=scalar(i,kps:kpe,j,P_mu_m0n) &
     764           +zdqfi_omp(subs,kps:kpe,5)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     765      scalar(i,kps:kpe,j,P_mu_m3n)=scalar(i,kps:kpe,j,P_mu_m3n) &
     766           +zdqfi_omp(subs,kps:kpe,6)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     767      scalar(i,kps:kpe,j,P_mu_m3CH4)=scalar(i,kps:kpe,j,P_mu_m3CH4) &
     768           +zdqfi_omp(subs,kps:kpe,7)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
     769      scalar(i,kps:kpe,j,P_CH4)=scalar(i,kps:kpe,j,P_CH4) &
     770           +zdqfi_omp(subs,kps:kpe,8)*dt * (1.d0+scalar(i,kps:kpe,j,P_CH4))
    741771    CASE DEFAULT
    742772      !SCALAR(i,kps:kpe,j,2:nq+1)=SCALAR(i,kps:kpe,j,2:nq+1)+zdqfi_omp(subs,kps:kpe,1:nq)*dt !!! here dt is needed
  • trunk/WRF.COMMON/INTERFACES_V4/module_model_constants.F

    r2872 r3661  
    2626   REAL :: cp !          = 7.*r_d/2.  !
    2727
    28    REAL    , PARAMETER :: r_v          = 461.6      ! gas constant for water vapor (J deg^-1 kg^-1)
     28   REAL :: r_v !         = 461.6      ! gas constant for water vapor (J deg^-1 kg^-1)
    2929   REAL :: cv !          = cp-r_d     ! Specific heat of air at contant volume (J deg^-1 kg^-1)
    3030   REAL :: cpv !         = 4.*r_v
    3131   REAL :: cvv !         = cpv-r_v    !
    3232   REAL :: cvpm !        = -cv/cp
    33    REAL    , PARAMETER :: cliq         = 4190.      ! specific heat of liquid water at 0^oC
    34    REAL    , PARAMETER :: cice         = 2106.      ! specific heat of ice at 0^oC
    35    REAL    , PARAMETER :: psat         = 610.78
     33   REAL :: cliq !        = 4190.      ! specific heat of liquid water at 0^oC
     34   REAL :: cice !        = 2106.      ! specific heat of ice at 0^oC
     35   REAL :: psat !        = 610.78
    3636   REAL :: rcv !         = r_d/cv     !
    3737   REAL :: rcp !         = r_d/cp
     
    4949   REAL :: reradius !     = 1./6370.0e03  ! reciprocal of earth radius (m^-1)
    5050
    51    REAL    , PARAMETER :: asselin      = .025
     51   REAL    , PARAMETER :: asselin      = .025 ! for asselin filter?
    5252!   REAL    , PARAMETER :: asselin      = .0
    53    REAL    , PARAMETER :: cb           = 25.
     53   REAL :: cb !          = 25.
    5454
    5555   REAL    , PARAMETER :: XLV0         = 3.15E6       !  constant defined for calculation of latent heating
     
    266266     g            = 1.35
    267267     r_d          = 298.734319568
     268     r_v          = 518.          ! gas constant for methane vapor at Titan (J.K-1.kg-1)
    268269     cp           = 1038.72627727
    269270     t0           = 94. ! earth : 300
Note: See TracChangeset for help on using the changeset viewer.