/[lmdze]/trunk/Sources/dyn3d/limz.f
ViewVC logotype

Annotation of /trunk/Sources/dyn3d/limz.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 27 - (hide annotations)
Thu Mar 25 14:29:07 2010 UTC (14 years, 2 months ago) by guez
Original Path: trunk/libf/dyn3d/limz.f
File size: 2285 byte(s)
"dyn3d" and "filtrez" do not contain any included file so make rules
have been updated.

"comdissip.f90" was useless, removed it.

"dynredem0" wrote undefined value in "controle(31)", that was
overwritten by "dynredem1". Now "dynredem0" just writes 0 to
"controle(31)".

Removed arguments of "inidissip". "inidissip" now accesses the
variables by use association.

In program "etat0_lim", "itaufin" is not defined so "dynredem1" wrote
undefined value to "controle(31)". Added argument "itau" of
"dynredem1" to correct that.

"itaufin" does not need to be a module variable (of "temps"), made it
a local variable of "leapfrog".

Removed calls to "diagedyn" from "leapfrog".

1 guez 3 !
2     ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/limz.F,v 1.1.1.1 2004/05/19 12:53:07 lmdzadmin Exp $
3     !
4     SUBROUTINE limz(s0,sz,sm,pente_max)
5     c
6     c Auteurs: P.Le Van, F.Hourdin, F.Forget
7     c
8     c ********************************************************************
9     c Shema d'advection " pseudo amont " .
10     c ********************************************************************
11     c nq,iq,q,pbaru,pbarv,w sont des arguments d'entree pour le s-pg ....
12     c
13     c
14     c --------------------------------------------------------------------
15     use dimens_m
16     use paramet_m
17     use comconst
18     use comvert
19     use logic
20     use comgeom
21     IMPLICIT NONE
22     c
23     c
24     c
25     c Arguments:
26     c ----------
27     real pente_max
28     REAL s0(ip1jmp1,llm),sm(ip1jmp1,llm)
29     real sz(ip1jmp1,llm)
30     c
31     c Local
32     c ---------
33     c
34     INTEGER ij,l,j,i,iju,ijq,indu(ip1jmp1),niju
35     integer n0,iadvplus(ip1jmp1,llm),nl(llm)
36     c
37     REAL q(ip1jmp1,llm)
38     real dzq(ip1jmp1,llm)
39    
40    
41     REAL new_m,zm
42     real dzqw(ip1jmp1)
43     real adzqw(ip1jmp1),dzqmax(ip1jmp1)
44    
45     Logical extremum,first
46     save first
47    
48     REAL SSUM,CVMGP,CVMGT
49     integer ismax,ismin
50     EXTERNAL SSUM, convflu,ismin,ismax
51    
52     data first/.true./
53    
54    
55     DO l = 1,llm
56     DO ij=1,ip1jmp1
57     q(ij,l) = s0(ij,l) / sm ( ij,l )
58     dzq(ij,l) = sz(ij,l) /sm(ij,l)
59     ENDDO
60     ENDDO
61    
62     c calcul de la pente en haut et en bas de la maille
63     do ij=1,ip1jmp1
64     do l = 1, llm-1
65     dzqw(l)=q(ij,l+1)-q(ij,l)
66     enddo
67     dzqw(llm)=0.
68    
69     do l=1,llm
70     adzqw(l)=abs(dzqw(l))
71     enddo
72    
73     c calcul de la pente maximum dans la maille en valeur absolue
74    
75     do l=2,llm-1
76     dzqmax(l)=pente_max*min(adzqw(l-1),adzqw(l))
77     enddo
78    
79     c calcul de la pente avec limitation
80    
81     do l=2,llm-1
82     if( dzqw(l-1)*dzqw(l).gt.0.
83     & .and. dzq(ij,l)*dzqw(l).gt.0.) then
84     dzq(ij,l)=
85     & sign(min(abs(dzq(ij,l)),dzqmax(l)),dzq(ij,l))
86     else
87     c extremum local
88     dzq(ij,l)=0.
89     endif
90     enddo
91    
92     DO l=1,llm
93     sz(ij,l) = dzq(ij,l)*sm(ij,l)
94     ENDDO
95    
96     ENDDO
97    
98     RETURN
99     END

  ViewVC Help
Powered by ViewVC 1.1.21