source: LMDZ5/trunk/libf/dyn3d/caldyn.F @ 1987

Last change on this file since 1987 was 1987, checked in by Ehouarn Millour, 10 years ago

Add updating pressure, mass and Exner function (ie: all variables which depend on surface pressure) after adding physics tendencies (which include a surface pressure tendency).
Note that this change induces slight changes in GCM results with respect to previous svn version of the code, even if surface pressure tendency is zero (because of recomputation of polar values as an average over polar points on the dynamics grid).
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.3 KB
Line 
1!
2! $Id: caldyn.F 1987 2014-02-24 15:05:47Z emillour $
3!
4      SUBROUTINE caldyn
5     $ (itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
6     $  phi,conser,du,dv,dteta,dp,w,pbaru,pbarv,time )
7
8      IMPLICIT NONE
9
10!=======================================================================
11!
12!  Auteur :  P. Le Van
13!
14!   Objet:
15!   ------
16!
17!   Calcul des tendances dynamiques.
18!
19! Modif 04/93 F.Forget
20!=======================================================================
21
22!-----------------------------------------------------------------------
23!   0. Declarations:
24!   ----------------
25
26#include "dimensions.h"
27#include "paramet.h"
28#include "comconst.h"
29#include "comvert.h"
30#include "comgeom.h"
31
32!   Arguments:
33!   ----------
34
35      LOGICAL,INTENT(IN) :: conser ! triggers printing some diagnostics
36      INTEGER,INTENT(IN) :: itau ! time step index
37      REAL,INTENT(IN) :: vcov(ip1jm,llm) ! covariant meridional wind
38      REAL,INTENT(IN) :: ucov(ip1jmp1,llm) ! covariant zonal wind
39      REAL,INTENT(IN) :: teta(ip1jmp1,llm) ! potential temperature
40      REAL,INTENT(IN) :: ps(ip1jmp1) ! surface pressure
41      REAL,INTENT(IN) :: phis(ip1jmp1) ! geopotential at the surface
42      REAL,INTENT(IN) :: pk(ip1jmp1,llm) ! Exner at mid-layer
43      REAL,INTENT(IN) :: pkf(ip1jmp1,llm) ! filtered Exner
44      REAL,INTENT(IN) :: phi(ip1jmp1,llm) ! geopotential
45      REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass
46      REAL,INTENT(OUT) :: dv(ip1jm,llm) ! tendency on vcov
47      REAL,INTENT(OUT) :: du(ip1jmp1,llm) ! tendency on ucov
48      REAL,INTENT(OUT) :: dteta(ip1jmp1,llm) ! tenddency on teta
49      REAL,INTENT(OUT) :: dp(ip1jmp1) ! tendency on ps
50      REAL,INTENT(OUT) :: w(ip1jmp1,llm) ! vertical velocity
51      REAL,INTENT(OUT) :: pbaru(ip1jmp1,llm) ! mass flux in the zonal direction
52      REAL,INTENT(OUT) :: pbarv(ip1jm,llm) ! mass flux in the meridional direction
53      REAL,INTENT(IN) :: time ! current time
54
55!   Local:
56!   ------
57
58      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
59      REAL ang(ip1jmp1,llm),p(ip1jmp1,llmp1)
60      REAL massebx(ip1jmp1,llm),masseby(ip1jm,llm),psexbarxy(ip1jm)
61      REAL vorpot(ip1jm,llm)
62      REAL ecin(ip1jmp1,llm),convm(ip1jmp1,llm)
63      REAL bern(ip1jmp1,llm)
64      REAL massebxy(ip1jm,llm)
65   
66
67      INTEGER   ij,l
68
69!-----------------------------------------------------------------------
70!   Compute dynamical tendencies:
71!--------------------------------
72
73      ! compute contravariant winds ucont() and vcont
74      CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
75      ! compute pressure p()
76      CALL pression ( ip1jmp1, ap      , bp   ,  ps  , p            )
77      ! compute psexbarxy() XY-area weighted-averaged surface pressure (what for?)
78      CALL psextbar (   ps   , psexbarxy                            )
79      ! compute mass in each atmospheric mesh: masse()
80      CALL massdair (    p   , masse                                )
81      ! compute X and Y-averages of mass, massebx() and masseby()
82      CALL massbar  (   masse, massebx , masseby                    )
83      ! compute XY-average of mass, massebxy()
84      call massbarxy(   masse, massebxy                             )
85      ! compute mass fluxes pbaru() and pbarv()
86      CALL flumass  ( massebx, masseby , vcont, ucont ,pbaru, pbarv )
87      ! compute dteta() , horizontal converging flux of theta
88      CALL dteta1   (   teta , pbaru   , pbarv, dteta               )
89      ! compute convm(), horizontal converging flux of mass
90      CALL convmas  (   pbaru, pbarv   , convm                      )
91
92      ! compute pressure variation due to mass convergence
93      DO ij =1, ip1jmp1
94         dp( ij ) = convm( ij,1 ) / airesurg( ij )
95      ENDDO
96
97      ! compute vertical velocity w()
98      CALL vitvert ( convm  , w                                  )
99      ! compute potential vorticity vorpot()
100      CALL tourpot ( vcov   , ucov  , massebxy  , vorpot         )
101      ! compute rotation induced du() and dv()
102      CALL dudv1   ( vorpot , pbaru , pbarv     , du     , dv    )
103      ! compute kinetic energy ecin()
104      CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
105      ! compute Bernouilli function bern()
106      CALL bernoui ( ip1jmp1, llm   , phi       , ecin   , bern  )
107      ! compute and add du() and dv() contributions from Bernouilli and pressure
108      CALL dudv2   ( teta   , pkf   , bern      , du     , dv    )
109
110
111      DO l=1,llm
112         DO ij=1,ip1jmp1
113            ang(ij,l) = ucov(ij,l) + constang(ij)
114         ENDDO
115      ENDDO
116
117      ! compute vertical advection contributions to du(), dv() and dteta()
118      CALL advect( ang, vcov, teta, w, massebx, masseby, du, dv,dteta )
119
120!  WARNING probleme de peridocite de dv sur les PC/linux. Pb d'arrondi
121!          probablement. Observe sur le code compile avec pgf90 3.0-1
122
123      DO l = 1, llm
124         DO ij = 1, ip1jm, iip1
125           IF( dv(ij,l).NE.dv(ij+iim,l) )  THEN
126!         PRINT *,'!!!ATTENTION!!! probleme de periodicite sur vcov', 
127!    ,   ' dans caldyn'
128!         PRINT *,' l,  ij = ', l, ij, ij+iim,dv(ij+iim,l),dv(ij,l)
129          dv(ij+iim,l) = dv(ij,l)
130           ENDIF
131         ENDDO
132      ENDDO
133
134!-----------------------------------------------------------------------
135!   Output some control variables:
136!---------------------------------
137
138      IF( conser )  THEN
139        CALL sortvarc
140     & ( itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time,vcov )
141      ENDIF
142
143      END
Note: See TracBrowser for help on using the repository browser.