source: trunk/LMDZ.PLUTO.old/libf/dyn3d/integrd.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 5.8 KB
Line 
1      SUBROUTINE integrd
2     $  (  nq,vcovm1,ucovm1,tetam1,psm1,massem1,
3     $     dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,finvmaold )
4
5      IMPLICIT NONE
6
7
8c=======================================================================
9cccccccccccccccccccccccccccccccccccccccccccc
10c
11!Mars       VERSION MARTIENNE de integrd.F
12c
13c   ..   modification de l'integration de  q   . 26/04/94 ..
14c   ....   Si shema Van-leer pour advection de q , on n'integre pas  q
15c      car q  a ete deja integre   dans "tracvl.F" appele par vanleer   ...
16cccccccccccccccccccccccccccccccccccccccccccc
17
18c
19c   Auteur:  P. Le Van
20c   -------
21c
22c   objet:
23c   ------
24c
25c   Incrementation des tendances dynamiques
26c
27c=======================================================================
28c-----------------------------------------------------------------------
29c   Declarations:
30c   -------------
31
32#include "dimensions.h"
33#include "paramet.h"
34#include "comconst.h"
35#include "comgeom.h"
36#include "comvert.h"
37#include "logic.h"
38#include "temps.h"
39#include "serre.h"
40
41c   Arguments:
42c   ----------
43
44      INTEGER nq
45
46      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
47      REAL q(ip1jmp1,llm,nq)
48      REAL ps(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1)
49
50      REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
51      REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm)
52
53      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
54      REAL dteta(ip1jmp1,llm),dp(ip1jmp1)
55      REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm)
56
57c   Local:
58c   ------
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      EXTERNAL  filtreg,massdair,pression
70      EXTERNAL  SCOPY
71      REAL SSUM
72      EXTERNAL SSUM
73
74c-----------------------------------------------------------------------
75
76      DO  l = 1,llm
77        DO  ij = 1,iip1
78         ucov(    ij    , l) = 0.
79         ucov( ij +ip1jm, l) = 0.
80         uscr(     ij      ) = 0.
81         uscr( ij +ip1jm   ) = 0.
82        ENDDO
83      ENDDO
84
85
86c    ............    integration  de       ps         ..............
87
88      !PRINT*,' TB18 dimdim=',ip1jmp1,llm,ip1jmp1*llm
89      !PRINT*,' TB18 massescr0=',massescr(:,1)
90      !PRINT*,' TB18 massescr00=',massescr(:,20)
91      !PRINT*,' TB18 massescr000=',massescr
92      !PRINT*,' TB18 shape=',shape(massescr)
93      !PRINT*,' TB18 shapem0=',shape(masse)
94      CALL scopydyn(ip1jmp1*llm, masse, 1, massescr, 1)
95      !PRINT*,' TB18 massescr=',massescr(:,1)
96      !PRINT*,' TB18 massescr=',massescr(:,20)
97      !PRINT*,' TB18 masse=',masse
98      !PRINT*,' TB18 shape1=',shape(massescr)
99      !PRINT*,' TB18 shapem=',shape(masse)
100      !DO ij = 1,ip1jmp1
101      !   DO l = 1,llm
102      !      if ( masse(ij,l).ne.massescr(ij,l)) then
103      !         PRINT*,' TB18 diff=',masse(ij,l)
104      !         PRINT*,' TB18 diff2=',massescr(ij,l)
105      !         PRINT*,' TB18 diff3=',ij,l   
106      !      endif
107      !   ENDDO
108      !ENDDO
109
110      DO 2 ij = 1,ip1jmp1
111       pscr (ij)    = ps(ij)
112       ps (ij)      = psm1(ij) + dt * dp(ij)
113c       write(102,*)'pression sol',ps(ij)
114   2  CONTINUE
115c
116      DO ij = 1,ip1jmp1
117        IF( ps(ij).LT.0. ) THEN
118         PRINT*,' Au point ij = ',ij, ' , pression sol neg. ', ps(ij)
119         write(*,*)'psm1(ij)=',psm1(ij),' dp(ij)=',dp(ij),
120     &             'dp(ij)*dt=',dp(ij)*dt,' dt=',dt
121         !PRINT*,'  TB18 ps= ',ps
122         !STOP' dans integrd'
123         !ps (ij)      = psm1(ij)  ! TB18
124        ENDIF
125      ENDDO
126c
127      IF( alphax.NE.0. )   THEN
128         DO  ij    = 1, iim
129          tppn(ij) = aire(   ij   ) * ps(  ij    )
130          tpps(ij) = aire(ij+ip1jm) * ps(ij+ip1jm)
131         ENDDO
132          tpn      = SSUM(iim,tppn,1)/apoln
133          tps      = SSUM(iim,tpps,1)/apols
134         DO ij   = 1, iip1
135          ps(   ij   )  = tpn
136          ps(ij+ip1jm)  = tps
137         ENDDO
138      ENDIF
139c
140c  ... Calcul  de la nouvelle masse d'air au dernier temps integre t+1 ...
141c
142      CALL pression ( ip1jmp1, ap, bp, ps, p )
143      CALL massdair (     p  , masse         )
144
145      CALL SCOPY( ijp1llm  , masse, 1, finvmasse,  1      )
146      CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1  )
147c
148
149c    ............   integration  de  ucov, vcov,  h     ..............
150
151      DO 10 l = 1,llm
152
153      DO 4 ij = iip2,ip1jm
154      uscr( ij )   =  ucov( ij,l )
155      ucov( ij,l ) = ucovm1( ij,l ) + dt * du( ij,l )
156   4  CONTINUE
157
158      DO 5 ij = 1,ip1jm
159      vscr( ij )   =  vcov( ij,l )
160      vcov( ij,l ) = vcovm1( ij,l ) + dt * dv( ij,l )
161   5  CONTINUE
162
163      DO 6 ij = 1,ip1jmp1
164      hscr( ij )    =  teta(ij,l)
165      teta ( ij,l ) = tetam1(ij,l) *  massem1(ij,l) / masse(ij,l)
166     $                + dt * dteta(ij,l) / masse(ij,l)
167   6  CONTINUE
168
169c   ....  Calcul de la valeur moyenne, unique  aux poles pour  teta    ......
170c
171c
172      DO  ij   = 1, iim
173        tppn(ij) = aire(   ij   ) * teta(  ij    ,l)
174        tpps(ij) = aire(ij+ip1jm) * teta(ij+ip1jm,l)
175      ENDDO
176        tpn      = SSUM(iim,tppn,1)/apoln
177        tps      = SSUM(iim,tpps,1)/apols
178
179      DO ij   = 1, iip1
180        teta(   ij   ,l)  = tpn
181        teta(ij+ip1jm,l)  = tps
182      ENDDO
183c
184
185      IF(leapf)  THEN
186         CALL SCOPY ( ip1jmp1, uscr(1), 1, ucovm1(1, l), 1 )
187         CALL SCOPY (   ip1jm, vscr(1), 1, vcovm1(1, l), 1 )
188         CALL SCOPY ( ip1jmp1, hscr(1), 1, tetam1(1, l), 1 )
189      END IF
190
191  10  CONTINUE
192
193
194c
195c   .......  integration de   q   ......
196c
197c
198c     .....   FIN  de l'integration  de   q    .......
199
200c    .................................................................
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
Note: See TracBrowser for help on using the repository browser.