source: LMDZ5/trunk/libf/dyn3d_common/limz.F @ 2597

Last change on this file since 2597 was 2597, checked in by Ehouarn Millour, 8 years ago

Cleanup in the dynamics: get rid of comconst.h, make it a module comconst_mod.
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.2 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE limz(s0,sz,sm,pente_max)
5c
6c     Auteurs:   P.Le Van, F.Hourdin, F.Forget
7c
8c    ********************************************************************
9c     Shema  d'advection " pseudo amont " .
10c    ********************************************************************
11c     nq,iq,q,pbaru,pbarv,w sont des arguments d'entree  pour le s-pg ....
12c
13c
14c   --------------------------------------------------------------------
15      IMPLICIT NONE
16c
17      include "dimensions.h"
18      include "paramet.h"
19      include "logic.h"
20      include "comvert.h"
21      include "comgeom.h"
22c
23c
24c   Arguments:
25c   ----------
26      real pente_max
27      REAL s0(ip1jmp1,llm),sm(ip1jmp1,llm)
28      real sz(ip1jmp1,llm)
29c
30c      Local
31c   ---------
32c
33      INTEGER ij,l,j,i,iju,ijq,indu(ip1jmp1),niju
34      integer n0,iadvplus(ip1jmp1,llm),nl(llm)
35c
36      REAL q(ip1jmp1,llm)
37      real dzq(ip1jmp1,llm)
38
39
40      REAL new_m,zm
41      real dzqw(ip1jmp1)
42      real adzqw(ip1jmp1),dzqmax(ip1jmp1)
43
44      Logical extremum,first
45      save first
46
47      REAL      SSUM,CVMGP,CVMGT
48      integer ismax,ismin
49      EXTERNAL  SSUM, ismin,ismax
50
51      data first/.true./
52
53
54       DO  l = 1,llm
55         DO  ij=1,ip1jmp1
56               q(ij,l) = s0(ij,l) / sm ( ij,l )
57               dzq(ij,l) = sz(ij,l) /sm(ij,l)
58         ENDDO
59       ENDDO
60
61c   calcul de la pente en haut et en bas de la maille
62       do ij=1,ip1jmp1
63       do l = 1, llm-1
64            dzqw(l)=q(ij,l+1)-q(ij,l)
65         enddo
66            dzqw(llm)=0.
67
68         do  l=1,llm
69            adzqw(l)=abs(dzqw(l))
70         enddo
71
72c   calcul de la pente maximum dans la maille en valeur absolue
73
74         do l=2,llm-1
75            dzqmax(l)=pente_max*min(adzqw(l-1),adzqw(l))
76         enddo
77
78c   calcul de la pente avec limitation
79
80         do l=2,llm-1
81            if(     dzqw(l-1)*dzqw(l).gt.0.
82     &         .and. dzq(ij,l)*dzqw(l).gt.0.) then
83              dzq(ij,l)=
84     &         sign(min(abs(dzq(ij,l)),dzqmax(l)),dzq(ij,l))
85            else
86c   extremum local
87               dzq(ij,l)=0.
88            endif
89         enddo
90
91         DO  l=1,llm
92               sz(ij,l) = dzq(ij,l)*sm(ij,l)
93         ENDDO
94
95       ENDDO
96
97      RETURN
98      END
Note: See TracBrowser for help on using the repository browser.