Changeset 2092 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Feb 7, 2019, 11:33:33 AM (6 years ago)
Author:
aboissinot
Message:

Uncomment two "corrections" (or "bidouilles" ccording to the author) in thermcell_flux. They are used only if
iflag_thermals_optflux is set to 0

Remove useless parameter fact_shell in thermcell_mod.

Location:
trunk/LMDZ.GENERIC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r2071 r2092  
    14441444- remove useless flag "iflag_thermals_alim" in thermcell_alim, thermcell_mod and thermcell_plume
    14451445- replace watersat subroutine by Psat_water in the thermal plume model, cf. revision 1993 or 29/08/2018 JL comment.
     1446
     1447==07/02/2018 == AB
     1448- uncomment two "corrections" in thermcell_flux. They are used only if iflag_thermals_optflux is set to 0
     1449- remove useless parameter fact_shell in thermcell_mod
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_flux.F90

    r2060 r2092  
    159159         
    160160!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    161 ! AB : I comment the correction and replace it by an uncompromising test.
     161! AB : I remove the correction and replace it by an uncompromising test.
    162162!      According to the previous derivations, we MUST have positive mass flux
    163163!      everywhere! Indeed, as soon as fm becomes negative, the plume stops.
     
    186186! Test sur fraca constante ou croissante au-dessus de lalim
    187187!------------------------------------------------------------------------------
    188 ! AB : do we have to decree that?
    189 !         IF (iflag_thermals_optflux.eq.0) THEN
    190 !            DO ig=1,ngrid
    191 !               IF (l.ge.lalim(ig).and.l.le.lmax(ig).and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) THEN
    192 !                  zzz = fm(ig,l) * rhobarz(ig,l+1) * zw2(ig,l+1)              &
    193 !                  &   / (rhobarz(ig,l) * zw2(ig,l))
    194 !                 
    195 !                  IF (fm(ig,l+1).gt.zzz) THEN
    196 !                     detr(ig,l) = detr(ig,l) + fm(ig,l+1) - zzz
    197 !                     fm(ig,l+1) = zzz
    198 !                     ncorecfm4  = ncorecfm4 + 1
    199 !                  ENDIF
    200 !               ENDIF
    201 !            ENDDO
    202 !         ENDIF
     188! AB : Do we have to decree that? If so, set iflag_thermals_optflux to 0
     189         IF (iflag_thermals_optflux==0) THEN
     190            DO ig=1,ngrid
     191               IF (l.ge.lalim(ig).and.l.le.lmax(ig).and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) THEN
     192                  zzz = fm(ig,l) * rhobarz(ig,l+1) * zw2(ig,l+1)              &
     193                  &   / (rhobarz(ig,l) * zw2(ig,l))
     194                 
     195                  IF (fm(ig,l+1).gt.zzz) THEN
     196                     detr(ig,l) = detr(ig,l) + fm(ig,l+1) - zzz
     197                     fm(ig,l+1) = zzz
     198                     ncorecfm4  = ncorecfm4 + 1
     199                  ENDIF
     200               ENDIF
     201            ENDDO
     202         ENDIF
    203203         
    204204!------------------------------------------------------------------------------
    205205! Test sur flux de masse constant ou decroissant au-dessus de lalim
    206206!------------------------------------------------------------------------------
    207 ! AB : do we have to decree that?
    208 !         IF (iflag_thermals_optflux==0) THEN
    209 !            DO ig=1,ngrid
    210 !               IF ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
    211 !                  f_old = fm(ig,l+1)
    212 !                  fm(ig,l+1) = fm(ig,l)
    213 !                  detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1)
    214 !                  ncorecfm5  = ncorecfm5 + 1
    215 !               ENDIF
    216 !            ENDDO
    217 !         ENDIF
     207! AB : Do we have to decree that? If so, set iflag_thermals_optflux to 0
     208         IF (iflag_thermals_optflux==0) THEN
     209            DO ig=1,ngrid
     210               IF ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
     211                  f_old = fm(ig,l+1)
     212                  fm(ig,l+1) = fm(ig,l)
     213                  detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1)
     214                  ncorecfm5  = ncorecfm5 + 1
     215               ENDIF
     216            ENDDO
     217         ENDIF
    218218         
    219219!------------------------------------------------------------------------------
     
    488488     
    489489!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    490 ! AB : test added to avoid problem when lmax = 0, which is not a
    491 !      fortran array index.
     490! AB : test added to avoid problem when lmax = 0, which is not a fortran index.
    492491!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    493492      IF (lmax(ig).gt.0) THEN
     
    505504      IF (prt_level.ge.1) THEN
    506505         
    507 ! AB : those tests were removed for their uselessness.
     506! AB : those outputs are commented for their uselessness.
    508507!         IF (ncorecfm2.ge.1) THEN
    509508!            print *, 'WARNING: Outgoing mass flux has negative value(s)!'
     
    511510!         ENDIF
    512511         
    513 ! AB : those tests were removed because I don't know if we should decree them.
    514 !         IF (ncorecfm4.ge.1) THEN
    515 !            print *, 'WARNING: Deacreasing updraft fraction above lalim!'
    516 !            print *, 'in', ncorecfm4, 'point(s)'
    517 !         ENDIF
    518 !         IF (ncorecfm5.ge.1) THEN
    519 !            print *, 'WARNING: Increasing mass flux above lalim!'
    520 !            print *, 'in', ncorecfm5, 'point(s)'
    521 !         ENDIF
     512         IF (ncorecfm4.ge.1) THEN
     513            print *, 'WARNING: Deacreasing updraft fraction above lalim!'
     514            print *, 'in', ncorecfm4, 'point(s)'
     515         ENDIF
     516         
     517         IF (ncorecfm5.ge.1) THEN
     518            print *, 'WARNING: Increasing mass flux above lalim!'
     519            print *, 'in', ncorecfm5, 'point(s)'
     520         ENDIF
    522521         
    523522         IF (ncorecfm6.ge.1) THEN
     
    526525         ENDIF
    527526         
    528 ! AB : that test was removed because I don't know if we should decree it.
     527! AB : those outputs are commented because corresponding test is also commented.
    529528!         IF (ncorecfm7.ge.1) THEN
    530529!            print *, 'WARNING: Detrainment is greater than mass flux!'
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_mod.F90

    r2069 r2092  
    11MODULE thermcell_mod
    2 
    3 IMPLICIT NONE
    4 
    5 
     2     
     3      IMPLICIT NONE
     4     
     5     
    66! Flags for computations
    7                                                             !     default
    8 INTEGER,PARAMETER :: iflag_thermals_optflux     = 0         !     0
    9 INTEGER,PARAMETER :: iflag_thermals_closure     = 2         !     2
    10 INTEGER,PARAMETER :: iflag_thermals             = 18        !     18
    11 
    12 ! Flags for diagnoses
    13 
    14 LOGICAL,PARAMETER :: sorties                    = .false.   !     false
    15 INTEGER,PARAMETER :: iflag_trig_bl              = 1         !     1
    16 INTEGER,PARAMETER :: iflag_clos_bl              = 1         !     1
    17 INTEGER,PARAMETER :: iflag_coupl                = 5         !     5
    18 
     7                                                                  !  default
     8      INTEGER,PARAMETER :: iflag_thermals_optflux     = 1         !  0        !
     9      INTEGER,PARAMETER :: iflag_thermals_closure     = 2         !  2        !
     10      INTEGER,PARAMETER :: iflag_thermals             = 18        !  18       !
     11     
     12! Flags for (terrestrial) diagnoses
     13     
     14      LOGICAL,PARAMETER :: sorties                    = .false.   !  false
     15      INTEGER,PARAMETER :: iflag_trig_bl              = 1         !  1
     16      INTEGER,PARAMETER :: iflag_clos_bl              = 1         !  1
     17      INTEGER,PARAMETER :: iflag_coupl                = 5         !  5
     18     
    1919! Physical parameters
    20 
    21 REAL,PARAMETER :: fact_thermals_ed_dz           = 0.007     !     0.007
    22 REAL,PARAMETER :: r_aspect_thermals             = 2.0       !     
    23 REAL,PARAMETER :: tau_thermals                  = 0.        !     0.
    24 REAL,PARAMETER :: betalpha                      = 0.9       !     0.9
    25 REAL,PARAMETER :: afact                         = 2./3.     !     2./3.
    26 REAL,PARAMETER :: fact_epsilon                  = 0.000     !     0.002
    27 REAL,PARAMETER :: detr_q_power                  = 0.5       !     0.5
    28 REAL,PARAMETER :: detr_q_coef                   = 0.012     !     0.012
    29 REAL,PARAMETER :: mix0                          = 0.        !     0.
    30 REAL,PARAMETER :: detr_min                      = 1.d-5     !     1.e-5
    31 REAL,PARAMETER :: entr_min                      = 1.d-5     !     1.e-5
    32 REAL,PARAMETER :: alphamax                      = 0.7       !     
    33 REAL,PARAMETER :: fomass_max                    = 0.5       !     
    34 REAL,PARAMETER :: fact_shell                    = 1.        !     1.
    35 REAL,PARAMETER :: pres_limit                    = 1.e5      !     1.e5
    36 
     20     
     21      REAL,PARAMETER :: fact_thermals_ed_dz           = 0.007     !  0.007    !
     22      REAL,PARAMETER :: r_aspect_thermals             = 1.0       !           Aspect ratio of the thermals (width / height)
     23      REAL,PARAMETER :: tau_thermals                  = 0.        !  0.       Relaxation time
     24      REAL,PARAMETER :: betalpha                      = 0.9       !  0.9      !
     25      REAL,PARAMETER :: afact                         = 2./3.     !  2./3.    !
     26      REAL,PARAMETER :: fact_epsilon                  = 0.000     !  0.002    !
     27      REAL,PARAMETER :: detr_q_power                  = 0.5       !  0.5      !
     28      REAL,PARAMETER :: detr_q_coef                   = 0.012     !  0.012    !
     29      REAL,PARAMETER :: mix0                          = 0.        !  0.       !
     30      REAL,PARAMETER :: detr_min                      = 1.d-5     !  1.e-5    Minimal detrainment value
     31      REAL,PARAMETER :: entr_min                      = 1.d-5     !  1.e-5    Maximal detrainment value
     32      REAL,PARAMETER :: alphamax                      = 0.7       !           Maximal permitted updraft fraction
     33      REAL,PARAMETER :: fomass_max                    = 0.5       !           Maximal permitted outgoing layer mass fraction
     34      REAL,PARAMETER :: pres_limit                    = 1.e5      !  1.e5     !
     35     
    3736!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    3837! AB : linf is used to set the lowest possible first level because we allow it
     
    4039!      first layer for gas giant.
    4140!      If there is a surface, it has to be set to 1.
    42 !      If someone want to call more than once the thermal plume model in one
    43 !      or more grid point, this variable must become a saved array of INTEGER
    44 !      with size ngrid.
     41!      If someone want to call more than once the thermal plume model in some
     42!      grid points, this variable may become a saved array of INTEGER with size
     43!      ngrid.
    4544!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    46 INTEGER,PARAMETER :: linf                       = 2
    47 
     45      INTEGER,PARAMETER :: linf                       = 2         !     1
     46     
    4847!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    49 ! AB : d_temp is an artificial virtual potential temperature added in layer
    50 !      linf which can be used to force convection to begin in it.
     48! AB : d_temp is an artificial virtual potential temperature offset added in
     49!      layer linf which can be used to force convection to begin in it.
    5150!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    52 REAL,PARAMETER :: d_temp                        = 10.       !     0.
    53 
     51      REAL,PARAMETER :: d_temp                        = 0.        !     0.
     52     
    5453! Parameters for diagnoses
    55 
    56 REAL,PARAMETER :: alp_bl_k                      = 0.5       !     0.5
    57 
     54     
     55      REAL,PARAMETER :: alp_bl_k                      = 0.5       !     0.5
     56     
    5857! Physical constants
    59 
    60 REAL,SAVE :: RTT
    61 REAL,SAVE :: RG
    62 REAL,SAVE :: RKAPPA
    63 REAL,SAVE :: RPI
    64 REAL,SAVE :: RD
    65 
     58     
     59      REAL,SAVE :: RTT
     60      REAL,SAVE :: RG
     61      REAL,SAVE :: RKAPPA
     62      REAL,SAVE :: RPI
     63      REAL,SAVE :: RD
     64     
    6665!$OMP THREADPRIVATE(RTT, RG, RKAPPA, RPI, RD)
    67 
     66     
    6867!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    6968! AB : Parameters needed only for a loop in thermcell_alp (diagnoses).
    7069!      Maybe to be removed.
    7170!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    72 INTEGER,PARAMETER :: nbsrf                      = 1
    73 
    74 
    75 CONTAINS
     71      INTEGER,PARAMETER :: nbsrf                      = 1
     72     
     73     
     74      CONTAINS
    7675     
    7776      SUBROUTINE init_thermcell_mod(g, rcp, r, pi, T_h2o_ice_liq, RV)
     77         
     78         IMPLICIT NONE
     79         
     80         REAL g
     81         REAL rcp
     82         REAL r
     83         REAL pi
     84         REAL T_h2o_ice_liq
     85         REAL RV
     86         
     87         RTT = T_h2o_ice_liq
     88         RG = g
     89         RKAPPA = rcp
     90         RPI = pi
     91         RD = r
     92         
     93         RETURN
     94      END SUBROUTINE init_thermcell_mod
    7895     
    79       IMPLICIT NONE
    80      
    81       REAL g
    82       REAL rcp
    83       REAL r
    84       REAL pi
    85       REAL T_h2o_ice_liq
    86       REAL RV
    87      
    88       RTT = T_h2o_ice_liq
    89       RG = g
    90       RKAPPA = rcp
    91       RPI = pi
    92       RD = r
    93      
    94       RETURN
    95       END SUBROUTINE init_thermcell_mod
    96 
    9796END MODULE thermcell_mod
Note: See TracChangeset for help on using the changeset viewer.