source: LMDZ5/trunk/libf/dyn3d/dissip.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: 3.4 KB
Line 
1!
2! $Id: dissip.F 1987 2014-02-24 15:05:47Z emillour $
3!
4      SUBROUTINE dissip( vcov,ucov,teta,p, dv,du,dh )
5c
6      IMPLICIT NONE
7
8
9c ..  Avec nouveaux operateurs star :  gradiv2 , divgrad2, nxgraro2  ...
10c                                 (  10/01/98  )
11
12c=======================================================================
13c
14c   Auteur:  P. Le Van
15c   -------
16c
17c   Objet:
18c   ------
19c
20c   Dissipation horizontale
21c
22c=======================================================================
23c-----------------------------------------------------------------------
24c   Declarations:
25c   -------------
26
27#include "dimensions.h"
28#include "paramet.h"
29#include "comconst.h"
30#include "comgeom.h"
31#include "comdissnew.h"
32#include "comdissipn.h"
33
34c   Arguments:
35c   ----------
36
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) :: p(ip1jmp1,llmp1) ! pressure
41      ! tendencies (.../s) on covariant winds and potential temperature
42      REAL,INTENT(OUT) :: dv(ip1jm,llm)
43      REAL,INTENT(OUT) :: du(ip1jmp1,llm)
44      REAL,INTENT(OUT) :: dh(ip1jmp1,llm)
45
46c   Local:
47c   ------
48
49      REAL gdx(ip1jmp1,llm),gdy(ip1jm,llm)
50      REAL grx(ip1jmp1,llm),gry(ip1jm,llm)
51      REAL te1dt(llm),te2dt(llm),te3dt(llm)
52      REAL deltapres(ip1jmp1,llm)
53
54      INTEGER l,ij
55
56      REAL  SSUM
57
58c-----------------------------------------------------------------------
59c   initialisations:
60c   ----------------
61
62      DO l=1,llm
63         te1dt(l) = tetaudiv(l) * dtdiss
64         te2dt(l) = tetaurot(l) * dtdiss
65         te3dt(l) = tetah(l)    * dtdiss
66      ENDDO
67      du=0.
68      dv=0.
69      dh=0.
70
71c-----------------------------------------------------------------------
72c   Calcul de la dissipation:
73c   -------------------------
74
75c   Calcul de la partie   grad  ( div ) :
76c   -------------------------------------
77
78
79      IF(lstardis) THEN
80         CALL gradiv2( llm,ucov,vcov,nitergdiv,gdx,gdy )
81      ELSE
82         CALL gradiv ( llm,ucov,vcov,nitergdiv,gdx,gdy )
83      ENDIF
84
85      DO l=1,llm
86
87         DO ij = 1, iip1
88            gdx(     ij ,l) = 0.
89            gdx(ij+ip1jm,l) = 0.
90         ENDDO
91
92         DO ij = iip2,ip1jm
93            du(ij,l) = du(ij,l) - te1dt(l) *gdx(ij,l)
94         ENDDO
95         DO ij = 1,ip1jm
96            dv(ij,l) = dv(ij,l) - te1dt(l) *gdy(ij,l)
97         ENDDO
98
99       ENDDO
100
101c   calcul de la partie   n X grad ( rot ):
102c   ---------------------------------------
103
104      IF(lstardis) THEN
105         CALL nxgraro2( llm,ucov, vcov, nitergrot,grx,gry )
106      ELSE
107         CALL nxgrarot( llm,ucov, vcov, nitergrot,grx,gry )
108      ENDIF
109
110
111      DO l=1,llm
112         DO ij = 1, iip1
113            grx(ij,l) = 0.
114         ENDDO
115
116         DO ij = iip2,ip1jm
117            du(ij,l) = du(ij,l) - te2dt(l) * grx(ij,l)
118         ENDDO
119         DO ij =  1, ip1jm
120            dv(ij,l) = dv(ij,l) - te2dt(l) * gry(ij,l)
121         ENDDO
122      ENDDO
123
124c   calcul de la partie   div ( grad ):
125c   -----------------------------------
126
127       
128      IF(lstardis) THEN
129
130       DO l = 1, llm
131          DO ij = 1, ip1jmp1
132            deltapres(ij,l) = AMAX1( 0.,  p(ij,l) - p(ij,l+1) )
133          ENDDO
134       ENDDO
135
136         CALL divgrad2( llm,teta, deltapres  ,niterh, gdx )
137      ELSE
138         CALL divgrad ( llm,teta, niterh, gdx        )
139      ENDIF
140
141      DO l = 1,llm
142         DO ij = 1,ip1jmp1
143            dh( ij,l ) = dh( ij,l ) - te3dt(l) * gdx( ij,l )
144         ENDDO
145      ENDDO
146
147      RETURN
148      END
Note: See TracBrowser for help on using the repository browser.