Changeset 2761


Ignore:
Timestamp:
Jan 11, 2017, 12:39:50 PM (7 years ago)
Author:
jyg
Message:

Two options introduced concerning deep convection
and wakes:

+ deep convection is allowed only when top
temperature is lower than t_top_max.
(Default: t_top_max=1000.).
+ wake number per unit area may now be
different over ocean and over land:
wdens_ref_o and wdens_ref_l.
(Default is:wdens_ref_o=8.e-12,
wdens_ref_l=8.e-12)


Location:
LMDZ5/trunk/libf/phylmd
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/calwake.F90

    r2671 r2761  
    2626
    2727  USE dimphy
     28  USE phys_state_var_mod, ONLY: pctsrf
     29  USE indice_sol_mod, ONLY: is_oce
     30  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
    2831  IMPLICIT NONE
    2932  ! ======================================================================
     
    5154  ! ------
    5255  REAL, DIMENSION(klon, klev),   INTENT (OUT)        :: dt_wake, dq_wake
    53   INTEGER, DIMENSION(klon),      INTENT (OUT)        :: wake_k
     56  REAL, DIMENSION(klon),         INTENT (OUT)        :: wake_k
    5457  REAL, DIMENSION(klon, klev),   INTENT (OUT)        :: wake_d_deltat_gw
    5558  REAL, DIMENSION(klon),         INTENT (OUT)        :: wake_h
     
    6972  ! -----------------
    7073  INTEGER                                            :: i, l
     74  INTEGER, DIMENSION(klon)                           :: znatsurf    ! 0 if pctsrf(is_oce)>0.1; 1 else.
    7175  REAL                                               :: aire
    7276  REAL, DIMENSION(klon, klev)                        :: p,  pi
     
    97101
    98102
    99   ! print *, '-> calwake, wake_s ', wake_s(1)
     103  IF (prt_level >= 10) THEN
     104    print *, '-> calwake, wake_s input ', wake_s(1)
     105  ENDIF
    100106
    101107  rdcp = 1./3.5
     108
     109  znatsurf(:) = 0
     110  DO i = 1,klon
     111    IF (pctsrf(i,is_oce) < 0.1) znatsurf(i) = 1
     112  ENDDO
    102113
    103114
     
    124135  END DO
    125136
     137!----------------------------------------------------------------
     138!         Initialize tendencies to zero
     139!----------------------------------------------------------------
     140dtls(:,:) = 0.
     141dqls(:,:) = 0.
     142d_deltat_gw(:,:) = 0.
     143d_deltatw(:,:) = 0.
     144d_deltaqw(:,:) = 0.
     145d_sigmaw(:) = 0.
     146d_wdens(:) = 0.
     147!
     148
    126149  DO i = 1, klon
    127150    sigd0(i) = sigd(i)
     
    132155  END DO
    133156
    134   DO i = 1, klon
    135     ktopw(i) = wake_k(i)
    136   END DO
     157!!jyg!  DO i = 1, klon                 
     158!!jyg!    ktopw(i) = NINT(wake_k(i))   
     159!!jyg!  END DO                         
    137160
    138161  DO i = 1, klon
     
    178201  END DO
    179202
    180   CALL wake(p, ph, pi, dtime, &
     203  CALL wake(znatsurf, p, ph, pi, dtime, &
    181204    te, qe, omgbe, &
    182205    dtdwn, dqdwn, amdwn, amup, dta, dqa, &
     
    254277    END IF
    255278  END DO
     279!
    256280
    257281!jyg< 
  • LMDZ5/trunk/libf/phylmd/cv3_routines.F90

    r2759 r2761  
    8585     cv_flag_feed=1
    8686     CALL getin_p('cv_flag_feed',cv_flag_feed)
     87     T_top_max = 1000.
     88     CALL getin_p('t_top_max',T_top_max)
    8789     dpbase=-40.
    8890     CALL getin_p('dpbase',dpbase)
     
    119121     CALL getin_p('tlcrit',tlcrit)
    120122
     123    WRITE (*, *) 't_top_max=', t_top_max
    121124    WRITE (*, *) 'dpbase=', dpbase
    122125    WRITE (*, *) 'pbcrit=', pbcrit
     
    10711074END SUBROUTINE icefrac
    10721075
    1073 SUBROUTINE cv3_undilute2(nloc, ncum, nd, icb, icbs, nk, &
     1076SUBROUTINE cv3_undilute2(nloc, ncum, nd, iflag, icb, icbs, nk, &
    10741077                         tnk, qnk, gznk, hnk, t, q, qs, gz, &
    10751078                         p, ph, h, tv, lv, lf, pbase, buoybase, plcl, &
     
    11161119  REAL, DIMENSION (nloc, nd), INTENT (INOUT)         :: tp, tvp, clw   ! Input for k = 1, icb+1 (computed in cv3_undilute1)
    11171120                                                                       ! Output above
     1121  INTEGER, DIMENSION (nloc), INTENT (INOUT)          :: iflag
    11181122
    11191123!outputs:
     
    15941598! ori          frac(i)=max(frac(i),0.0)
    15951599! ori 540  continue
     1600
     1601! --------------------------------------------------------------------
     1602!   Prevent convection when top is too hot
     1603! --------------------------------------------------------------------
     1604  DO i = 1,ncum
     1605    IF (t(i,inb(i)) > T_top_max) iflag(i) = 10
     1606  ENDDO
    15961607
    15971608! =====================================================================
  • LMDZ5/trunk/libf/phylmd/cv3param.h

    r2757 r2761  
    2020      real dtovsh, dpbase, dttrig
    2121      real dtcrit, tau, beta, alpha, alpha1
     22      real T_top_max
    2223      real tau_stop, noconv_stop
    2324      real wbmax
     
    3233                      ,dtovsh, dpbase, dttrig &
    3334                      ,dtcrit, tau, beta, alpha, alpha1 &
     35                      ,T_top_max &
    3436                      ,tau_stop, noconv_stop &
    3537                      ,wbmax &
  • LMDZ5/trunk/libf/phylmd/cva_driver.F90

    r2654 r2761  
    353353!         9     No moist convection: cloud base is higher
    354354!               then the level NL-1.
     355!        10     No moist convection: cloud top is too warm.
     356!
    355357
    356358! ft:   Array of temperature tendency (K/s) of dimension ND, defined at same
     
    907909        if (prt_level >= 9) &
    908910             PRINT *, 'cva_driver -> cv3_undilute2'
    909       CALL cv3_undilute2(nloc, ncum, nd, icb, icbs, nk, &              !na->nd
     911      CALL cv3_undilute2(nloc, ncum, nd, iflag, icb, icbs, nk, &        !na->nd
    910912                         tnk, qnk, gznk, hnk, t, q, qs, gz, &
    911913                         p, ph, h, tv, lv, lf, pbase, buoybase, plcl, &
  • LMDZ5/trunk/libf/phylmd/wake.F90

    r2759 r2761  
    22! $Id$
    33
    4 SUBROUTINE wake(p, ph, pi, dtime, &
     4SUBROUTINE wake(znatsurf, p, ph, pi, dtime, &
    55                te0, qe0, omgb, &
    66                dtdwn, dqdwn, amdwn, amup, dta, dqa, &
     
    124124  ! --------------------
    125125
     126  INTEGER, DIMENSION (klon),        INTENT(IN)          :: znatsurf
    126127  REAL, DIMENSION (klon, klev),     INTENT(IN)          :: p, pi
    127128  REAL, DIMENSION (klon, klev+1),   INTENT(IN)          :: ph
     
    167168  LOGICAL, SAVE                                         :: first = .TRUE.
    168169  !$OMP THREADPRIVATE(first)
    169   REAL, SAVE                                            :: stark, wdens_ref, coefgw, alpk
     170!jyg<
     171!!  REAL, SAVE                                            :: stark, wdens_ref, coefgw, alpk
     172  REAL, SAVE, DIMENSION(2)                              :: wdens_ref
     173  REAL, SAVE                                            :: stark, coefgw, alpk
     174!>jyg
    170175  REAL, SAVE                                            :: crep_upper, crep_sol 
    171176  !$OMP THREADPRIVATE(stark, wdens_ref, coefgw, alpk, crep_upper, crep_sol)
     
    319324  alpk=0.25
    320325  CALL getin_p('alpk',alpk)
    321   wdens_ref=8.E-12
    322   CALL getin_p('wdens_ref',wdens_ref)
     326!jyg<
     327!!  wdens_ref=8.E-12
     328!!  CALL getin_p('wdens_ref',wdens_ref)
     329  wdens_ref(1)=8.E-12
     330  wdens_ref(2)=8.E-12
     331  CALL getin_p('wdens_ref_o',wdens_ref(1))    !wake number per unit area ; ocean
     332  CALL getin_p('wdens_ref_l',wdens_ref(2))    !wake number per unit area ; land
     333!>jyg
    323334  coefgw=4.
    324335  CALL getin_p('coefgw',coefgw)
     
    326337  WRITE(*,*) 'stark=', stark
    327338  WRITE(*,*) 'alpk=', alpk
    328   WRITE(*,*) 'wdens_ref=', wdens_ref
     339!jyg<
     340!!  WRITE(*,*) 'wdens_ref=', wdens_ref
     341  WRITE(*,*) 'wdens_ref_o=', wdens_ref(1)
     342  WRITE(*,*) 'wdens_ref_l=', wdens_ref(2)
     343!>jyg
    329344  WRITE(*,*) 'coefgw=', coefgw
    330345
     
    339354  ! Les densites peuvent evoluer si les poches debordent
    340355  ! (voir au tout debut de la boucle sur les substeps)
    341   wdens(:) = wdens_ref
     356!jyg<
     357!!  wdens(:) = wdens_ref
     358  DO i = 1,klon
     359    wdens(i) = wdens_ref(znatsurf(i)+1)
     360  ENDDO
     361!>jyg
    342362
    343363  ! print*,'stark',stark
Note: See TracChangeset for help on using the changeset viewer.