source: trunk/LMDZ.COMMON/libf/dyn3dpar/caldyn_p.F @ 1980

Last change on this file since 1980 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

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