/[lmdze]/trunk/dyn3d/limy.f
ViewVC logotype

Contents of /trunk/dyn3d/limy.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 27 - (show annotations)
Thu Mar 25 14:29:07 2010 UTC (14 years, 2 months ago) by guez
Original Path: trunk/libf/dyn3d/limy.f
File size: 5068 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 !
2 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/limy.F,v 1.1.1.1 2004/05/19 12:53:07 lmdzadmin Exp $
3 !
4 SUBROUTINE limy(s0,sy,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 q,w sont des arguments d'entree pour le s-pg ....
12 c dq sont des arguments de sortie pour le s-pg ....
13 c
14 c
15 c --------------------------------------------------------------------
16 use dimens_m
17 use paramet_m
18 use comconst
19 use comvert
20 use logic
21 use comgeom
22 IMPLICIT NONE
23 c
24 c
25 c
26 c Arguments:
27 c ----------
28 real pente_max
29 real s0(ip1jmp1,llm),sy(ip1jmp1,llm),sm(ip1jmp1,llm)
30 c
31 c Local
32 c ---------
33 c
34 INTEGER i,ij,l
35 c
36 REAL q(ip1jmp1,llm)
37 REAL airej2,airejjm,airescb(iim),airesch(iim)
38 real sigv,dyq(ip1jmp1),dyqv(ip1jm)
39 real adyqv(ip1jm),dyqmax(ip1jmp1)
40 REAL qbyv(ip1jm,llm)
41
42 REAL qpns,qpsn,apn,aps,dyn1,dys1,dyn2,dys2
43 Logical extremum,first
44 save first
45
46 real convpn,convps,convmpn,convmps
47 real sinlon(iip1),sinlondlon(iip1)
48 real coslon(iip1),coslondlon(iip1)
49 save sinlon,coslon,sinlondlon,coslondlon
50 c
51 c
52 REAL SSUM
53 integer ismax,ismin
54 EXTERNAL SSUM, convflu,ismin,ismax
55
56 data first/.true./
57
58 if(first) then
59 print*,'SCHEMA AMONT NOUVEAU'
60 first=.false.
61 do i=2,iip1
62 coslon(i)=cos(rlonv(i))
63 sinlon(i)=sin(rlonv(i))
64 coslondlon(i)=coslon(i)*(rlonu(i)-rlonu(i-1))/pi
65 sinlondlon(i)=sinlon(i)*(rlonu(i)-rlonu(i-1))/pi
66 enddo
67 coslon(1)=coslon(iip1)
68 coslondlon(1)=coslondlon(iip1)
69 sinlon(1)=sinlon(iip1)
70 sinlondlon(1)=sinlondlon(iip1)
71 endif
72
73 c
74
75 do l = 1, llm
76 c
77 DO ij=1,ip1jmp1
78 q(ij,l) = s0(ij,l) / sm ( ij,l )
79 dyq(ij) = sy(ij,l) / sm ( ij,l )
80 ENDDO
81 c
82 c --------------------------------
83 c CALCUL EN LATITUDE
84 c --------------------------------
85
86 c On commence par calculer la valeur du traceur moyenne sur le premier cercle
87 c de latitude autour du pole (qpns pour le pole nord et qpsn pour
88 c le pole nord) qui sera utilisee pour evaluer les pentes au pole.
89
90 airej2 = SSUM( iim, aire(iip2), 1 )
91 airejjm= SSUM( iim, aire(ip1jm -iim), 1 )
92 DO i = 1, iim
93 airescb(i) = aire(i+ iip1) * q(i+ iip1,l)
94 airesch(i) = aire(i+ ip1jm- iip1) * q(i+ ip1jm- iip1,l)
95 ENDDO
96 qpns = SSUM( iim, airescb ,1 ) / airej2
97 qpsn = SSUM( iim, airesch ,1 ) / airejjm
98
99 c calcul des pentes aux points v
100
101 do ij=1,ip1jm
102 dyqv(ij)=q(ij,l)-q(ij+iip1,l)
103 adyqv(ij)=abs(dyqv(ij))
104 ENDDO
105
106 c calcul des pentes aux points scalaires
107
108 do ij=iip2,ip1jm
109 dyqmax(ij)=min(adyqv(ij-iip1),adyqv(ij))
110 dyqmax(ij)=pente_max*dyqmax(ij)
111 enddo
112
113 c calcul des pentes aux poles
114
115 c calcul des pentes limites aux poles
116
117 c print*,dyqv(iip1+1)
118 c apn=abs(dyq(1)/dyqv(iip1+1))
119 c print*,dyq(ip1jm+1)
120 c print*,dyqv(ip1jm-iip1+1)
121 c aps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))
122 c do ij=2,iim
123 c apn=amax1(abs(dyq(ij)/dyqv(ij)),apn)
124 c aps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)
125 c enddo
126 c apn=min(pente_max/apn,1.)
127 c aps=min(pente_max/aps,1.)
128
129
130 c cas ou on a un extremum au pole
131
132 c if(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.)
133 c & apn=0.
134 c if(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)*
135 c & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.)
136 c & aps=0.
137
138 c limitation des pentes aux poles
139 c do ij=1,iip1
140 c dyq(ij)=apn*dyq(ij)
141 c dyq(ip1jm+ij)=aps*dyq(ip1jm+ij)
142 c enddo
143
144 c test
145 c do ij=1,iip1
146 c dyq(iip1+ij)=0.
147 c dyq(ip1jm+ij-iip1)=0.
148 c enddo
149 c do ij=1,ip1jmp1
150 c dyq(ij)=dyq(ij)*cos(rlatu((ij-1)/iip1+1))
151 c enddo
152
153 if(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.)
154 & then
155 do ij=1,iip1
156 dyqmax(ij)=0.
157 enddo
158 else
159 do ij=1,iip1
160 dyqmax(ij)=pente_max*abs(dyqv(ij))
161 enddo
162 endif
163
164 if(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)*
165 & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.)
166 &then
167 do ij=ip1jm+1,ip1jmp1
168 dyqmax(ij)=0.
169 enddo
170 else
171 do ij=ip1jm+1,ip1jmp1
172 dyqmax(ij)=pente_max*abs(dyqv(ij-iip1))
173 enddo
174 endif
175
176 c calcul des pentes limitees
177
178 do ij=1,ip1jmp1
179 if(dyqv(ij)*dyqv(ij-iip1).gt.0.) then
180 dyq(ij)=sign(min(abs(dyq(ij)),dyqmax(ij)),dyq(ij))
181 else
182 dyq(ij)=0.
183 endif
184 enddo
185
186 DO ij=1,ip1jmp1
187 sy(ij,l) = dyq(ij) * sm ( ij,l )
188 ENDDO
189
190 enddo ! fin de la boucle sur les couches verticales
191
192 RETURN
193 END

  ViewVC Help
Powered by ViewVC 1.1.21