source: LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_caldyn.f90 @ 5209

Last change on this file since 5209 was 5186, checked in by abarral, 9 days ago

Encapsulate files in modules

  • 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.2 KB
Line 
1MODULE lmdz_caldyn
2  IMPLICIT NONE; PRIVATE
3  PUBLIC caldyn
4
5CONTAINS
6
7  SUBROUTINE caldyn &
8          (itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, &
9          phi, conser, du, dv, dteta, dp, w, pbaru, pbarv, time)
10
11    USE comvert_mod, ONLY: ap, bp
12    USE lmdz_comgeom
13
14    USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
15    USE lmdz_paramet
16    USE lmdz_advect, ONLY: advect
17    USE lmdz_dteta1, ONLY: dteta1
18    USE lmdz_dudv1, ONLY: dudv1
19    USE lmdz_dudv2, ONLY: dudv2
20
21    IMPLICIT NONE
22
23    !=======================================================================
24
25    !  Auteur :  P. Le Van
26
27    !   Objet:
28    !   ------
29
30    !   Calcul des tendances dynamiques.
31
32    ! Modif 04/93 F.Forget
33    !=======================================================================
34
35    !-----------------------------------------------------------------------
36    !   0. Declarations:
37    !   ----------------
38
39
40
41
42    !   Arguments:
43    !   ----------
44
45    LOGICAL, INTENT(IN) :: conser ! triggers printing some diagnostics
46    INTEGER, INTENT(IN) :: itau ! time step index
47    REAL, INTENT(IN) :: vcov(ip1jm, llm) ! covariant meridional wind
48    REAL, INTENT(IN) :: ucov(ip1jmp1, llm) ! covariant zonal wind
49    REAL, INTENT(IN) :: teta(ip1jmp1, llm) ! potential temperature
50    REAL, INTENT(IN) :: ps(ip1jmp1) ! surface pressure
51    REAL, INTENT(IN) :: phis(ip1jmp1) ! geopotential at the surface
52    REAL, INTENT(IN) :: pk(ip1jmp1, llm) ! Exner at mid-layer
53    REAL, INTENT(IN) :: pkf(ip1jmp1, llm) ! filtered Exner
54    REAL, INTENT(IN) :: phi(ip1jmp1, llm) ! geopotential
55    REAL, INTENT(OUT) :: masse(ip1jmp1, llm) ! air mass
56    REAL, INTENT(OUT) :: dv(ip1jm, llm) ! tendency on vcov
57    REAL, INTENT(OUT) :: du(ip1jmp1, llm) ! tendency on ucov
58    REAL, INTENT(OUT) :: dteta(ip1jmp1, llm) ! tenddency on teta
59    REAL, INTENT(OUT) :: dp(ip1jmp1) ! tendency on ps
60    REAL, INTENT(OUT) :: w(ip1jmp1, llm) ! vertical velocity
61    REAL, INTENT(OUT) :: pbaru(ip1jmp1, llm) ! mass flux in the zonal direction
62    REAL, INTENT(OUT) :: pbarv(ip1jm, llm) ! mass flux in the meridional direction
63    REAL, INTENT(IN) :: time ! current time
64
65    !   Local:
66    !   ------
67
68    REAL :: vcont(ip1jm, llm), ucont(ip1jmp1, llm)
69    REAL :: ang(ip1jmp1, llm), p(ip1jmp1, llmp1)
70    REAL :: massebx(ip1jmp1, llm), masseby(ip1jm, llm), psexbarxy(ip1jm)
71    REAL :: vorpot(ip1jm, llm)
72    REAL :: ecin(ip1jmp1, llm), convm(ip1jmp1, llm)
73    REAL :: bern(ip1jmp1, llm)
74    REAL :: massebxy(ip1jm, llm)
75
76    INTEGER :: ij, l
77
78    !-----------------------------------------------------------------------
79    !   Compute dynamical tendencies:
80    !--------------------------------
81
82    ! compute contravariant winds ucont() and vcont
83    CALL covcont  (llm, ucov, vcov, ucont, vcont)
84    ! compute pressure p()
85    CALL pression (ip1jmp1, ap, bp, ps, p)
86    ! compute psexbarxy() XY-area weighted-averaged surface pressure (what for?)
87    CALL psextbar (ps, psexbarxy)
88    ! compute mass in each atmospheric mesh: masse()
89    CALL massdair (p, masse)
90    ! compute X and Y-averages of mass, massebx() and masseby()
91    CALL massbar  (masse, massebx, masseby)
92    ! compute XY-average of mass, massebxy()
93    CALL massbarxy(masse, massebxy)
94    ! compute mass fluxes pbaru() and pbarv()
95    CALL flumass  (massebx, masseby, vcont, ucont, pbaru, pbarv)
96    ! compute dteta() , horizontal converging flux of theta
97    CALL dteta1   (teta, pbaru, pbarv, dteta)
98    ! compute convm(), horizontal converging flux of mass
99    CALL convmas  (pbaru, pbarv, convm)
100
101    ! compute pressure variation due to mass convergence
102    DO ij = 1, ip1jmp1
103      dp(ij) = convm(ij, 1) / airesurg(ij)
104    ENDDO
105
106    ! compute vertical velocity w()
107    CALL vitvert (convm, w)
108    ! compute potential vorticity vorpot()
109    CALL tourpot (vcov, ucov, massebxy, vorpot)
110    ! compute rotation induced du() and dv()
111    CALL dudv1   (vorpot, pbaru, pbarv, du, dv)
112    ! compute kinetic energy ecin()
113    CALL enercin (vcov, ucov, vcont, ucont, ecin)
114    ! compute Bernouilli function bern()
115    CALL bernoui (ip1jmp1, llm, phi, ecin, bern)
116    ! compute and add du() and dv() contributions from Bernouilli and pressure
117    CALL dudv2   (teta, pkf, bern, du, dv)
118
119    DO l = 1, llm
120      DO ij = 1, ip1jmp1
121        ang(ij, l) = ucov(ij, l) + constang(ij)
122      ENDDO
123    ENDDO
124
125    ! compute vertical advection contributions to du(), dv() and dteta()
126    CALL advect(ang, vcov, teta, w, massebx, masseby, du, dv, dteta)
127
128    !  WARNING probleme de peridocite de dv sur les PC/linux. Pb d'arrondi
129    ! probablement. Observe sur le code compile avec pgf90 3.0-1
130
131    DO l = 1, llm
132      DO ij = 1, ip1jm, iip1
133        IF(dv(ij, l)/=dv(ij + iim, l))  THEN
134          ! PRINT *,'!!!ATTENTION!!! probleme de periodicite sur vcov',
135          !    ,   ' dans caldyn'
136          ! PRINT *,' l,  ij = ', l, ij, ij+iim,dv(ij+iim,l),dv(ij,l)
137          dv(ij + iim, l) = dv(ij, l)
138        ENDIF
139      ENDDO
140    ENDDO
141
142    !-----------------------------------------------------------------------
143    !   Output some control variables:
144    !---------------------------------
145
146    IF(conser)  THEN
147      CALL sortvarc &
148              (itau, ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, time, vcov)
149    ENDIF
150
151  END SUBROUTINE caldyn
152
153END MODULE lmdz_caldyn
Note: See TracBrowser for help on using the repository browser.