/[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/phylmd/CV3_routines/cv3_mixing.f revision 82 by guez, Wed Mar 5 14:57:53 2014 UTC trunk/Sources/phylmd/CV3_routines/cv3_mixing.f revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC
# Line 1  Line 1 
1    module cv3_mixing_m
2    
3        SUBROUTINE cv3_mixing(nloc,ncum,nd,na,ntra,icb,nk,inb &    implicit none
                           ,ph,t,rr,rs,u,v,tra,h,lv,qnk &  
                           ,hp,tv,tvp,ep,clw,m,sig &  
          ,ment,qent,uent,vent, nent, sij,elij,ments,qents,traent)  
             use cv3_param_m  
             use cvthermo  
       implicit none  
   
 !---------------------------------------------------------------------  
 ! a faire:  
 !     - changer rr(il,1) -> qnk(il)  
 !   - vectorisation de la partie normalisation des flux (do 789...)  
 !---------------------------------------------------------------------  
   
   
 ! inputs:  
       integer, intent(in):: ncum, nd, na, ntra, nloc  
       integer icb(nloc), inb(nloc), nk(nloc)  
       real sig(nloc,nd)  
       real qnk(nloc)  
       real ph(nloc,nd+1)  
       real t(nloc,nd), rr(nloc,nd), rs(nloc,nd)  
       real u(nloc,nd), v(nloc,nd)  
       real tra(nloc,nd,ntra) ! input of convect3  
       real lv(nloc,na), h(nloc,na), hp(nloc,na)  
       real tv(nloc,na), tvp(nloc,na), ep(nloc,na), clw(nloc,na)  
       real m(nloc,na)        ! input of convect3  
   
 ! outputs:  
       real ment(nloc,na,na), qent(nloc,na,na)  
       real uent(nloc,na,na), vent(nloc,na,na)  
       real sij(nloc,na,na), elij(nloc,na,na)  
       real traent(nloc,nd,nd,ntra)  
       real ments(nloc,nd,nd), qents(nloc,nd,nd)  
       real sigij(nloc,nd,nd)  
       integer nent(nloc,nd)  
   
 ! local variables:  
       integer i, j, k, il, im, jm  
       integer num1, num2  
       real rti, bf2, anum, denom, dei, altem, cwat, stemp, qp  
       real alt, smid, sjmin, sjmax, delp, delm  
       real asij(nloc), smax(nloc), scrit(nloc)  
       real asum(nloc,nd),bsum(nloc,nd),csum(nloc,nd)  
       real wgh  
       real zm(nloc,na)  
       logical lwork(nloc)  
   
 !=====================================================================  
 ! --- INITIALIZE VARIOUS ARRAYS USED IN THE COMPUTATIONS  
 !=====================================================================  
4    
5          do 361 j=1,nl  contains
6          do 360 i=1,ncum  
7      SUBROUTINE cv3_mixing(nloc,ncum,nd,na,icb,nk,inb &
8           ,ph,t,rr,rs,u,v,h,lv,qnk &
9           ,hp,tv,tvp,ep,clw,m,sig &
10           ,ment,qent,uent,vent, nent, sij,elij,ments,qents)
11        use cv3_param_m
12        use cvthermo
13    
14        !---------------------------------------------------------------------
15        ! a faire:
16        !     - changer rr(il,1) -> qnk(il)
17        !   - vectorisation de la partie normalisation des flux (do 789...)
18        !---------------------------------------------------------------------
19    
20    
21        ! inputs:
22        integer, intent(in):: ncum, nd, na, nloc
23        integer icb(nloc), inb(nloc), nk(nloc)
24        real sig(nloc,nd)
25        real qnk(nloc)
26        real ph(nloc,nd+1)
27        real t(nloc,nd), rr(nloc,nd), rs(nloc,nd)
28        real u(nloc,nd), v(nloc,nd)
29        real lv(nloc,na), h(nloc,na), hp(nloc,na)
30        real tv(nloc,na), tvp(nloc,na), ep(nloc,na), clw(nloc,na)
31        real m(nloc,na)        ! input of convect3
32    
33        ! outputs:
34        real ment(nloc,na,na), qent(nloc,na,na)
35        real uent(nloc,na,na), vent(nloc,na,na)
36        real sij(nloc,na,na), elij(nloc,na,na)
37        real ments(nloc,nd,nd), qents(nloc,nd,nd)
38        real sigij(nloc,nd,nd)
39        integer nent(nloc,nd)
40    
41        ! local variables:
42        integer i, j, k, il, im, jm
43        integer num1, num2
44        real rti, bf2, anum, denom, dei, altem, cwat, stemp, qp
45        real alt, smid, sjmin, sjmax, delp, delm
46        real asij(nloc), smax(nloc), scrit(nloc)
47        real asum(nloc,nd),bsum(nloc,nd),csum(nloc,nd)
48        real wgh
49        real zm(nloc,na)
50        logical lwork(nloc)
51    
52        !=====================================================================
53        ! --- INITIALIZE VARIOUS ARRAYS USED IN THE COMPUTATIONS
54        !=====================================================================
55    
56        do  j=1,nl
57           do  i=1,ncum
58            nent(i,j)=0            nent(i,j)=0
59  ! in convect3, m is computed in cv3_closure            ! in convect3, m is computed in cv3_closure
60  ! ori          m(i,1)=0.0            ! ori          m(i,1)=0.0
61   360    continue         end do
62   361    continue      end do
63    
64  ! ori      do 400 k=1,nlp      do  j=1,nl
65  ! ori       do 390 j=1,nlp         do  k=1,nl
66        do 400 j=1,nl            do  i=1,ncum
67         do 390 k=1,nl               qent(i,k,j)=rr(i,j)
68            do 385 i=1,ncum               uent(i,k,j)=u(i,j)
69              qent(i,k,j)=rr(i,j)               vent(i,k,j)=v(i,j)
70              uent(i,k,j)=u(i,j)               elij(i,k,j)=0.0
71              vent(i,k,j)=v(i,j)               !ym            ment(i,k,j)=0.0
72              elij(i,k,j)=0.0               !ym            sij(i,k,j)=0.0
73  !ym            ment(i,k,j)=0.0            end do
74  !ym            sij(i,k,j)=0.0         end do
75   385      continue      end do
76   390    continue  
77   400  continue      !ym
78        ment(1:ncum,1:nd,1:nd)=0.0
79  !ym      sij(1:ncum,1:nd,1:nd)=0.0
80        ment(1:ncum,1:nd,1:nd)=0.0  
81        sij(1:ncum,1:nd,1:nd)=0.0      zm(:,:)=0.
82    
83        zm(:,:)=0.      !=====================================================================
84        ! --- CALCULATE ENTRAINED AIR MASS FLUX (ment), TOTAL WATER MIXING
85  !=====================================================================      ! --- RATIO (QENT), TOTAL CONDENSED WATER (elij), AND MIXING
86  ! --- CALCULATE ENTRAINED AIR MASS FLUX (ment), TOTAL WATER MIXING      ! --- FRACTION (sij)
87  ! --- RATIO (QENT), TOTAL CONDENSED WATER (elij), AND MIXING      !=====================================================================
88  ! --- FRACTION (sij)  
89  !=====================================================================      do  i=minorig+1, nl
90    
91        do 750 i=minorig+1, nl         do  j=minorig,nl
92              do  il=1,ncum
93         do 710 j=minorig,nl               if( (i.ge.icb(il)).and.(i.le.inb(il)).and. &
94          do 700 il=1,ncum                    (j.ge.(icb(il)-1)).and.(j.le.inb(il)))then
95           if( (i.ge.icb(il)).and.(i.le.inb(il)).and. &  
96              (j.ge.(icb(il)-1)).and.(j.le.inb(il)))then                  rti=rr(il,1)-ep(il,i)*clw(il,i)
97                    bf2=1.+lv(il,j)*lv(il,j)*rs(il,j)/(rrv*t(il,j)*t(il,j)*cpd)
98            rti=rr(il,1)-ep(il,i)*clw(il,i)                  anum=h(il,j)-hp(il,i)+(cpv-cpd)*t(il,j)*(rti-rr(il,j))
99            bf2=1.+lv(il,j)*lv(il,j)*rs(il,j)/(rrv*t(il,j)*t(il,j)*cpd)                  denom=h(il,i)-hp(il,i)+(cpd-cpv)*(rr(il,i)-rti)*t(il,j)
100            anum=h(il,j)-hp(il,i)+(cpv-cpd)*t(il,j)*(rti-rr(il,j))                  dei=denom
101            denom=h(il,i)-hp(il,i)+(cpd-cpv)*(rr(il,i)-rti)*t(il,j)                  if(abs(dei).lt.0.01)dei=0.01
102            dei=denom                  sij(il,i,j)=anum/dei
103            if(abs(dei).lt.0.01)dei=0.01                  sij(il,i,i)=1.0
104            sij(il,i,j)=anum/dei                  altem=sij(il,i,j)*rr(il,i)+(1.-sij(il,i,j))*rti-rs(il,j)
105            sij(il,i,i)=1.0                  altem=altem/bf2
106            altem=sij(il,i,j)*rr(il,i)+(1.-sij(il,i,j))*rti-rs(il,j)                  cwat=clw(il,j)*(1.-ep(il,j))
107            altem=altem/bf2                  stemp=sij(il,i,j)
108            cwat=clw(il,j)*(1.-ep(il,j))                  if((stemp.lt.0.0.or.stemp.gt.1.0.or.altem.gt.cwat) &
109            stemp=sij(il,i,j)                       .and.j.gt.i)then
110            if((stemp.lt.0.0.or.stemp.gt.1.0.or.altem.gt.cwat) &                     anum=anum-lv(il,j)*(rti-rs(il,j)-cwat*bf2)
111                         .and.j.gt.i)then                     denom=denom+lv(il,j)*(rr(il,i)-rti)
112             anum=anum-lv(il,j)*(rti-rs(il,j)-cwat*bf2)                     if(abs(denom).lt.0.01)denom=0.01
113             denom=denom+lv(il,j)*(rr(il,i)-rti)                     sij(il,i,j)=anum/denom
114             if(abs(denom).lt.0.01)denom=0.01                     altem=sij(il,i,j)*rr(il,i)+(1.-sij(il,i,j))*rti-rs(il,j)
115             sij(il,i,j)=anum/denom                     altem=altem-(bf2-1.)*cwat
116             altem=sij(il,i,j)*rr(il,i)+(1.-sij(il,i,j))*rti-rs(il,j)                  end if
117             altem=altem-(bf2-1.)*cwat                  if(sij(il,i,j).gt.0.0.and.sij(il,i,j).lt.0.95)then
118                       qent(il,i,j)=sij(il,i,j)*rr(il,i)+(1.-sij(il,i,j))*rti
119                       uent(il,i,j)=sij(il,i,j)*u(il,i)+(1.-sij(il,i,j))*u(il,nk(il))
120                       vent(il,i,j)=sij(il,i,j)*v(il,i)+(1.-sij(il,i,j))*v(il,nk(il))
121                       elij(il,i,j)=altem
122                       elij(il,i,j)=amax1(0.0,elij(il,i,j))
123                       ment(il,i,j)=m(il,i)/(1.-sij(il,i,j))
124                       nent(il,i)=nent(il,i)+1
125                    end if
126                    sij(il,i,j)=amax1(0.0,sij(il,i,j))
127                    sij(il,i,j)=amin1(1.0,sij(il,i,j))
128                 endif ! new
129              end do
130           end do
131    
132           !
133           !   ***   if no air can entrain at level i assume that updraft detrains  ***
134           !   ***   at that level and calculate detrained air flux and properties  ***
135           !
136    
137           !@      do 170 i=icb(il),inb(il)
138    
139           do  il=1,ncum
140              if ((i.ge.icb(il)).and.(i.le.inb(il)).and.(nent(il,i).eq.0)) then
141                 !@      if(nent(il,i).eq.0)then
142                 ment(il,i,i)=m(il,i)
143                 qent(il,i,i)=rr(il,nk(il))-ep(il,i)*clw(il,i)
144                 uent(il,i,i)=u(il,nk(il))
145                 vent(il,i,i)=v(il,nk(il))
146                 elij(il,i,i)=clw(il,i)
147                 !MAF      sij(il,i,i)=1.0
148                 sij(il,i,i)=0.0
149            end if            end if
150           if(sij(il,i,j).gt.0.0.and.sij(il,i,j).lt.0.95)then         end do
151            qent(il,i,j)=sij(il,i,j)*rr(il,i)+(1.-sij(il,i,j))*rti      end do
           uent(il,i,j)=sij(il,i,j)*u(il,i)+(1.-sij(il,i,j))*u(il,nk(il))  
           vent(il,i,j)=sij(il,i,j)*v(il,i)+(1.-sij(il,i,j))*v(il,nk(il))  
 !!!!      do k=1,ntra  
 !!!!      traent(il,i,j,k)=sij(il,i,j)*tra(il,i,k)  
 !!!!     :      +(1.-sij(il,i,j))*tra(il,nk(il),k)  
 !!!!      end do  
           elij(il,i,j)=altem  
           elij(il,i,j)=amax1(0.0,elij(il,i,j))  
           ment(il,i,j)=m(il,i)/(1.-sij(il,i,j))  
           nent(il,i)=nent(il,i)+1  
          end if  
          sij(il,i,j)=amax1(0.0,sij(il,i,j))  
          sij(il,i,j)=amin1(1.0,sij(il,i,j))  
          endif ! new  
  700   continue  
  710  continue  
   
 !  
 !   ***   if no air can entrain at level i assume that updraft detrains  ***  
 !   ***   at that level and calculate detrained air flux and properties  ***  
 !  
   
 !@      do 170 i=icb(il),inb(il)  
   
       do 740 il=1,ncum  
       if ((i.ge.icb(il)).and.(i.le.inb(il)).and.(nent(il,i).eq.0)) then  
 !@      if(nent(il,i).eq.0)then  
       ment(il,i,i)=m(il,i)  
       qent(il,i,i)=rr(il,nk(il))-ep(il,i)*clw(il,i)  
       uent(il,i,i)=u(il,nk(il))  
       vent(il,i,i)=v(il,nk(il))  
       elij(il,i,i)=clw(il,i)  
 !MAF      sij(il,i,i)=1.0  
       sij(il,i,i)=0.0  
       end if  
  740  continue  
  750  continue  
   
       do 100 j=minorig,nl  
       do 101 i=minorig,nl  
       do 102 il=1,ncum  
       if ((j.ge.(icb(il)-1)).and.(j.le.inb(il)) &  
           .and.(i.ge.icb(il)).and.(i.le.inb(il)))then  
        sigij(il,i,j)=sij(il,i,j)  
       endif  
  102  continue  
  101  continue  
  100  continue  
 !@      enddo  
   
 !@170   continue  
   
 !=====================================================================  
 !   ---  NORMALIZE ENTRAINED AIR MASS FLUXES  
 !   ---  TO REPRESENT EQUAL PROBABILITIES OF MIXING  
 !=====================================================================  
   
       call zilch(asum,nloc*nd)  
       call zilch(csum,nloc*nd)  
       call zilch(csum,nloc*nd)  
152    
153        do il=1,ncum      do  j=minorig,nl
154         lwork(il) = .FALSE.         do  i=minorig,nl
155        enddo            do  il=1,ncum
156                 if ((j.ge.(icb(il)-1)).and.(j.le.inb(il)) &
157                      .and.(i.ge.icb(il)).and.(i.le.inb(il)))then
158                    sigij(il,i,j)=sij(il,i,j)
159                 endif
160              end do
161           end do
162        end do
163        !@      enddo
164    
165        DO 789 i=minorig+1,nl      !@170   continue
166    
167        num1=0      !=====================================================================
168        do il=1,ncum      !   ---  NORMALIZE ENTRAINED AIR MASS FLUXES
169         if ( i.ge.icb(il) .and. i.le.inb(il) ) num1=num1+1      !   ---  TO REPRESENT EQUAL PROBABILITIES OF MIXING
170        enddo      !=====================================================================
       if (num1.le.0) goto 789  
   
   
       do 781 il=1,ncum  
        if ( i.ge.icb(il) .and. i.le.inb(il) ) then  
         lwork(il)=(nent(il,i).ne.0)  
         qp=rr(il,1)-ep(il,i)*clw(il,i)  
         anum=h(il,i)-hp(il,i)-lv(il,i)*(qp-rs(il,i)) &  
                  +(cpv-cpd)*t(il,i)*(qp-rr(il,i))  
         denom=h(il,i)-hp(il,i)+lv(il,i)*(rr(il,i)-qp) &  
                  +(cpd-cpv)*t(il,i)*(rr(il,i)-qp)  
         if(abs(denom).lt.0.01)denom=0.01  
         scrit(il)=anum/denom  
         alt=qp-rs(il,i)+scrit(il)*(rr(il,i)-qp)  
         if(scrit(il).le.0.0.or.alt.le.0.0)scrit(il)=1.0  
         smax(il)=0.0  
         asij(il)=0.0  
        endif  
 781   continue  
   
       do 175 j=nl,minorig,-1  
   
       num2=0  
       do il=1,ncum  
        if ( i.ge.icb(il) .and. i.le.inb(il) .and. &  
             j.ge.(icb(il)-1) .and. j.le.inb(il)  &  
             .and. lwork(il) ) num2=num2+1  
       enddo  
       if (num2.le.0) goto 175  
   
       do 782 il=1,ncum  
       if ( i.ge.icb(il) .and. i.le.inb(il) .and. &  
             j.ge.(icb(il)-1) .and. j.le.inb(il)  &  
             .and. lwork(il) ) then  
   
        if(sij(il,i,j).gt.1.0e-16.and.sij(il,i,j).lt.0.95)then  
         wgh=1.0  
         if(j.gt.i)then  
          sjmax=amax1(sij(il,i,j+1),smax(il))  
          sjmax=amin1(sjmax,scrit(il))  
          smax(il)=amax1(sij(il,i,j),smax(il))  
          sjmin=amax1(sij(il,i,j-1),smax(il))  
          sjmin=amin1(sjmin,scrit(il))  
          if(sij(il,i,j).lt.(smax(il)-1.0e-16))wgh=0.0  
          smid=amin1(sij(il,i,j),scrit(il))  
         else  
          sjmax=amax1(sij(il,i,j+1),scrit(il))  
          smid=amax1(sij(il,i,j),scrit(il))  
          sjmin=0.0  
          if(j.gt.1)sjmin=sij(il,i,j-1)  
          sjmin=amax1(sjmin,scrit(il))  
         endif  
         delp=abs(sjmax-smid)  
         delm=abs(sjmin-smid)  
         asij(il)=asij(il)+wgh*(delp+delm)  
         ment(il,i,j)=ment(il,i,j)*(delp+delm)*wgh  
        endif  
       endif  
 782   continue  
   
 175   continue  
   
       do il=1,ncum  
        if (i.ge.icb(il).and.i.le.inb(il).and.lwork(il)) then  
         asij(il)=amax1(1.0e-16,asij(il))  
         asij(il)=1.0/asij(il)  
         asum(il,i)=0.0  
         bsum(il,i)=0.0  
         csum(il,i)=0.0  
        endif  
       enddo  
171    
172        do 180 j=minorig,nl      call zilch(asum,nloc*nd)
173         do il=1,ncum      call zilch(csum,nloc*nd)
174          if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &      call zilch(csum,nloc*nd)
175           .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then  
176           ment(il,i,j)=ment(il,i,j)*asij(il)      do il=1,ncum
177          endif         lwork(il) = .FALSE.
178         enddo      enddo
179  180   continue  
180        DO  i=minorig+1,nl
181    
182        do 190 j=minorig,nl         num1=0
183         do il=1,ncum         do il=1,ncum
184          if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &            if ( i.ge.icb(il) .and. i.le.inb(il) ) num1=num1+1
          .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then  
          asum(il,i)=asum(il,i)+ment(il,i,j)  
          ment(il,i,j)=ment(il,i,j)*sig(il,j)  
          bsum(il,i)=bsum(il,i)+ment(il,i,j)  
         endif  
185         enddo         enddo
186  190   continue         if (num1.le.0) cycle
187    
188    
189           do  il=1,ncum
190              if ( i.ge.icb(il) .and. i.le.inb(il) ) then
191                 lwork(il)=(nent(il,i).ne.0)
192                 qp=rr(il,1)-ep(il,i)*clw(il,i)
193                 anum=h(il,i)-hp(il,i)-lv(il,i)*(qp-rs(il,i)) &
194                      +(cpv-cpd)*t(il,i)*(qp-rr(il,i))
195                 denom=h(il,i)-hp(il,i)+lv(il,i)*(rr(il,i)-qp) &
196                      +(cpd-cpv)*t(il,i)*(rr(il,i)-qp)
197                 if(abs(denom).lt.0.01)denom=0.01
198                 scrit(il)=anum/denom
199                 alt=qp-rs(il,i)+scrit(il)*(rr(il,i)-qp)
200                 if(scrit(il).le.0.0.or.alt.le.0.0)scrit(il)=1.0
201                 smax(il)=0.0
202                 asij(il)=0.0
203              endif
204           end do
205    
206           do  j=nl,minorig,-1
207    
208              num2=0
209              do il=1,ncum
210                 if ( i.ge.icb(il) .and. i.le.inb(il) .and. &
211                      j.ge.(icb(il)-1) .and. j.le.inb(il)  &
212                      .and. lwork(il) ) num2=num2+1
213              enddo
214              if (num2.le.0) cycle
215    
216              do  il=1,ncum
217                 if ( i.ge.icb(il) .and. i.le.inb(il) .and. &
218                      j.ge.(icb(il)-1) .and. j.le.inb(il)  &
219                      .and. lwork(il) ) then
220    
221                    if(sij(il,i,j).gt.1.0e-16.and.sij(il,i,j).lt.0.95)then
222                       wgh=1.0
223                       if(j.gt.i)then
224                          sjmax=amax1(sij(il,i,j+1),smax(il))
225                          sjmax=amin1(sjmax,scrit(il))
226                          smax(il)=amax1(sij(il,i,j),smax(il))
227                          sjmin=amax1(sij(il,i,j-1),smax(il))
228                          sjmin=amin1(sjmin,scrit(il))
229                          if(sij(il,i,j).lt.(smax(il)-1.0e-16))wgh=0.0
230                          smid=amin1(sij(il,i,j),scrit(il))
231                       else
232                          sjmax=amax1(sij(il,i,j+1),scrit(il))
233                          smid=amax1(sij(il,i,j),scrit(il))
234                          sjmin=0.0
235                          if(j.gt.1)sjmin=sij(il,i,j-1)
236                          sjmin=amax1(sjmin,scrit(il))
237                       endif
238                       delp=abs(sjmax-smid)
239                       delm=abs(sjmin-smid)
240                       asij(il)=asij(il)+wgh*(delp+delm)
241                       ment(il,i,j)=ment(il,i,j)*(delp+delm)*wgh
242                    endif
243                 endif
244              end do
245    
246        do il=1,ncum         end do
        if (i.ge.icb(il).and.i.le.inb(il).and.lwork(il)) then  
         bsum(il,i)=amax1(bsum(il,i),1.0e-16)  
         bsum(il,i)=1.0/bsum(il,i)  
        endif  
       enddo  
247    
       do 195 j=minorig,nl  
248         do il=1,ncum         do il=1,ncum
249          if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &            if (i.ge.icb(il).and.i.le.inb(il).and.lwork(il)) then
250           .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then               asij(il)=amax1(1.0e-16,asij(il))
251           ment(il,i,j)=ment(il,i,j)*asum(il,i)*bsum(il,i)               asij(il)=1.0/asij(il)
252          endif               asum(il,i)=0.0
253                 bsum(il,i)=0.0
254                 csum(il,i)=0.0
255              endif
256         enddo         enddo
 195   continue  
257    
258        do 197 j=minorig,nl         do  j=minorig,nl
259              do il=1,ncum
260                 if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &
261                      .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then
262                    ment(il,i,j)=ment(il,i,j)*asij(il)
263                 endif
264              enddo
265           end do
266    
267           do  j=minorig,nl
268              do il=1,ncum
269                 if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &
270                      .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then
271                    asum(il,i)=asum(il,i)+ment(il,i,j)
272                    ment(il,i,j)=ment(il,i,j)*sig(il,j)
273                    bsum(il,i)=bsum(il,i)+ment(il,i,j)
274                 endif
275              enddo
276           end do
277    
278         do il=1,ncum         do il=1,ncum
279          if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &            if (i.ge.icb(il).and.i.le.inb(il).and.lwork(il)) then
280           .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then               bsum(il,i)=amax1(bsum(il,i),1.0e-16)
281           csum(il,i)=csum(il,i)+ment(il,i,j)               bsum(il,i)=1.0/bsum(il,i)
282          endif            endif
283         enddo         enddo
 197   continue  
284    
285        do il=1,ncum         do  j=minorig,nl
        if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &  
            .and. csum(il,i).lt.m(il,i) ) then  
         nent(il,i)=0  
         ment(il,i,i)=m(il,i)  
         qent(il,i,i)=rr(il,1)-ep(il,i)*clw(il,i)  
         uent(il,i,i)=u(il,nk(il))  
         vent(il,i,i)=v(il,nk(il))  
         elij(il,i,i)=clw(il,i)  
 !MAF        sij(il,i,i)=1.0  
         sij(il,i,i)=0.0  
        endif  
       enddo ! il  
   
 789   continue  
 !  
 ! MAF: renormalisation de MENT  
       do jm=1,nd  
         do im=1,nd  
286            do il=1,ncum            do il=1,ncum
287            zm(il,im)=zm(il,im)+(1.-sij(il,im,jm))*ment(il,im,jm)               if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &
288           end do                    .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then
289          end do                  ment(il,i,j)=ment(il,i,j)*asum(il,i)*bsum(il,i)
290        end do               endif
291  !            enddo
292        do jm=1,nd         end do
293          do im=1,nd  
294           do  j=minorig,nl
295            do il=1,ncum            do il=1,ncum
296            if(zm(il,im).ne.0.) then               if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &
297            ment(il,im,jm)=ment(il,im,jm)*m(il,im)/zm(il,im)                    .and. j.ge.(icb(il)-1) .and. j.le.inb(il) ) then
298                    csum(il,i)=csum(il,i)+ment(il,i,j)
299                 endif
300              enddo
301           end do
302    
303           do il=1,ncum
304              if ( i.ge.icb(il) .and. i.le.inb(il) .and. lwork(il) &
305                   .and. csum(il,i).lt.m(il,i) ) then
306                 nent(il,i)=0
307                 ment(il,i,i)=m(il,i)
308                 qent(il,i,i)=rr(il,1)-ep(il,i)*clw(il,i)
309                 uent(il,i,i)=u(il,nk(il))
310                 vent(il,i,i)=v(il,nk(il))
311                 elij(il,i,i)=clw(il,i)
312                 !MAF        sij(il,i,i)=1.0
313                 sij(il,i,i)=0.0
314            endif            endif
315           end do         enddo ! il
316    
317        end DO
318        !
319        ! MAF: renormalisation de MENT
320        do jm=1,nd
321           do im=1,nd
322              do il=1,ncum
323                 zm(il,im)=zm(il,im)+(1.-sij(il,im,jm))*ment(il,im,jm)
324              end do
325         end do         end do
326        end do      end do
327  !      !
328        do jm=1,nd      do jm=1,nd
329         do im=1,nd         do im=1,nd
330          do 999 il=1,ncum            do il=1,ncum
331           qents(il,im,jm)=qent(il,im,jm)               if(zm(il,im).ne.0.) then
332           ments(il,im,jm)=ment(il,im,jm)                  ment(il,im,jm)=ment(il,im,jm)*m(il,im)/zm(il,im)
333  999     continue               endif
334              end do
335           end do
336        end do
337        !
338        do jm=1,nd
339           do im=1,nd
340              do  il=1,ncum
341                 qents(il,im,jm)=qent(il,im,jm)
342                 ments(il,im,jm)=ment(il,im,jm)
343              end do
344         enddo         enddo
345        enddo      enddo
346    
347      end SUBROUTINE cv3_mixing
348    
349        return  end module cv3_mixing_m
       end  

Legend:
Removed from v.82  
changed lines
  Added in v.134

  ViewVC Help
Powered by ViewVC 1.1.21