Changeset 5791 for LMDZ6/branches/contrails/libf/phylmd/cv3p_mixing.f90
- Timestamp:
- Jul 28, 2025, 7:23:15 PM (6 days ago)
- Location:
- LMDZ6/branches/contrails
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/contrails
- Property svn:mergeinfo changed
/LMDZ6/trunk merged: 5654-5683,5685-5690,5692-5715,5718-5721,5726-5727,5729,5744-5761,5763-5778,5780,5785-5789
- Property svn:mergeinfo changed
-
LMDZ6/branches/contrails/libf/phylmd/cv3p_mixing.f90
r5346 r5791 1 MODULE cv3p_mixing_mod 2 PRIVATE 3 PUBLIC cv3p_mixing 4 CONTAINS 5 6 SUBROUTINE cv3p_mixing_pre 7 8 END SUBROUTINE cv3p_mixing_pre 9 1 10 SUBROUTINE cv3p_mixing(nloc, ncum, nd, na, ntra, icb, nk, inb, & 2 11 ph, t, rr, rs, u, v, tra, h, lv, lf, frac, qta, & … … 13 22 ! ************************************************************** 14 23 15 USE yomcst2_mod_h 24 USE yomcst2_mod_h, ONLY : Fmax, gammas, scut, qqa1, qqa2 16 25 USE lmdz_cv_ini, ONLY : cpd,cpv,minorig,nl,rrv 17 26 USE cvflag_mod_h … … 76 85 INTEGER nstep 77 86 78 INTEGER,SAVE :: igout=1 79 !$OMP THREADPRIVATE(igout) 87 INTEGER,PARAMETER :: igout=1 80 88 81 89 ! -- Mixing probability distribution functions 82 90 83 91 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 85 97 Qcoef1(F) = tanh(F/gammas) 86 98 Qcoef2(F) = (tanh(F/gammas)+gammas*log(cosh((1.-F)/gammas)/cosh(F/gammas))) … … 94 106 Rmix(F) = qqa1*Rmix1(F) + qqa2*Rmix2(F) 95 107 96 INTEGER, SAVE :: ifrst97 DATA ifrst/0/98 !$OMP THREADPRIVATE(ifrst)99 108 100 109 … … 103 112 ! ===================================================================== 104 113 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) 117 116 118 117 ! ori do 360 i=1,ncum*nlp 119 118 DO j = 1, nl 120 DO i = 1, ncum121 nent(i , j) = 0119 DO il = 1, ncum 120 nent(il, j) = 0 122 121 ! in convect3, m is computed in cv3_closure 123 122 ! ori m(i,1)=0.0 … … 129 128 DO j = 1, nl 130 129 DO k = 1, nl 131 DO i = 1, ncum132 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.0136 hent(i , k, j) = 0.0130 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 137 136 !AC! Ment(i,k,j)=0.0 138 137 !AC! Sij(i,k,j)=0.0 … … 295 294 ! ===================================================================== 296 295 297 CALL zilch(csum, nloc*nd)298 296 csum(:,:) = 0. 297 299 298 DO il = 1, ncum 300 299 lwork(il) = .FALSE. … … 309 308 IF (i>=icb(il) .AND. i<=inb(il)) num1 = num1 + 1 310 309 END DO 311 IF (num1<=0) GO TO 789 310 !ym IF (num1<=0) GO TO 789 311 IF (num1<=0) CYCLE 312 312 313 313 … … 389 389 lwork(il)) num2 = num2 + 1 390 390 END DO 391 IF (num2<=0) GO TO 175392 391 !ym IF (num2<=0) GO TO 175 392 IF (num2<=0) CYCLE 393 393 ! ----------------------------------------------- 394 394 IF (j>i) THEN … … 627 627 628 628 ! --------------------------------------------------------------- 629 175 END DO! End loop on destination level "j"629 END DO !ym label 175 ! End loop on destination level "j" 630 630 ! --------------------------------------------------------------- 631 631 … … 692 692 693 693 ! --------------------------------------------------------------- 694 789 END DO ! End loop on origin level "i" 694 END DO !ym label 789 ! End loop on origin level "i" 695 695 696 ! --------------------------------------------------------------- 696 697 … … 699 700 END SUBROUTINE cv3p_mixing 700 701 702 END MODULE cv3p_mixing_mod
Note: See TracChangeset
for help on using the changeset viewer.