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/cv3p_mixing.f90

    r5346 r5791  
     1MODULE cv3p_mixing_mod
     2  PRIVATE
     3  PUBLIC cv3p_mixing
     4CONTAINS
     5
     6SUBROUTINE cv3p_mixing_pre
     7
     8END SUBROUTINE cv3p_mixing_pre
     9
    110SUBROUTINE cv3p_mixing(nloc, ncum, nd, na, ntra, icb, nk, inb, &
    211                       ph, t, rr, rs, u, v, tra, h, lv, lf, frac, qta, &
     
    1322! **************************************************************
    1423
    15 USE yomcst2_mod_h
     24USE yomcst2_mod_h, ONLY : Fmax, gammas, scut, qqa1, qqa2
    1625   USE lmdz_cv_ini, ONLY : cpd,cpv,minorig,nl,rrv
    1726  USE cvflag_mod_h
     
    7685  INTEGER nstep
    7786
    78   INTEGER,SAVE                                       :: igout=1
    79 !$OMP THREADPRIVATE(igout)
     87  INTEGER,PARAMETER                                       :: igout=1
    8088
    8189! --   Mixing probability distribution functions
    8290
    8391  REAL Qcoef1, Qcoef2, QFF, QFFF, Qmix, Rmix, Qmix1, Rmix1, Qmix2, Rmix2, F
    84 
     92  REAL :: Qcoef1max,Qcoef2max  !ym WARNING
     93                               !ym redefine local variable instead use module variable
     94                               !ym to check when refactoring deep convection
     95                               !ym => eliminate "first" SAVE variable
     96                               !ym probably all these folowing lines will be removed
    8597  Qcoef1(F) = tanh(F/gammas)
    8698  Qcoef2(F) = (tanh(F/gammas)+gammas*log(cosh((1.-F)/gammas)/cosh(F/gammas)))
     
    94106  Rmix(F) = qqa1*Rmix1(F) + qqa2*Rmix2(F)
    95107
    96   INTEGER, SAVE :: ifrst
    97   DATA ifrst/0/
    98 !$OMP THREADPRIVATE(ifrst)
    99108
    100109
     
    103112! =====================================================================
    104113
    105 ! -- Initialize mixing PDF coefficients
    106   IF (ifrst==0) THEN
    107     ifrst = 1
    108     Qcoef1max = Qcoef1(Fmax)
    109     Qcoef2max = Qcoef2(Fmax)
    110 !<jyg
    111    print*, 'fmax, gammas, qqa1, qqa2, Qcoef1max, Qcoef2max ', &
    112             fmax, gammas, qqa1, qqa2, Qcoef1max, Qcoef2max
    113 !>jyg
    114 !
    115   END IF
    116 
     114  Qcoef1max = Qcoef1(Fmax)
     115  Qcoef2max = Qcoef2(Fmax)
    117116
    118117! ori        do 360 i=1,ncum*nlp
    119118  DO j = 1, nl
    120     DO i = 1, ncum
    121       nent(i, j) = 0
     119    DO il = 1, ncum
     120      nent(il, j) = 0
    122121! in convect3, m is computed in cv3_closure
    123122! ori          m(i,1)=0.0
     
    129128  DO j = 1, nl
    130129    DO k = 1, nl
    131       DO i = 1, ncum
    132         Qent(i, k, j) = rr(i, j)
    133         uent(i, k, j) = u(i, j)
    134         vent(i, k, j) = v(i, j)
    135         elij(i, k, j) = 0.0
    136         hent(i, k, j) = 0.0
     130      DO il = 1, ncum
     131        Qent(il, k, j) = rr(il, j)
     132        uent(il, k, j) = u(il, j)
     133        vent(il, k, j) = v(il, j)
     134        elij(il, k, j) = 0.0
     135        hent(il, k, j) = 0.0
    137136!AC!            Ment(i,k,j)=0.0
    138137!AC!            Sij(i,k,j)=0.0
     
    295294! =====================================================================
    296295
    297   CALL zilch(csum, nloc*nd)
    298 
     296  csum(:,:) = 0.
     297 
    299298  DO il = 1, ncum
    300299    lwork(il) = .FALSE.
     
    309308      IF (i>=icb(il) .AND. i<=inb(il)) num1 = num1 + 1
    310309    END DO
    311     IF (num1<=0) GO TO 789
     310!ym    IF (num1<=0) GO TO 789
     311    IF (num1<=0) CYCLE
    312312
    313313
     
    389389            lwork(il)) num2 = num2 + 1
    390390      END DO
    391       IF (num2<=0) GO TO 175
    392 
     391!ym      IF (num2<=0) GO TO 175
     392      IF (num2<=0) CYCLE
    393393! -----------------------------------------------
    394394      IF (j>i) THEN
     
    627627
    628628! ---------------------------------------------------------------
    629 175 END DO        ! End loop on destination level "j"
     629    END DO  !ym label 175      ! End loop on destination level "j"
    630630! ---------------------------------------------------------------
    631631
     
    692692
    693693! ---------------------------------------------------------------
    694 789 END DO              ! End loop on origin level "i"
     694END DO  !ym label 789             ! End loop on origin level "i"
     695
    695696! ---------------------------------------------------------------
    696697
     
    699700END SUBROUTINE cv3p_mixing
    700701
     702END MODULE cv3p_mixing_mod
Note: See TracChangeset for help on using the changeset viewer.