/[lmdze]/trunk/Sources/phylmd/CV30_routines/cv30_mixing.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/CV30_routines/cv30_mixing.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/Sources/phylmd/CV3_routines/cv3_mixing.f revision 145 by guez, Tue Jun 16 15:23:29 2015 UTC trunk/Sources/phylmd/CV30_routines/cv30_mixing.f revision 187 by guez, Mon Mar 21 18:01:02 2016 UTC
# Line 1  Line 1 
1  module cv3_mixing_m  module cv30_mixing_m
2    
3    implicit none    implicit none
4    
5  contains  contains
6    
7    SUBROUTINE cv3_mixing(nloc, ncum, nd, na, icb, nk, inb, t, rr, rs, u, v, h, &    SUBROUTINE cv30_mixing(nloc, ncum, nd, na, icb, nk, inb, t, rr, rs, u, v, h, &
8         lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, sij, elij, &         lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, sij, elij, &
9         ments, qents)         ments, qents)
10      use cv3_param_m      use cv30_param_m
11      use cvthermo      use cvthermo
12    
13      !---------------------------------------------------------------------      !---------------------------------------------------------------------
# Line 18  contains Line 18  contains
18    
19      ! inputs:      ! inputs:
20      integer, intent(in):: ncum, nd, na, nloc      integer, intent(in):: ncum, nd, na, nloc
21      integer icb(nloc), inb(nloc), nk(nloc)      integer, intent(in):: icb(nloc), inb(nloc), nk(nloc)
22      real sig(nloc, nd)      real sig(nloc, nd)
23      real t(nloc, nd), rr(nloc, nd), rs(nloc, nd)      real t(nloc, nd), rr(nloc, nd), rs(nloc, nd)
24      real u(nloc, nd), v(nloc, nd)      real u(nloc, nd), v(nloc, nd)
# Line 31  contains Line 31  contains
31      real uent(nloc, na, na), vent(nloc, na, na)      real uent(nloc, na, na), vent(nloc, na, na)
32      real sij(nloc, na, na), elij(nloc, na, na)      real sij(nloc, na, na), elij(nloc, na, na)
33      real ments(nloc, nd, nd), qents(nloc, nd, nd)      real ments(nloc, nd, nd), qents(nloc, nd, nd)
     real sigij(nloc, nd, nd)  
34      integer nent(nloc, nd)      integer nent(nloc, nd)
35    
36      ! local variables:      ! local variables:
# Line 50  contains Line 49  contains
49      do j=1, nl      do j=1, nl
50         do i=1, ncum         do i=1, ncum
51            nent(i, j)=0            nent(i, j)=0
52            ! in convect3, m is computed in cv3_closure            ! in convect3, m is computed in cv30_closure
53            ! ori m(i, 1)=0.0            ! ori m(i, 1)=0.0
54         end do         end do
55      end do      end do
# Line 124  contains Line 123  contains
123         ! *** if no air can entrain at level i assume that updraft detrains ***         ! *** if no air can entrain at level i assume that updraft detrains ***
124         ! *** at that level and calculate detrained air flux and properties ***         ! *** at that level and calculate detrained air flux and properties ***
125    
        !@ do 170 i=icb(il), inb(il)  
   
126         do il=1, ncum         do il=1, ncum
127            if ((i >= icb(il)).and.(i <= inb(il)).and.(nent(il, i) == 0)) then            if ((i >= icb(il)).and.(i <= inb(il)).and.(nent(il, i) == 0)) then
128               !@ if(nent(il, i) == 0)then               !@ if(nent(il, i) == 0)then
# Line 140  contains Line 137  contains
137         end do         end do
138      end do      end do
139    
     do j=minorig, nl  
        do i=minorig, nl  
           do il=1, ncum  
              if ((j >= (icb(il)-1)).and.(j <= inb(il)) &  
                   .and.(i >= icb(il)).and.(i <= inb(il)))then  
                 sigij(il, i, j)=sij(il, i, j)  
              endif  
           end do  
        end do  
     end do  
     !@ enddo  
   
     !@170 continue  
   
140      ! --- NORMALIZE ENTRAINED AIR MASS FLUXES      ! --- NORMALIZE ENTRAINED AIR MASS FLUXES
141      ! --- TO REPRESENT EQUAL PROBABILITIES OF MIXING      ! --- TO REPRESENT EQUAL PROBABILITIES OF MIXING
142    
143      call zilch(asum, nloc*nd)      asum = 0.
144      call zilch(csum, nloc*nd)      csum = 0.
     call zilch(csum, nloc*nd)  
145    
146      do il=1, ncum      do il=1, ncum
147         lwork(il) = .FALSE.         lwork(il) = .FALSE.
# Line 331  contains Line 313  contains
313         enddo         enddo
314      enddo      enddo
315    
316    end SUBROUTINE cv3_mixing    end SUBROUTINE cv30_mixing
317    
318  end module cv3_mixing_m  end module cv30_mixing_m

Legend:
Removed from v.145  
changed lines
  Added in v.187

  ViewVC Help
Powered by ViewVC 1.1.21