/[lmdze]/trunk/libf/dyn3d/integrd.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/integrd.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 32 - (show annotations)
Tue Apr 6 17:52:58 2010 UTC (14 years, 1 month ago) by guez
File size: 4814 byte(s)
Split "stringop.f90" into single-procedure files. Gathered files in directory
"IOIPSL/Stringop".

Split "flincom.f90" into "flincom.f90" and "flinget.f90". Removed
unused procedures from module "flincom". Removed unused argument
"filename" of procedure "flinopen_nozoom".

Removed unused files.

Split "grid_change.f90" into "grid_change.f90" and
"gr_phy_write_3d.f90".

Removed unused procedures from modules "calendar", "ioipslmpp",
"grid_atob", "gath_cpl" and "getincom". Removed unused procedures in
files "ppm3d.f" and "thermcell.f".

Split "mathelp.f90" into "mathelp.f90" and "mathop.f90".

Removed unused variable "dpres" of module "comvert".

Use argument "itau" instead of local variables "iadvtr" and "first" to
control algorithm in procedure "fluxstokenc".

Removed unused arguments of procedure "integrd".

Removed useless computations at the end of procedure "leapfrog".

Merged common block "matrfil" into module "parafilt".

1 module integrd_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE integrd(nq,vcovm1,ucovm1,tetam1,psm1,massem1,dv,du,dteta,dp, &
8 vcov,ucov,teta,q,ps,masse,finvmaold,leapf, dt)
9
10 ! From dyn3d/integrd.F,v 1.1.1.1 2004/05/19 12:53:05
11 ! Auteur: P. Le Van
12 ! objet:
13 ! Incrementation des tendances dynamiques
14
15 USE dimens_m, ONLY : iim, llm
16 USE paramet_m, ONLY : iip1, iip2, ijp1llm, ip1jm, ip1jmp1, jjp1, llmp1
17 USE comvert, ONLY : ap, bp
18 USE comgeom, ONLY : aire, apoln, apols
19 USE pression_m, ONLY : pression
20 USE filtreg_m, ONLY : filtreg
21
22 ! Arguments:
23
24 INTEGER, intent(in):: nq
25
26 REAL vcov(ip1jm,llm), ucov(ip1jmp1,llm), teta(ip1jmp1,llm)
27 REAL q(ip1jmp1,llm,nq)
28 REAL ps(ip1jmp1), masse(ip1jmp1,llm)
29
30 REAL vcovm1(ip1jm,llm), ucovm1(ip1jmp1,llm)
31 REAL tetam1(ip1jmp1,llm), psm1(ip1jmp1), massem1(ip1jmp1,llm)
32
33 REAL dv(ip1jm,llm), du(ip1jmp1,llm)
34 REAL dteta(ip1jmp1,llm), dp(ip1jmp1)
35 REAL finvmaold(ip1jmp1,llm)
36 LOGICAL, INTENT (IN) :: leapf
37 real, intent(in):: dt
38
39 ! Local:
40
41 REAL vscr(ip1jm), uscr(ip1jmp1), hscr(ip1jmp1), pscr(ip1jmp1)
42 REAL massescr(ip1jmp1,llm), finvmasse(ip1jmp1,llm)
43 REAL p(ip1jmp1,llmp1)
44 REAL tpn, tps, tppn(iim), tpps(iim)
45 REAL qpn, qps, qppn(iim), qpps(iim)
46 REAL deltap(ip1jmp1,llm)
47
48 INTEGER l, ij, iq
49
50 REAL ssum
51
52 !-----------------------------------------------------------------------
53
54 DO l = 1, llm
55 DO ij = 1, iip1
56 ucov(ij,l) = 0.
57 ucov(ij+ip1jm,l) = 0.
58 uscr(ij) = 0.
59 uscr(ij+ip1jm) = 0.
60 END DO
61 END DO
62
63
64 ! ............ integration de ps ..............
65
66 CALL scopy(ip1jmp1*llm,masse,1,massescr,1)
67
68 DO ij = 1, ip1jmp1
69 pscr(ij) = ps(ij)
70 ps(ij) = psm1(ij) + dt*dp(ij)
71 END DO
72
73 DO ij = 1, ip1jmp1
74 IF (ps(ij)<0.) THEN
75 PRINT *, ' Au point ij = ', ij, ' , pression sol neg. ', ps(ij)
76 STOP 'integrd'
77 END IF
78 END DO
79
80 DO ij = 1, iim
81 tppn(ij) = aire(ij)*ps(ij)
82 tpps(ij) = aire(ij+ip1jm)*ps(ij+ip1jm)
83 END DO
84 tpn = ssum(iim,tppn,1)/apoln
85 tps = ssum(iim,tpps,1)/apols
86 DO ij = 1, iip1
87 ps(ij) = tpn
88 ps(ij+ip1jm) = tps
89 END DO
90
91 ! ... Calcul de la nouvelle masse d'air au dernier temps integre t+1 .
92
93 CALL pression(ip1jmp1,ap,bp,ps,p)
94 CALL massdair(p,masse)
95
96 CALL scopy(ijp1llm,masse,1,finvmasse,1)
97 CALL filtreg(finvmasse,jjp1,llm,-2,2,.TRUE.,1)
98
99
100 ! ............ integration de ucov, vcov, h ..............
101
102 DO l = 1, llm
103
104 DO ij = iip2, ip1jm
105 uscr(ij) = ucov(ij,l)
106 ucov(ij,l) = ucovm1(ij,l) + dt*du(ij,l)
107 END DO
108
109 DO ij = 1, ip1jm
110 vscr(ij) = vcov(ij,l)
111 vcov(ij,l) = vcovm1(ij,l) + dt*dv(ij,l)
112 END DO
113
114 DO ij = 1, ip1jmp1
115 hscr(ij) = teta(ij,l)
116 teta(ij,l) = tetam1(ij,l)*massem1(ij,l)/masse(ij,l) + &
117 dt*dteta(ij,l)/masse(ij,l)
118 END DO
119
120 ! .... Calcul de la valeur moyenne, unique aux poles pour teta .
121
122
123 DO ij = 1, iim
124 tppn(ij) = aire(ij)*teta(ij,l)
125 tpps(ij) = aire(ij+ip1jm)*teta(ij+ip1jm,l)
126 END DO
127 tpn = ssum(iim,tppn,1)/apoln
128 tps = ssum(iim,tpps,1)/apols
129
130 DO ij = 1, iip1
131 teta(ij,l) = tpn
132 teta(ij+ip1jm,l) = tps
133 END DO
134
135
136 IF (leapf) THEN
137 CALL scopy(ip1jmp1,uscr(1),1,ucovm1(1,l),1)
138 CALL scopy(ip1jm,vscr(1),1,vcovm1(1,l),1)
139 CALL scopy(ip1jmp1,hscr(1),1,tetam1(1,l),1)
140 END IF
141
142 END DO
143
144 DO l = 1, llm
145 DO ij = 1, ip1jmp1
146 deltap(ij,l) = p(ij,l) - p(ij,l+1)
147 END DO
148 END DO
149
150 CALL qminimum(q,nq,deltap)
151
152 ! ..... Calcul de la valeur moyenne, unique aux poles pour q .....
153
154
155 DO iq = 1, nq
156 DO l = 1, llm
157
158 DO ij = 1, iim
159 qppn(ij) = aire(ij)*q(ij,l,iq)
160 qpps(ij) = aire(ij+ip1jm)*q(ij+ip1jm,l,iq)
161 END DO
162 qpn = ssum(iim,qppn,1)/apoln
163 qps = ssum(iim,qpps,1)/apols
164
165 DO ij = 1, iip1
166 q(ij,l,iq) = qpn
167 q(ij+ip1jm,l,iq) = qps
168 END DO
169
170 END DO
171 END DO
172
173
174 CALL scopy(ijp1llm,finvmasse,1,finvmaold,1)
175
176
177 ! ..... FIN de l'integration de q .......
178
179 IF (leapf) THEN
180 CALL scopy(ip1jmp1,pscr,1,psm1,1)
181 CALL scopy(ip1jmp1*llm,massescr,1,massem1,1)
182 END IF
183
184 END SUBROUTINE integrd
185
186 end module integrd_m

  ViewVC Help
Powered by ViewVC 1.1.21