source: trunk/LMDZ.COMMON/libf/dyn3d_common/limz.F @ 3493

Last change on this file since 3493 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

File size: 2.1 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 "comgeom.h"
20c
21c
22c   Arguments:
23c   ----------
24      real pente_max
25      REAL s0(ip1jmp1,llm),sm(ip1jmp1,llm)
26      real sz(ip1jmp1,llm)
27c
28c      Local
29c   ---------
30c
31      INTEGER ij,l,j,i,iju,ijq,indu(ip1jmp1),niju
32      integer n0,iadvplus(ip1jmp1,llm),nl(llm)
33c
34      REAL q(ip1jmp1,llm)
35      real dzq(ip1jmp1,llm)
36
37
38      REAL new_m,zm
39      real dzqw(ip1jmp1)
40      real adzqw(ip1jmp1),dzqmax(ip1jmp1)
41
42      Logical extremum,first
43      save first
44
45      REAL      SSUM,CVMGP,CVMGT
46      integer ismax,ismin
47      EXTERNAL  SSUM, convflu,ismin,ismax
48      EXTERNAL filtreg
49
50      data first/.true./
51
52
53       DO  l = 1,llm
54         DO  ij=1,ip1jmp1
55               q(ij,l) = s0(ij,l) / sm ( ij,l )
56               dzq(ij,l) = sz(ij,l) /sm(ij,l)
57         ENDDO
58       ENDDO
59
60c   calcul de la pente en haut et en bas de la maille
61       do ij=1,ip1jmp1
62       do l = 1, llm-1
63            dzqw(l)=q(ij,l+1)-q(ij,l)
64         enddo
65            dzqw(llm)=0.
66
67         do  l=1,llm
68            adzqw(l)=abs(dzqw(l))
69         enddo
70
71c   calcul de la pente maximum dans la maille en valeur absolue
72
73         do l=2,llm-1
74            dzqmax(l)=pente_max*min(adzqw(l-1),adzqw(l))
75         enddo
76
77c   calcul de la pente avec limitation
78
79         do l=2,llm-1
80            if(     dzqw(l-1)*dzqw(l).gt.0.
81     &         .and. dzq(ij,l)*dzqw(l).gt.0.) then
82              dzq(ij,l)=
83     &         sign(min(abs(dzq(ij,l)),dzqmax(l)),dzq(ij,l))
84            else
85c   extremum local
86               dzq(ij,l)=0.
87            endif
88         enddo
89
90         DO  l=1,llm
91               sz(ij,l) = dzq(ij,l)*sm(ij,l)
92         ENDDO
93
94       ENDDO
95
96      RETURN
97      END
Note: See TracBrowser for help on using the repository browser.