Ignore:
Timestamp:
Jan 16, 2023, 4:47:09 PM (23 months ago)
Author:
jleconte
Message:

Use new tendencies with symbol PLA for planet

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/WRF.COMMON/INTERFACES_V4/module_lmd_driver.F

    r2868 r2869  
    3030        RADT, &
    3131        TSK,PSFC, &
    32         RTHBLTEN,RUBLTEN,RVBLTEN, &
     32        RTHPLATEN,RUPLATEN,RVPLATEN, &
    3333        num_3d_s,SCALAR, &
    3434        num_3d_m,moist, &
     
    117117     dz8w,p8w,p,exner,t,t8w,rho,u,v,z,th,p_hyd,p_hyd_w
    118118REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(OUT ) :: &
    119      RTHBLTEN,RUBLTEN,RVBLTEN, &
     119     RTHPLATEN,RUPLATEN,RVPLATEN, &
    120120     HR_SW,HR_LW,HR_DYN,DDT,DT_RAD,DT_VDF,RDUST,VMR_ICE,RICE,&
    121121     CLOUDFRAC,RH,DQICE,DQVAP,DTLSC,DTRAIN,DT_MOIST,H2OICE_REFF
     
    442442IF (TRACER_MODE .EQ. 0) THEN
    443443    q_prof(:,1)=0.95
     444ELSE IF (TRACER_MODE .GE. 1) THEN
     445    ! to be clean we should have an automatized process that makes sure that moist is sent to igcm_h2o_vap and etc.
     446    q_prof(:,1) = SCALAR(i,kps:kpe,j,P_QH2O) / (1.d0 + SCALAR(i,kps:kpe,j,P_QH2O)) !! P_xxx is the index for variable xxx.
     447    q_prof(:,2) = SCALAR(i,kps:kpe,j,P_QH2O_ICE) / (1.d0 + SCALAR(i,kps:kpe,j,P_QH2O))
     448    ! conversion from mass mixing ratio in WRF to specific concentration in Physiq
    444449ELSE IF (TRACER_MODE .GE. 42) THEN
    445450    ! to be clean we should have an automatized process that makes sure that moist is sent to igcm_h2o_vap and etc.
     
    684689!! DEDUCE TENDENCIES FOR WRF !!
    685690!!***************************!!
    686 RTHBLTEN(ims:ime,kms:kme,jms:jme)=0.
    687 RUBLTEN(ims:ime,kms:kme,jms:jme)=0.
    688 RVBLTEN(ims:ime,kms:kme,jms:jme)=0.
     691RTHPLATEN(ims:ime,kms:kme,jms:jme)=0.
     692RUPLATEN(ims:ime,kms:kme,jms:jme)=0.
     693RVPLATEN(ims:ime,kms:kme,jms:jme)=0.
    689694PSFC(ims:ime,jms:jme)=p8w(ims:ime,kms,jms:jme) ! was done in surface driver in regular WRF
    690695!------------------------------------------------------------------!
     
    702707
    703708    ! zonal wind
    704   RUBLTEN(i,kps:kpe,j) = zdufi_omp(subs,kps:kpe)
     709  RUPLATEN(i,kps:kpe,j) = zdufi_omp(subs,kps:kpe)
    705710    ! meridional wind
    706   RVBLTEN(i,kps:kpe,j) = zdvfi_omp(subs,kps:kpe)
     711  RVPLATEN(i,kps:kpe,j) = zdvfi_omp(subs,kps:kpe)
    707712    ! potential temperature
    708713    ! (dT = dtheta * exner for isobaric coordinates or if pressure variations are negligible)
    709   RTHBLTEN(i,kps:kpe,j) = zdtfi_omp(subs,kps:kpe) / exner(i,kps:kpe,j)
     714  RTHPLATEN(i,kps:kpe,j) = zdtfi_omp(subs,kps:kpe) / exner(i,kps:kpe,j)
    710715    ! update surface pressure (cf CO2 cycle in physics)
    711716    ! here dt is needed
     
    722727      SCALAR(i,kps:kpe,j,2) = SCALAR(i,kps:kpe,j,2)*exp(-dt/tau_decay)
    723728      SCALAR(i,1,j,2) = SCALAR(i,1,j,2) + 1. !! this tracer is emitted in the surface layer
     729    CASE(1)
     730      scalar(i,kps:kpe,j,P_QH2O)=scalar(i,kps:kpe,j,P_QH2O) &
     731          +zdqfi_omp(subs,kps:kpe,1)*dt * (1.d0+scalar(i,kps:kpe,j,P_QH2O))
     732      scalar(i,kps:kpe,j,P_QH2O_ICE)=scalar(i,kps:kpe,j,P_QH2O_ICE) &
     733           +zdqfi_omp(subs,kps:kpe,2)*dt * (1.d0+scalar(i,kps:kpe,j,P_QH2O))
     734       ! if you want to use this mode, RTHPLATEN should be corrected as below.
     735       ! we keep it like that for the moment for testing.
    724736    CASE(42)
    725737      moist(i,kps:kpe,j,P_QV)=moist(i,kps:kpe,j,P_QV) &
     
    727739      scalar(i,kps:kpe,j,P_QH2O_ICE)=scalar(i,kps:kpe,j,P_QH2O_ICE) &
    728740           +zdqfi_omp(subs,kps:kpe,2)*dt * (1.d0+moist(i,kps:kpe,j,P_QV))
    729        ! if you want to use this mode, RTHBLTEN should be corrected as below.
     741       ! if you want to use this mode, RTHPLATEN should be corrected as below.
    730742       ! we keep it like that for the moment for testing.
    731743    CASE(43)
     
    734746      scalar(i,kps:kpe,j,P_QH2O_ICE)=scalar(i,kps:kpe,j,P_QH2O_ICE) &
    735747           +zdqfi_omp(subs,kps:kpe,2)*dt * (1.d0+moist(i,kps:kpe,j,P_QV))
    736       RTHBLTEN(i,kps:kpe,j) = RTHBLTEN(i,kps:kpe,j) &
     748      RTHPLATEN(i,kps:kpe,j) = RTHPLATEN(i,kps:kpe,j) &
    737749        * (1.d0+moist(i,kps:kpe,j,P_QV))/(1.d0+rvovrd*moist(i,kps:kpe,j,P_QV))
    738750        ! correct dT/dt assuming a constant molar heat capacity.
Note: See TracChangeset for help on using the changeset viewer.