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

Contents of /trunk/dyn3d/integrd.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 27 - (show annotations)
Thu Mar 25 14:29:07 2010 UTC (14 years, 1 month ago) by guez
Original Path: trunk/libf/dyn3d/integrd.f
File size: 5305 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/integrd.F,v 1.1.1.1 2004/05/19 12:53:05 lmdzadmin Exp $
3 !
4 SUBROUTINE integrd
5 $ ( nq,vcovm1,ucovm1,tetam1,psm1,massem1,
6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,finvmaold,
7 $ leapf )
8
9 use dimens_m
10 use paramet_m
11 use comconst
12 use comvert
13 use logic
14 use comgeom
15 use serre
16 use temps
17 use iniadvtrac_m
18 use pression_m, only: pression
19 use filtreg_m, only: filtreg
20
21 IMPLICIT NONE
22
23
24 c=======================================================================
25 c
26 c Auteur: P. Le Van
27 c -------
28 c
29 c objet:
30 c ------
31 c
32 c Incrementation des tendances dynamiques
33 c
34 c=======================================================================
35 c-----------------------------------------------------------------------
36 c Declarations:
37 c -------------
38
39
40 c Arguments:
41 c ----------
42
43 INTEGER nq
44
45 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
46 REAL q(ip1jmp1,llm,nq)
47 REAL ps(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1)
48
49 REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
50 REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm)
51
52 REAL dv(ip1jm,llm),du(ip1jmp1,llm)
53 REAL dteta(ip1jmp1,llm),dp(ip1jmp1)
54 REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm)
55 logical, intent(in):: leapf
56
57 c Local:
58 c ------
59
60 REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1)
61 REAL massescr( ip1jmp1,llm ), finvmasse(ip1jmp1,llm)
62 REAL p(ip1jmp1,llmp1)
63 REAL tpn,tps,tppn(iim),tpps(iim)
64 REAL qpn,qps,qppn(iim),qpps(iim)
65 REAL deltap( ip1jmp1,llm )
66
67 INTEGER l,ij,iq
68
69 REAL SSUM
70
71 c-----------------------------------------------------------------------
72
73 DO l = 1,llm
74 DO ij = 1,iip1
75 ucov( ij , l) = 0.
76 ucov( ij +ip1jm, l) = 0.
77 uscr( ij ) = 0.
78 uscr( ij +ip1jm ) = 0.
79 ENDDO
80 ENDDO
81
82
83 c ............ integration de ps ..............
84
85 CALL SCOPY(ip1jmp1*llm, masse, 1, massescr, 1)
86
87 DO 2 ij = 1,ip1jmp1
88 pscr (ij) = ps(ij)
89 ps (ij) = psm1(ij) + dt * dp(ij)
90 2 CONTINUE
91 c
92 DO ij = 1,ip1jmp1
93 IF( ps(ij).LT.0. ) THEN
94 PRINT *,' Au point ij = ',ij, ' , pression sol neg. ', ps(ij)
95 STOP 'integrd'
96 ENDIF
97 ENDDO
98 c
99 DO ij = 1, iim
100 tppn(ij) = aire( ij ) * ps( ij )
101 tpps(ij) = aire(ij+ip1jm) * ps(ij+ip1jm)
102 ENDDO
103 tpn = SSUM(iim,tppn,1)/apoln
104 tps = SSUM(iim,tpps,1)/apols
105 DO ij = 1, iip1
106 ps( ij ) = tpn
107 ps(ij+ip1jm) = tps
108 ENDDO
109 c
110 c ... Calcul de la nouvelle masse d'air au dernier temps integre t+1 ...
111 c
112 CALL pression ( ip1jmp1, ap, bp, ps, p )
113 CALL massdair ( p , masse )
114
115 CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 )
116 CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1 )
117 c
118
119 c ............ integration de ucov, vcov, h ..............
120
121 DO 10 l = 1,llm
122
123 DO 4 ij = iip2,ip1jm
124 uscr( ij ) = ucov( ij,l )
125 ucov( ij,l ) = ucovm1( ij,l ) + dt * du( ij,l )
126 4 CONTINUE
127
128 DO 5 ij = 1,ip1jm
129 vscr( ij ) = vcov( ij,l )
130 vcov( ij,l ) = vcovm1( ij,l ) + dt * dv( ij,l )
131 5 CONTINUE
132
133 DO 6 ij = 1,ip1jmp1
134 hscr( ij ) = teta(ij,l)
135 teta ( ij,l ) = tetam1(ij,l) * massem1(ij,l) / masse(ij,l)
136 $ + dt * dteta(ij,l) / masse(ij,l)
137 6 CONTINUE
138
139 c .... Calcul de la valeur moyenne, unique aux poles pour teta ......
140 c
141 c
142 DO ij = 1, iim
143 tppn(ij) = aire( ij ) * teta( ij ,l)
144 tpps(ij) = aire(ij+ip1jm) * teta(ij+ip1jm,l)
145 ENDDO
146 tpn = SSUM(iim,tppn,1)/apoln
147 tps = SSUM(iim,tpps,1)/apols
148
149 DO ij = 1, iip1
150 teta( ij ,l) = tpn
151 teta(ij+ip1jm,l) = tps
152 ENDDO
153 c
154
155 IF(leapf) THEN
156 CALL SCOPY ( ip1jmp1, uscr(1), 1, ucovm1(1, l), 1 )
157 CALL SCOPY ( ip1jm, vscr(1), 1, vcovm1(1, l), 1 )
158 CALL SCOPY ( ip1jmp1, hscr(1), 1, tetam1(1, l), 1 )
159 END IF
160
161 10 CONTINUE
162
163 DO l = 1, llm
164 DO ij = 1, ip1jmp1
165 deltap(ij,l) = p(ij,l) - p(ij,l+1)
166 ENDDO
167 ENDDO
168
169 CALL qminimum( q, nq, deltap )
170 c
171 c ..... Calcul de la valeur moyenne, unique aux poles pour q .....
172 c
173
174 DO iq = 1, nq
175 DO l = 1, llm
176
177 DO ij = 1, iim
178 qppn(ij) = aire( ij ) * q( ij ,l,iq)
179 qpps(ij) = aire(ij+ip1jm) * q(ij+ip1jm,l,iq)
180 ENDDO
181 qpn = SSUM(iim,qppn,1)/apoln
182 qps = SSUM(iim,qpps,1)/apols
183
184 DO ij = 1, iip1
185 q( ij ,l,iq) = qpn
186 q(ij+ip1jm,l,iq) = qps
187 ENDDO
188
189 ENDDO
190 ENDDO
191
192
193 CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )
194 c
195 c
196 c ..... FIN de l'integration de q .......
197
198 15 continue
199
200 c .................................................................
201
202
203 IF( leapf ) THEN
204 CALL SCOPY ( ip1jmp1 , pscr , 1, psm1 , 1 )
205 CALL SCOPY ( ip1jmp1*llm, massescr, 1, massem1, 1 )
206 END IF
207
208 RETURN
209 END

  ViewVC Help
Powered by ViewVC 1.1.21