/[lmdze]/trunk/Sources/dyn3d/Vlsplt/vlsplt.f
ViewVC logotype

Diff of /trunk/Sources/dyn3d/Vlsplt/vlsplt.f

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

trunk/libf/dyn3d/Vlsplt/vlsplt.f90 revision 31 by guez, Thu Apr 1 14:59:19 2010 UTC trunk/Sources/dyn3d/Vlsplt/vlsplt.f revision 157 by guez, Mon Jul 20 16:01:49 2015 UTC
# Line 1  Line 1 
1  !  module vlsplt_m
 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/vlsplt.F,v 1.2  
 !     2005/02/24 12:16:57 fairhead Exp $  
 !  
 !  
 !  
   
       SUBROUTINE vlsplt(q,pente_max,masse,w,pbaru,pbarv,pdt)  
 !  
 !     Auteurs:   P.Le Van, F.Hourdin, F.Forget  
 !  
 !    *************************************************************  
 !     Shema  d'advection " pseudo amont " .  
 !    **************************************************************  
 !     q,pbaru,pbarv,w sont des arguments d'entree  pour le s-pg ....  
 !  
 !   pente_max facteur de limitation des pentes: 2 en general  
 !                                               0 pour un schema amont  
 !   pbaru,pbarv,w flux de masse en u ,v ,w  
 !   pdt pas de temps  
 !  
 !   ---------------------------------------------------------------  
       use dimens_m  
       use paramet_m  
       use comconst  
       use comvert  
       use logic  
       IMPLICIT NONE  
 !  
   
 !  
 !   Arguments:  
 !   ----------  
       REAL masse(ip1jmp1,llm),pente_max  
 !      REAL masse(iip1,jjp1,llm),pente_max  
       REAL, intent(in):: pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm)  
       REAL q(ip1jmp1,llm)  
 !      REAL q(iip1,jjp1,llm)  
       REAL w(ip1jmp1,llm)  
       real, intent(in):: pdt  
 !  
 !      Local  
 !   ---------  
 !  
       INTEGER i,ij,l,j,ii  
       INTEGER ijlqmin,iqmin,jqmin,lqmin  
 !  
       REAL zm(ip1jmp1,llm),newmasse  
       REAL mu(ip1jmp1,llm)  
       REAL mv(ip1jm,llm)  
       REAL mw(ip1jmp1,llm+1)  
       REAL zq(ip1jmp1,llm),zz  
       REAL dqx(ip1jmp1,llm),dqy(ip1jmp1,llm),dqz(ip1jmp1,llm)  
       REAL second,temps0,temps1,temps2,temps3  
       REAL ztemps1,ztemps2,ztemps3  
       REAL zzpbar, zzw  
       LOGICAL testcpu  
       SAVE testcpu  
       SAVE temps1,temps2,temps3  
       INTEGER iminn,imaxx  
   
       REAL qmin,qmax  
       DATA qmin,qmax/0.,1.e33/  
       DATA testcpu/.false./  
       DATA temps1,temps2,temps3/0.,0.,0./  
   
   
         zzpbar = 0.5 * pdt  
         zzw    = pdt  
       DO l=1,llm  
         DO ij = iip2,ip1jm  
             mu(ij,l)=pbaru(ij,l) * zzpbar  
          ENDDO  
          DO ij=1,ip1jm  
             mv(ij,l)=pbarv(ij,l) * zzpbar  
          ENDDO  
          DO ij=1,ip1jmp1  
             mw(ij,l)=w(ij,l) * zzw  
          ENDDO  
       ENDDO  
   
       DO ij=1,ip1jmp1  
          mw(ij,llm+1)=0.  
       ENDDO  
   
       CALL SCOPY(ijp1llm,q,1,zq,1)  
       CALL SCOPY(ijp1llm,masse,1,zm,1)  
   
       call vlx(zq,pente_max,zm,mu)  
   
       call vly(zq,pente_max,zm,mv)  
       call vlz(zq,pente_max,zm,mw)  
   
   
       call vly(zq,pente_max,zm,mv)  
   
   
       call vlx(zq,pente_max,zm,mu)  
   
   
       DO l=1,llm  
          DO ij=1,ip1jmp1  
            q(ij,l)=zq(ij,l)  
          ENDDO  
          DO ij=1,ip1jm+1,iip1  
             q(ij+iim,l)=q(ij,l)  
          ENDDO  
       ENDDO  
2    
3        RETURN    IMPLICIT NONE
4        END  
5    contains
6    
7      SUBROUTINE vlsplt(q, pente_max, masse, w, pbaru, pbarv, pdt)
8    
9        ! From LMDZ4/libf/dyn3d/vlsplt.F, version 1.2 2005/02/24 12:16:57 fairhead
10    
11        ! Authors: P. Le Van, F. Hourdin, F. Forget
12    
13        ! Sch\'ema d'advection "pseudo-amont".
14    
15        USE dimens_m, ONLY: iim, llm
16        USE paramet_m, ONLY: iip1, iip2, ijp1llm, ip1jm, ip1jmp1
17        use vlx_m, only: vlx
18    
19        REAL, intent(inout):: q(ip1jmp1, llm)
20    
21        REAL, intent(in):: pente_max
22        ! facteur de limitation des pentes, 2 en general
23    
24        real, intent(in):: masse(ip1jmp1, llm)
25        REAL, intent(in):: w(ip1jmp1, llm) ! flux de masse
26    
27        REAL, intent(in):: pbaru( ip1jmp1, llm ), pbarv( ip1jm, llm)
28        ! flux de masse en u, v
29    
30        real, intent(in):: pdt ! pas de temps
31    
32        ! Local:
33    
34        INTEGER ij, l
35        REAL zm(ip1jmp1, llm)
36        REAL mu(ip1jmp1, llm)
37        REAL mv(ip1jm, llm)
38        REAL mw(ip1jmp1, llm+1)
39        REAL zzpbar, zzw
40    
41        !---------------------------------------------------------------
42    
43        zzpbar = 0.5 * pdt
44        zzw = pdt
45        DO l = 1, llm
46           DO ij = iip2, ip1jm
47              mu(ij, l) = pbaru(ij, l) * zzpbar
48           ENDDO
49           DO ij = 1, ip1jm
50              mv(ij, l) = pbarv(ij, l) * zzpbar
51           ENDDO
52           DO ij = 1, ip1jmp1
53              mw(ij, l) = w(ij, l) * zzw
54           ENDDO
55        ENDDO
56    
57        DO ij = 1, ip1jmp1
58           mw(ij, llm+1) = 0.
59        ENDDO
60    
61        zm = masse
62    
63        call vlx(q, pente_max, zm, mu)
64        call vly(q, pente_max, zm, mv)
65        call vlz(q, pente_max, zm, mw)
66        call vly(q, pente_max, zm, mv)
67        call vlx(q, pente_max, zm, mu)
68    
69        DO ij = 1, ip1jm + 1, iip1
70           q(ij + iim, :) = q(ij, :)
71        ENDDO
72    
73      END SUBROUTINE vlsplt
74    
75    end module vlsplt_m

Legend:
Removed from v.31  
changed lines
  Added in v.157

  ViewVC Help
Powered by ViewVC 1.1.21