Changeset 2398


Ignore:
Timestamp:
Nov 19, 2015, 12:19:38 PM (9 years ago)
Author:
jyg
Message:

Introduction of two new flags (ok_conv_stop
[Def=F], ok_intermittent [Def=F]) and one new
parameter (tau_stop [Def=15000]) in
conv_param.data:

. ok_conv_stop=T => convective mass fluxes are

set to zero if there is no trigger for a time
lapse longer than tau_stop.

. ok_intermittent=T => intermittent convection is

represented; the change concerns the upper
bound on the cloud base mass flux in
cv3p2_closure.F90.

The upper bound on Alp in physiq.F90 should

also be changed: this is still to be done.

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

Legend:

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

    r2393 r2398  
    9393    tau = 8000.
    9494
     95! -- end of convection
     96
     97    tau_stop = 15000.
     98    ok_convstop = .False.
     99
     100    ok_intermittent = .False.
     101
    95102! -- interface cloud parameterization:
    96103
     
    111118    READ (99, *, END=9998) flag_wb
    112119    READ (99, *, END=9998) wbmax
     120    READ (99, *, END=9998) ok_convstop
     121    READ (99, *, END=9998) tau_stop
     122    READ (99, *, END=9998) ok_intermittent
    1131239998 CONTINUE
    114124    CLOSE (99)
     
    122132    WRITE (*, *) 'flag_wb =', flag_wb
    123133    WRITE (*, *) 'wbmax =', wbmax
     134    WRITE (*, *) 'ok_convstop =', ok_convstop
     135    WRITE (*, *) 'tau_stop =', tau_stop
     136    WRITE (*, *) 'ok_intermittent =', ok_intermittent
    124137
    125138! IM Lecture du fichier ep_param.data
     
    145158   CALL bcast(flag_wb)
    146159   CALL bcast(wbmax)
     160   CALL bcast(ok_convstop)
     161   CALL bcast(tau_stop)
     162   CALL bcast(ok_intermittent)
    147163
    148164   CALL bcast(flag_epkeorig)
     
    163179! c      alpha  = alpha*1.5
    164180
     181  noconv_stop = max(2.,tau_stop/delt)
     182
    165183  RETURN
    166184END SUBROUTINE cv3_param
     185
     186SUBROUTINE cv3_incrcount(len, nd, delt, sig)
     187
     188IMPLICIT NONE
     189
     190! =====================================================================
     191!  Increment the counter sig(nd)
     192! =====================================================================
     193
     194  include "cv3param.h"
     195
     196!inputs:
     197  INTEGER, INTENT(IN)                     :: len
     198  INTEGER, INTENT(IN)                     :: nd
     199  REAL, INTENT(IN)                        :: delt ! timestep (seconds)
     200
     201!input/output
     202  REAL, DIMENSION(len,nd), INTENT(INOUT)  :: sig
     203
     204!local variables
     205  INTEGER il
     206
     207!    print *,'cv3_incrcount : noconv_stop ',noconv_stop
     208!    print *,'cv3_incrcount in, sig(1,nd) ',sig(1,nd)
     209    IF(ok_convstop) THEN
     210      DO il = 1, len
     211        sig(il, nd) = sig(il, nd) + 1.
     212        sig(il, nd) = min(sig(il,nd), noconv_stop+0.1)
     213      END DO
     214    ELSE
     215      DO il = 1, len
     216        sig(il, nd) = sig(il, nd) + 1.
     217        sig(il, nd) = min(sig(il,nd), 12.1)
     218      END DO
     219    ENDIF  ! (ok_convstop)
     220!    print *,'cv3_incrcount out, sig(1,nd) ',sig(1,nd)
     221
     222  RETURN
     223END SUBROUTINE cv3_incrcount
    167224
    168225SUBROUTINE cv3_prelim(len, nd, ndp1, t, q, p, ph, &
  • LMDZ5/trunk/libf/phylmd/cv3p2_closure.F90

    r2374 r2398  
    6262  REAL, DIMENSION (nloc, nd)                         :: dtmin, sigold
    6363  REAL, DIMENSION (nloc, nd)                         :: coefmix
     64  REAL, DIMENSION (nloc)                             :: dtminmax
    6465  REAL, DIMENSION (nloc)                             :: pzero, ptop2old
    6566  REAL, DIMENSION (nloc)                             :: cina, cinb
     
    163164  ! -------------------------------------------------------------
    164165
     166!jyg<
     167  IF (ok_convstop) THEN
     168    DO k = 1, nl - 1
     169      DO il = 1, ncum
     170        IF (sig(il,nd)<1.5 .OR. sig(il,nd)>noconv_stop) THEN
     171          sig(il, k) = 0.0
     172          w0(il, k) = 0.0
     173        END IF
     174      END DO
     175    END DO
     176  ELSE
    165177  DO k = 1, nl - 1
    166178    DO il = 1, ncum
     
    171183    END DO
    172184  END DO
     185  ENDIF  ! (ok_convstop)
     186!>jyg
    173187  IF (prt_level>=20) PRINT *, 'cv3p2_closure apres 400'
    174188
     
    427441  DO il = 1, ncum
    428442    cape(il) = 0.0
     443    dtminmax(il) = -100.
    429444  END DO
    430445
     
    447462    END DO
    448463  END DO
     464!jyg<
     465!  Store maximum of dtmin
     466!  C est pas terrible d avoir ce test sur Ale+Cin encore une fois ici.
     467!                      A REVOIR !
     468  DO k = 1, nl
     469    DO il = 1, ncum
     470      IF (k>=(icb(il)+1) .AND. k<=inb(il) .AND. ale(il)+cin(il)>0.) THEN
     471        dtminmax(il) = max(dtmin(il,k), dtminmax(il))
     472      ENDIF
     473    END DO
     474  END DO
     475!
     476!    prevent convection when ale+cin <= 0
     477  DO k = 1, nl
     478    DO il = 1, ncum
     479      IF (k>=(icb(il)+1) .AND. k<=inb(il)) THEN
     480        dtmin(il,k) = min(dtmin(il,k), dtminmax(il))
     481      ENDIF
     482    END DO
     483  END DO
     484!>jyg
    449485!
    450486  IF (prt_level >= 20) THEN
    451487    print *,'cv3p2_closure: dtmin ', (k, dtmin(igout,k), k=1,nl)
     488    print *,'cv3p2_closure: dtminmax ', dtminmax(igout)
    452489  ENDIF
    453490!
     
    588625  END DO
    589626
     627!jyg<
     628  IF (OK_intermittent) THEN
     629    DO il = 1, ncum
     630      IF (cbmflim(il)>1.E-6) THEN
     631        cbmfalpb(il) = min(cbmfalp(il), (cbmfmax(il)-beta*cbmf0(il))/(1.-beta))
     632        ! print*,'cbmfalpb',cbmfalpb(il),cbmfmax(il)
     633      END IF
     634    END DO
     635  ELSE
     636!>jyg
    590637  DO il = 1, ncum
    591638    IF (cbmflim(il)>1.E-6) THEN
     
    599646    END IF
    600647  END DO
     648  ENDIF  !(OK_intermittent)
    601649  IF (prt_level>=20) PRINT *, 'cv3p2_closure apres cbmfalpb: cbmfalpb ',cbmfalpb(igout)
    602650
     
    637685  ! c     decreasing (i.e. if the final mass flux (cbmflast) is greater than
    638686  ! c     the target mass flux (cbmfalpb)).
     687  ! c    If(ok_convstop): set iflag to 4 if no positive buoyancy has been met
    639688
    640689!jyg  DO il = 1, ncum
     
    658707  END DO
    659708
     709!jyg<
     710  IF (ok_convstop) THEN
     711    DO il = 1, ncum
     712      IF (dtminmax(il) .LE. 0.) THEN
     713        iflag(il) = 4
     714      END IF
     715    END DO
     716  ELSE
     717!>jyg
    660718  DO k = 1, nl
    661719    DO il = 1, ncum
     
    667725    END DO
    668726  END DO
     727  ENDIF ! (ok_convstop)
    669728!
    670729  IF (prt_level >= 10) THEN
  • LMDZ5/trunk/libf/phylmd/cv3param.h

    r2253 r2398  
    77!------------------------------------------------------------
    88
     9      logical ok_convstop
     10      logical ok_intermittent
    911      integer noff, minorig, nl, nlp, nlm
    1012      real sigdz, spfac
     
    1517      real dtovsh, dpbase, dttrig
    1618      real dtcrit, tau, beta, alpha, alpha1
     19      real tau_stop, noconv_stop
    1720      real wbmax
    1821      real delta
     
    2528                      ,dtovsh, dpbase, dttrig &
    2629                      ,dtcrit, tau, beta, alpha, alpha1 &
     30                      ,tau_stop, noconv_stop &
    2731                      ,wbmax &
    2832                      ,delta, betad  &
    2933                      ,flag_epKEorig &
    3034                      ,flag_wb &
    31                       ,noff, minorig, nl, nlp, nlm
     35                      ,noff, minorig, nl, nlp, nlm  &
     36                      ,ok_convstop, ok_intermittent
    3237!$OMP THREADPRIVATE(/cv3param/)
    3338
  • LMDZ5/trunk/libf/phylmd/cva_driver.F90

    r2397 r2398  
    622622  END DO
    623623
     624!!  IF (iflag_con==3) THEN
     625!!    DO il = 1, len
     626!!      sig1(il, nd) = sig1(il, nd) + 1.
     627!!      sig1(il, nd) = amin1(sig1(il,nd), 12.1)
     628!!    END DO
     629!!  END IF
     630
    624631  IF (iflag_con==3) THEN
    625     DO il = 1, len
    626       sig1(il, nd) = sig1(il, nd) + 1.
    627       sig1(il, nd) = amin1(sig1(il,nd), 12.1)
    628     END DO
    629   END IF
     632      CALL cv3_incrcount(len,nd,delt,sig1)
     633  END IF  ! (iflag_con==3)
    630634
    631635! RomP >>>
Note: See TracChangeset for help on using the changeset viewer.