source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/caldyn_p.F @ 264

Last change on this file since 264 was 222, checked in by ymipsl, 10 years ago

Creating temporary dynamico/lmdz/saturn branche

YM

File size: 7.6 KB
Line 
1!
2! $Id: $
3!
4#undef DEBUG_IO
5c#define DEBUG_IO
6
7      SUBROUTINE caldyn_p
8     $ (itau,ucov,vcov,teta,ps,masse,pk,pkf,tsurpk,phis ,
9     $  phi,conser,du,dv,dteta,dp,w,pbaru,pbarv,time )
10      USE parallel_lmdz
11      USE Write_Field_p
12     
13      IMPLICIT NONE
14
15!=======================================================================
16!
17!  Auteur :  P. Le Van
18!
19!   Objet:
20!   ------
21!
22!   Calcul des tendances dynamiques.
23!
24! Modif 04/93 F.Forget
25!=======================================================================
26
27!-----------------------------------------------------------------------
28!   0. Declarations:
29!   ----------------
30
31#include "dimensions.h"
32#include "paramet.h"
33#include "comconst.h"
34#include "comvert.h"
35#include "comgeom.h"
36
37!   Arguments:
38!   ----------
39
40      LOGICAL,INTENT(IN) :: conser ! triggers printing some diagnostics
41      INTEGER,INTENT(IN) :: itau ! time step index
42      REAL,INTENT(IN) :: vcov(ip1jm,llm) ! covariant meridional wind
43      REAL,INTENT(IN) :: ucov(ip1jmp1,llm) ! covariant zonal wind
44      REAL,INTENT(IN) :: teta(ip1jmp1,llm) ! potential temperature
45      REAL,INTENT(IN) :: ps(ip1jmp1) ! surface pressure
46      REAL,INTENT(IN) :: phis(ip1jmp1) ! geopotential at the surface
47      REAL,INTENT(IN) :: pk(ip1jmp1,llm) ! Exner at mid-layer
48      REAL,INTENT(IN) :: pkf(ip1jmp1,llm) ! filtered Exner
49      REAL,INTENT(IN) :: tsurpk(ip1jmp1,llm) ! cpp * temperature / pk
50      REAL,INTENT(IN) :: phi(ip1jmp1,llm) ! geopotential
51      REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass
52      REAL,INTENT(OUT) :: dv(ip1jm,llm) ! tendency on vcov
53      REAL,INTENT(OUT) :: du(ip1jmp1,llm) ! tendency on ucov
54      REAL,INTENT(OUT) :: dteta(ip1jmp1,llm) ! tenddency on teta
55      REAL,INTENT(OUT) :: dp(ip1jmp1) ! tendency on ps
56      REAL,INTENT(OUT) :: w(ip1jmp1,llm) ! vertical velocity
57      REAL,INTENT(OUT) :: pbaru(ip1jmp1,llm) ! mass flux in the zonal direction
58      REAL,INTENT(OUT) :: pbarv(ip1jm,llm) ! mass flux in the meridional direction
59      REAL,INTENT(IN) :: time ! current time
60
61!   Local:
62!   ------
63
64      REAL,SAVE :: vcont(ip1jm,llm),ucont(ip1jmp1,llm)
65      REAL,SAVE :: ang(ip1jmp1,llm)
66      REAL,SAVE :: p(ip1jmp1,llmp1)
67      REAL,SAVE :: massebx(ip1jmp1,llm),masseby(ip1jm,llm)
68      REAL,SAVE :: psexbarxy(ip1jm)
69      REAL,SAVE :: vorpot(ip1jm,llm)
70      REAL,SAVE :: ecin(ip1jmp1,llm)
71      REAL,SAVE :: bern(ip1jmp1,llm)
72      REAL,SAVE :: massebxy(ip1jm,llm)
73      REAL,SAVE :: convm(ip1jmp1,llm)
74!      REAL,SAVE :: temp(ip1jmp1,llm)
75      INTEGER   ij,l,ijb,ije,ierr
76
77!-----------------------------------------------------------------------
78!   Compute dynamical tendencies:
79!--------------------------------
80
81      ! compute contravariant winds ucont() and vcont
82      CALL covcont_p  ( llm    , ucov    , vcov , ucont, vcont        )
83      ! compute pressure p()
84      CALL pression_p ( ip1jmp1, ap      , bp   ,  ps  , p            )
85cym      CALL psextbar (   ps   , psexbarxy                          )
86c$OMP BARRIER
87      ! compute mass in each atmospheric mesh: masse()
88      CALL massdair_p (    p   , masse                                )
89      ! compute X and Y-averages of mass, massebx() and masseby()
90      CALL massbar_p  (   masse, massebx , masseby                    )
91      ! compute XY-average of mass, massebxy()
92      call massbarxy_p(   masse, massebxy                             )
93      ! compute mass fluxes pbaru() and pbarv()
94      CALL flumass_p  ( massebx, masseby , vcont, ucont ,pbaru, pbarv )
95      ! compute dteta() , horizontal converging flux of theta
96      CALL dteta1_p   (   teta , pbaru   , pbarv, dteta               )
97      ! compute convm(), horizontal converging flux of mass
98      CALL convmas1_p  (   pbaru, pbarv   , convm                      )
99c$OMP BARRIER     
100      CALL convmas2_p  (   convm                      )
101c$OMP BARRIER
102#ifdef DEBUG_IO
103c$OMP BARRIER
104c$OMP MASTER
105      call WriteField_p('ucont',reshape(ucont,(/iip1,jmp1,llm/)))
106      call WriteField_p('vcont',reshape(vcont,(/iip1,jjm,llm/)))
107      call WriteField_p('p',reshape(p,(/iip1,jmp1,llmp1/)))
108      call WriteField_p('masse',reshape(masse,(/iip1,jmp1,llm/)))
109      call WriteField_p('massebx',reshape(massebx,(/iip1,jmp1,llm/)))
110      call WriteField_p('masseby',reshape(masseby,(/iip1,jjm,llm/)))
111      call WriteField_p('massebxy',reshape(massebxy,(/iip1,jjm,llm/)))
112      call WriteField_p('pbaru',reshape(pbaru,(/iip1,jmp1,llm/)))
113      call WriteField_p('pbarv',reshape(pbarv,(/iip1,jjm,llm/)))
114      call WriteField_p('dteta',reshape(dteta,(/iip1,jmp1,llm/)))
115      call WriteField_p('convm',reshape(convm,(/iip1,jmp1,llm/)))
116c$OMP END MASTER
117c$OMP BARRIER
118#endif     
119
120c$OMP BARRIER
121c$OMP MASTER
122      ijb=ij_begin
123      ije=ij_end
124      ! compute pressure variation due to mass convergence
125      DO ij =ijb, ije
126         dp( ij ) = convm( ij,1 ) / airesurg( ij )
127      ENDDO
128c$OMP END MASTER
129c$OMP BARRIER
130c$OMP FLUSH
131
132      ! compute vertical velocity w()
133      CALL vitvert_p ( convm  , w                                  )
134      ! compute potential vorticity vorpot()
135      CALL tourpot_p ( vcov   , ucov  , massebxy  , vorpot         )
136      ! compute rotation induced du() and dv()
137      CALL dudv1_p   ( vorpot , pbaru , pbarv     , du     , dv    )
138
139#ifdef DEBUG_IO     
140c$OMP BARRIER
141c$OMP MASTER
142      call WriteField_p('w',reshape(w,(/iip1,jmp1,llm/)))
143      call WriteField_p('vorpot',reshape(vorpot,(/iip1,jjm,llm/)))
144      call WriteField_p('du',reshape(du,(/iip1,jmp1,llm/)))
145      call WriteField_p('dv',reshape(dv,(/iip1,jjm,llm/)))
146c$OMP END MASTER
147c$OMP BARRIER
148#endif     
149     
150      ! compute kinetic energy ecin()
151      CALL enercin_p ( vcov   , ucov  , vcont     , ucont  , ecin  )
152      ! compute Bernouilli function bern()
153      CALL bernoui_p ( ip1jmp1, llm   , phi       , ecin   , bern  )
154      ! compute and add du() and dv() contributions from Bernouilli and pressure
155      CALL dudv2_p   ( tsurpk , pkf   , bern      , du     , dv    )
156
157#ifdef DEBUG_IO
158c$OMP BARRIER
159c$OMP MASTER
160      call WriteField_p('ecin',reshape(ecin,(/iip1,jmp1,llm/)))
161      call WriteField_p('bern',reshape(bern,(/iip1,jmp1,llm/)))
162      call WriteField_p('du',reshape(du,(/iip1,jmp1,llm/)))
163      call WriteField_p('dv',reshape(dv,(/iip1,jjm,llm/)))
164      call WriteField_p('pkf',reshape(pkf,(/iip1,jmp1,llm/)))
165c$OMP END MASTER
166c$OMP BARRIER
167#endif
168     
169      ijb=ij_begin-iip1
170      ije=ij_end+iip1
171     
172      if (pole_nord) ijb=ij_begin
173      if (pole_sud) ije=ij_end
174
175c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
176      DO l=1,llm
177         DO ij=ijb,ije
178            ang(ij,l) = ucov(ij,l) + constang(ij)
179        ENDDO
180      ENDDO
181c$OMP END DO
182
183      ! compute vertical advection contributions to du(), dv() and dteta()
184      CALL advect_new_p(ang,vcov,teta,w,massebx,masseby,du,dv,dteta) 
185
186C  WARNING probleme de peridocite de dv sur les PC/linux. Pb d'arrondi
187C          probablement. Observe sur le code compile avec pgf90 3.0-1
188      ijb=ij_begin
189      ije=ij_end
190      if (pole_sud) ije=ij_end-iip1
191
192c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
193      DO l = 1, llm
194         DO ij = ijb, ije, iip1
195           IF( dv(ij,l).NE.dv(ij+iim,l) )  THEN
196c         PRINT *,'!!!ATTENTION!!! probleme de periodicite sur vcov', 
197c    ,   ' dans caldyn'
198c         PRINT *,' l,  ij = ', l, ij, ij+iim,dv(ij+iim,l),dv(ij,l)
199          dv(ij+iim,l) = dv(ij,l)
200          endif
201         enddo
202      enddo
203c$OMP END DO NOWAIT     
204c-----------------------------------------------------------------------
205c   Sorties eventuelles des variables de controle:
206c   ----------------------------------------------
207
208      IF( conser )  THEN
209c ym ---> exige communication collective ( aussi dans advect)
210        CALL sortvarc
211     $ (itau,ucov,tsurpk,ps,masse,pk,phis,vorpot,phi,bern,dp,time,vcov)
212
213      ENDIF
214
215      END
Note: See TracBrowser for help on using the repository browser.