Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (6 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/cva_driver.f90

    r5618 r5791  
    11
    22! $Id$
     3!$gpum horizontal len nloc ncum klon
     4MODULE cva_driver_mod
     5  PRIVATE
     6  LOGICAL, SAVE :: debut = .TRUE.
     7  !$OMP THREADPRIVATE(debut)
     8  LOGICAL, SAVE :: never_compress=.FALSE.   ! if true, compression is desactivated in convection
     9  !$OMP THREADPRIVATE(never_compress)
     10
     11  PUBLIC cva_driver_pre, cva_driver_post, cva_driver
     12
     13CONTAINS
     14
     15! called before cva_driver
     16SUBROUTINE cva_driver_pre(nd, k_upper, iflag_con, iflag_ice_thermo, ok_conserv_q, delt)
     17USE cv3_routines_mod, ONLY : cv3_routine_pre, cv3_param 
     18USE cv_routines_mod, ONLY : cv_param
     19USE ioipsl_getin_p_mod, ONLY : getin_p
     20USE s2s
     21IMPLICIT NONE
     22  INTEGER, INTENT (IN)                               :: nd
     23  INTEGER, INTENT (IN)                               :: k_upper
     24  INTEGER, INTENT (IN)                               :: iflag_con
     25  INTEGER, INTENT (IN)                               :: iflag_ice_thermo
     26  REAL, INTENT (IN)                                  :: delt
     27  LOGICAL, INTENT (IN)                               :: ok_conserv_q
     28
     29  IF (debut) THEN
     30    ! -------------------------------------------------------------------
     31    ! --- SET CONSTANTS AND PARAMETERS
     32    ! -------------------------------------------------------------------
     33
     34    ! -- set simulation flags:
     35    ! (common cvflag)
     36    never_compress = .FALSE.
     37    CALL getin_p("convection_no_compression",never_compress)
     38    IF (s2s_gpu_activated()) never_compress = .TRUE.  ! for GPU, compression must be disabled
     39    CALL cv_flag(iflag_ice_thermo)
     40
     41    ! -- set thermodynamical constants:
     42    ! (common cvthermo)
     43
     44    CALL cv_thermo(iflag_con)
     45
     46    ! -- set convect parameters
     47
     48    ! includes microphysical parameters and parameters that
     49    ! control the rate of approach to quasi-equilibrium)
     50    ! (common cvparam)
     51
     52    IF (iflag_con==3) THEN
     53      CALL cv3_param(nd, k_upper, delt)
     54    END IF
     55
     56    IF (iflag_con==4) THEN
     57      CALL cv_param(nd)
     58    END IF
     59   
     60    CALL cv3_routine_pre(ok_conserv_q)
     61  ENDIF
     62
     63END SUBROUTINE cva_driver_pre
     64
     65!called after cva_driver
     66SUBROUTINE cva_driver_post
     67IMPLICIT NONE
     68  IF (debut) THEN
     69    debut=.FALSE.
     70  ENDIF
     71END SUBROUTINE cva_driver_post
    372
    473SUBROUTINE cva_driver(len, nd, ndp1, ntra, nloc, k_upper, &
     
    42111  USE print_control_mod, ONLY: prt_level, lunout
    43112  USE add_phys_tend_mod, ONLY: fl_cor_ebil
     113  USE cv3_routines_mod
     114  USE cv_routines_mod
     115  USE cv3a_compress_mod, ONLY : cv3a_compress
     116  USE cv3p_mixing_mod, ONLY   : cv3p_mixing
     117  USE cv3p1_closure_mod, ONLY : cv3p1_closure
     118  USE cv3p2_closure_mod, ONLY : cv3p2_closure
     119  USE cv3_mixscale_mod, ONLY : cv3_mixscale
     120  USE cv3a_uncompress_mod, ONLY : cv3a_uncompress
     121  USE cv3_enthalpmix_mod, ONLY : cv3_enthalpmix
     122  USE cv3_estatmix_mod, ONLY : cv3_estatmix
    44123  IMPLICIT NONE
    45124
     
    418497
    419498  LOGICAL ok_inhib ! True => possible inhibition of convection by dryness
    420   LOGICAL, SAVE :: debut = .TRUE.
    421 !$OMP THREADPRIVATE(debut)
    422499
    423500  REAL coef_convective(len)   ! = 1 for convective points, = 0 otherwise
     
    545622  REAL epmax_diag(nloc) ! epmax_cape
    546623
    547   CHARACTER (LEN=20) :: modname = 'cva_driver'
     624  CHARACTER (LEN=20), PARAMETER :: modname = 'cva_driver'
    548625  CHARACTER (LEN=80) :: abort_message
    549626
     
    551628  REAL, PARAMETER    :: Cape_noconv = -1.
    552629
    553   INTEGER,SAVE                                       :: igout=1
    554 !$OMP THREADPRIVATE(igout)
    555 
     630  INTEGER, PARAMETER                                       :: igout=1
     631  LOGICAL :: is_convect(len)   ! is convection is active on column
    556632
    557633! print *, 't1, t1_wake ',(k,t1(1,k),t1_wake(1,k),k=1,nd)
    558634! print *, 'q1, q1_wake ',(k,q1(1,k),q1_wake(1,k),k=1,nd)
    559635
    560 ! -------------------------------------------------------------------
    561 ! --- SET CONSTANTS AND PARAMETERS
    562 ! -------------------------------------------------------------------
    563 
    564 ! -- set simulation flags:
    565 ! (common cvflag)
    566 
    567   CALL cv_flag(iflag_ice_thermo)
    568 
    569 ! -- set thermodynamical constants:
    570 ! (common cvthermo)
    571 
    572   CALL cv_thermo(iflag_con)
    573 
    574 ! -- set convect parameters
    575 
    576 ! includes microphysical parameters and parameters that
    577 ! control the rate of approach to quasi-equilibrium)
    578 ! (common cvparam)
    579 
    580   IF (iflag_con==3) THEN
    581     CALL cv3_param(nd, k_upper, delt)
    582 
    583   END IF
    584 
    585   IF (iflag_con==4) THEN
    586     CALL cv_param(nd)
    587   END IF
     636
    588637
    589638! ---------------------------------------------------------------------
     
    835884!  gridpoints and the weights "coef_convective" (= 1. for convective gridpoints and = 0.
    836885!  elsewhere).
    837   ncum = 0
    838   coef_convective(:) = 0.
    839886  DO i = 1, len
    840887    IF (iflag1(i)==0) THEN
    841888      coef_convective(i) = 1.
    842       ncum = ncum + 1
    843       idcum(ncum) = i
     889      is_convect(i) = .TRUE.
     890    ELSE
     891      coef_convective(i) = 0.
     892      is_convect(i) = .FALSE.     
    844893    END IF
    845894  END DO
    846895
    847 ! print*,'len, ncum = ',len,ncum
     896 
     897  IF (never_compress) THEN
     898    compress = .FALSE.
     899    DO i = 1,len
     900      idcum(i) = i
     901    ENDDO
     902    ncum=len
     903  ELSE
     904    ncum = 0
     905    DO i = 1, len
     906      IF (iflag1(i)==0) THEN
     907        ncum = ncum + 1
     908        idcum(ncum) = i
     909      END IF
     910    END DO
     911   
     912    IF (ncum>0) THEN
     913!   If the fraction of convective points is larger than comp_threshold, then compression
     914!   is assumed useless.
     915      compress = ncum .lt. len*comp_threshold
     916      IF (.not. compress) THEN
     917        DO i = 1,len
     918          idcum(i) = i
     919        ENDDO
     920        ncum=len
     921      ENDIF
     922    ENDIF
     923
     924  ENDIF   
    848925
    849926  IF (ncum>0) THEN
     
    855932
    856933    IF (iflag_con==3) THEN
    857 ! print*,'ncum tv1 ',ncum,tv1
    858 ! print*,'tvp1 ',tvp1
    859 !jyg<
    860 !   If the fraction of convective points is larger than comp_threshold, then compression
    861 !   is assumed useless.
    862 !
    863   compress = ncum .lt. len*comp_threshold
    864 !
    865   IF (.not. compress) THEN
    866     DO i = 1,len
    867       idcum(i) = i
    868     ENDDO
    869   ENDIF
    870 !
    871 !>jyg
    872         if (prt_level >= 9) &
    873              PRINT *, 'cva_driver -> cv3a_compress'
     934      if (prt_level >= 9) PRINT *, 'cva_driver -> cv3a_compress'
    874935      CALL cv3a_compress(len, nloc, ncum, nd, ntra, compress, &
    875936                         iflag1, nk1, icb1, icbs1, &
     
    894955                         Ale, Alp, omega)
    895956
    896 ! print*,'tv ',tv
    897 ! print*,'tvp ',tvp
    898957
    899958    END IF
    900959
    901960    IF (iflag_con==4) THEN
    902         if (prt_level >= 9) &
    903              PRINT *, 'cva_driver -> cv_compress'
     961      if (prt_level >= 9) PRINT *, 'cva_driver -> cv_compress'
    904962      CALL cv_compress(len, nloc, ncum, nd, &
    905                        iflag1, nk1, icb1, &
     963                       iflag1, compress, nk1, icb1, &
    906964                       cbmf1, plcl1, tnk1, qnk1, gznk1, &
    907965                       t1, q1, qs1, u1, v1, gz1, &
     
    9611019!      END IF
    9621020      IF (iflag_mix>=1) THEN
    963         CALL zilch(supmax, nloc*nd)
     1021        supmax(:,:)=0.
    9641022        if (prt_level >= 9) &
    9651023             PRINT *, 'cva_driver -> cv3p_mixing'
     
    9731031
    9741032      ELSE
    975         CALL zilch(supmax, nloc*nd)
     1033        supmax(:,:)=0.
    9761034      END IF
    9771035    END IF
     
    10501108                        unk, vnk, hp, tv, tvp, ep, clw, m, sig, &
    10511109                        ment, qent, uent, vent, nent, sigij, elij, ments, qents, traent)
    1052         CALL zilch(hent, nloc*nd*nd)
     1110        hent(1:nloc,1:nd,1:nd) = 0.
    10531111      ELSE
    10541112!!jyg:  Essais absurde pour voir
     
    12121270        if (prt_level >= 9) &
    12131271             PRINT *, 'cva_driver -> cv3a_uncompress'
    1214       CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, compress, &
     1272      CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, is_convect, compress, &
    12151273                           iflag, icb, inb, &
    12161274                           precip, cbmf, plcl, plfc, wbeff, sig, w0, ptop2, &
     
    12541312        if (prt_level >= 9) &
    12551313             PRINT *, 'cva_driver -> cv_uncompress'
    1256       CALL cv_uncompress(nloc, len, ncum, nd, idcum, &
     1314      CALL cv_uncompress(nloc, len, ncum, nd, idcum, is_convect, compress, &
    12571315                           iflag, &
    12581316                           precip, cbmf, &
     
    12851343  IF (debut) THEN
    12861344    PRINT *, ' cv_uncompress -> '
    1287     debut = .FALSE.
    12881345  END IF  !(debut) THEN
    12891346
     
    12911348  RETURN
    12921349END SUBROUTINE cva_driver
     1350
     1351END MODULE cva_driver_mod
Note: See TracChangeset for help on using the changeset viewer.