Changeset 3276 for trunk


Ignore:
Timestamp:
Mar 20, 2024, 4:29:20 PM (8 months ago)
Author:
jleconte
Message:

moist_adj_generic cleaned, completed and commented

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/moistadj_generic.F90

    r3104 r3276  
    11subroutine moistadj_generic(ngrid, nlayer, nq, pt, pq, pdq, pplev, pplay, pdtmana, pdqmana, ptimestep, rneb)
    22
    3    !use watercommon_h, only: T_h2O_ice_liq, RLVTT, RCPD, RCPV, Psat_water, Lcpdqsat_water
    4    !USE tracer_h, only: igcm_h2o_vap, igcm_h2o_ice
    53   use generic_cloud_common_h
    64   use generic_tracer_index_mod, only: generic_tracer_index
     
    2119!     -------
    2220!     Adapted from the moistadj.F90 routine
    23 !     for generic tracers (condensable species)
     21!     for generic condensable species (GCS) tracers
    2422!     by Noe CLEMENT (2023)
    2523!     
     
    7573      DOUBLE PRECISION :: zdp, zdpm
    7674
    77       real q_cri(ngrid,nlayer)
     75      real q_cri(ngrid,nlayer) ! moist convection inhibition criterion
    7876
    7977      REAL zsat ! super-saturation
     
    9997
    10098         RCPD = cpp
    101          ! RCPV   = 1.88e3 ! specific heat capacity of water vapor at 350K ! MUST BE CHANGED !!!
    102          ! 1.709e3 for methane - should be added in table_tracers_condensable (datagcm)
    10399
    104100         write(*,*) "value for metallicity? "
     
    116112               RLVTT_generic = constants_RLVTT_generic(iq)
    117113               RCPV_generic = constants_RCPV_generic(iq)
     114               Tref = constants_Tref(iq)
     115
     116               write(*,*) noms(igcm_generic_vap),", q_cri at ", Tref, "K (in kg/kg): ", ( 1 / (1 - 1/epsi_generic)) * (r * mugaz/1000.) / delta_vapH * Tref
     117
    118118            endif
    119119         enddo
     
    158158            call Lcpdqsat_generic(v_t,v_p,zpsat(i,k),zqs(i,k),zdqs(i,k),zdlnpsat(i,k))
    159159
    160             !call Psat_water(v_t,v_p,zpsat(i,k),zqs(i,k))
    161             !call Lcpdqsat_water(v_t,v_p,zpsat(i,k),zqs(i,k),zdqs(i,k),zdlnpsat(i,k))
    162160         ENDDO
    163161      ENDDO
     
    179177            gamcpdz(i,k) = ( (R/RCPD*v_cptt2*(1.- v_zqs) + RLVTT_generic*v_zqs) * (pplay(i,k-1)-pplay(i,k))/pplev(i,k) )  &
    180178               / (((1.- v_zqs) + v_zqs * RCPV_generic/RCPD)*v_pratio + v_zqs  * v_dlnpsat)               
     179            ! Note that gamcpdz is defined as positive, so -gamcpdz is the real moist-adiabatic gradient [dT/dz]_ad
    181180         ENDDO
    182181      ENDDO
    183182     
    184       !     calculates moist convection inhibition criterion
    185       DO k = 1, nlayer
    186          DO i = 1, ngrid
    187             q_cri(i,k) = ( 1 / (1 - 1/epsi_generic)) * r * mugaz/1000. / delta_vapH * zt(i,k)
    188          ENDDO
    189       ENDDO
    190 
    191       write(*,*) "q_cri at 80K : ", ( 1 / (1 - 1/epsi_generic)) * (r * mugaz/1000.) / delta_vapH * 80
    192 
    193 !------------------------------------ modification of unstable profile
     183      ! calculate moist convection inhibition criterion
     184      IF (epsi_generic .gt. 1) THEN ! GCS molecular weight is heavier than dry gas:
     185         ! inhibition of moist convection if vapor amount exceeds q_cri (Eq. 17 of Leconte et al. 2017)
     186         DO k = 1, nlayer
     187            DO i = 1, ngrid
     188               q_cri(i,k) = ( 1 / (1 - 1/epsi_generic)) * r * mugaz/1000. / delta_vapH * zt(i,k)
     189            ENDDO
     190         ENDDO
     191      ELSE ! GCS molecular weight is lighter than dry gas
     192         DO k = 1, nlayer
     193            DO i = 1, ngrid
     194               q_cri(i,k) = 2. ! vapor amount will never exceed q_cri, q_cri call becomes transparent in the next lines
     195            ENDDO
     196         ENDDO
     197      ENDIF
     198
     199
     200!------------------------------------ defining the bottom (k1) and the top (k2) of the moist-convective column
    194201      DO 9999 i = 1, ngrid
    195202
     
    209216         +(local_q(i,k2)-zqs(i,k2))*(pplev(i,k2)-pplev(i,k2+1))
    210217
     218      ! if: (gradient is not steeper than moist-adiabat) or (level is not saturated) or (moist convection is inhibited because criterion is satisfied)
     219      ! then: no moist convection (GO TO 810)
    211220      IF ( zflo.LE.0.0 .OR. zsat.LE.0.0 .OR. local_q(i,k2-1).GT.q_cri(i,k2-1)) GOTO 810
    212221      k1 = k2 - 1
     
    224233   821 CONTINUE
    225234
    226 !------------------------------------------------------ local adjustment
     235!------------------------------------------------------ local adjustment of the moist-convective column between k1 and k2
    227236   830 CONTINUE ! actual adjustment
    228237   Do nn=1,niter
     
    254263         call Psat_generic(v_t,v_p,metallicity,zpsat(i,k),zqs(i,k))
    255264         call Lcpdqsat_generic(v_t,v_p,zpsat(i,k),zqs(i,k),zdqs(i,k),zdlnpsat(i,k))
    256          
    257          !call Psat_water(v_t,v_p,zpsat(i,k),zqs(i,k))
    258          !call Lcpdqsat_water(v_t,v_p,zpsat(i,k),zqs(i,k),zdqs(i,k),zdlnpsat(i,k))
    259265
    260266      ENDDO
     
    293299!     Test to see if we've reached the bottom
    294300
    295       IF (k1 .EQ. 1) GOTO 841 ! yes we have!
     301      IF (k1 .EQ. 1) GOTO 841 ! yes we have! the bottom of moist-convective column is the bottom of the model
     302
    296303      zflo = v_cptt(i,k1-1) - v_cptt(i,k1) - gamcpdz(i,k1)
    297304      zsat=(local_q(i,k1-1)-zqs(i,k1-1))*(pplev(i,k1-1)-pplev(i,k1))   &
    298305         + (local_q(i,k1)-zqs(i,k1))*(pplev(i,k1)-pplev(i,k1+1))
    299       IF (zflo.LE.0.0 .OR. zsat.LE.0.0) GOTO 841 ! yes we have!
     306
     307      IF (zflo.LE.0.0 .OR. zsat.LE.0.0 .OR. local_q(i,k1-1).GT.q_cri(i,k1-1)) GOTO 841 ! yes we have!
     308      ! the bottom of the moist-convective column is no more convective: GOTO 841
    300309
    301310   840 CONTINUE
    302311      k1 = k1 - 1
    303312      IF (k1 .EQ. 1) GOTO 830 ! GOTO 820 (a tester, Z.X.Li, mars 1995)
     313      ! bottom of moist-convective column is bottom of the model but is still convective: GOTO 830
    304314      zsat = zsat + (local_q(i,k1-1)-zqs(i,k1-1))               &
    305315                  *(pplev(i,k1-1)-pplev(i,k1))
    306316      zflo = v_cptt(i,k1-1) - v_cptt(i,k1) - gamcpdz(i,k1)
    307       IF (zflo.GT.0.0 .AND. zsat.GT.0.0) THEN
     317      IF (zflo.GT.0.0 .AND. zsat.GT.0.0 .AND. local_q(i,k1-1).LT.q_cri(i,k1-1)) THEN
     318         ! the bottom of the moist-convective column is still convective
     319         ! we continue to search for the non-convective bottom
    308320         GOTO 840
    309321      ELSE
     322         ! the bottom of the moist-convective column is no more convective now,
     323         ! but, since the bottom of moist-convective column has changed, we must do again the adjustment
    310324         GOTO 830 ! GOTO 820 (a tester, Z.X.Li, mars 1995)
    311325      ENDIF
     
    313327
    314328      GOTO 810 ! look for other layers higher up
     329      ! because there could be other moist-convective columns higher up (but separated from the one we have just calculated before)
    315330
    3163319999 CONTINUE ! loop over all the points
    317332
    318333!-----------------------------------------------------------------------
    319 ! Determine the cloud fraction (hypothese: la nebulosite a lieu
    320 ! a l'endroit ou la vapeur d'eau est diminuee par l'ajustement):
     334! Determine the cloud fraction (hypothesis: nebulosity occurs
     335! where GCS vapor is reduced by adjustment):
    321336
    322337      DO k = 1, nlayer
     
    329344      ENDDO
    330345
    331 ! Distribuer l'eau condensee en eau liquide nuageuse (hypothese:
    332 ! l'eau liquide est distribuee aux endroits ou la vapeur d'eau
    333 ! diminue et d'une maniere proportionnelle a cet diminution):
     346! Distribute GCS condensates into cloudy liquid/solid condensates (hypothesis:
     347! liquid/solid condensates are distributed to areas where GCS vapor
     348! decreases and are distributed in proportion to this decrease):
    334349      DO i = 1, ngrid
    335350         IF (itest(i)) THEN
     
    368383      ENDDO
    369384
    370 !    now subroutine -----> GCM variables
     385      ! now subroutine -----> GCM variables
    371386      DO k = 1, nlayer
    372387         DO i = 1, ngrid
Note: See TracChangeset for help on using the changeset viewer.