source: LMDZ5/trunk/libf/dyn3dmem/dissip_loc.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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
File size: 5.1 KB
Line 
1      SUBROUTINE dissip_loc( vcov,ucov,teta,p, dv,du,dh )
2c
3      USE parallel_lmdz
4      USE write_field_loc
5      USE dissip_mod
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 vcov(ijb_v:ije_v,llm),ucov(ijb_u:ije_u,llm)
38      REAL teta(ijb_u:ije_u,llm)
39      REAL  p( ijb_u:ije_u,llmp1 )
40      REAL dv(ijb_v:ije_v,llm),du(ijb_u:ije_u,llm),dh(ijb_u:ije_u,llm)
41
42c   Local:
43c   ------
44
45      REAL gdx(ijb_u:ije_u,llm),gdy(ijb_v:ije_v,llm)
46      REAL grx(ijb_u:ije_u,llm),gry(ijb_v:ije_v,llm)
47      REAL te1dt(llm),te2dt(llm),te3dt(llm)
48      REAL deltapres(ijb_u:ije_u,llm)
49
50      INTEGER l,ij
51
52      REAL  SSUM
53      integer :: ijb,ije
54     
55      LOGICAl,SAVE :: first=.TRUE.
56!$OMP THREADPRIVATE(first)
57
58      IF (first) THEN
59        CALL dissip_allocate
60        first=.FALSE.
61      ENDIF
62c-----------------------------------------------------------------------
63c   initialisations:
64c   ----------------
65
66c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
67      DO l=1,llm
68         te1dt(l) = tetaudiv(l) * dtdiss
69         te2dt(l) = tetaurot(l) * dtdiss
70         te3dt(l) = tetah(l)    * dtdiss
71      ENDDO
72c$OMP END DO NOWAIT
73c      CALL initial0( ijp1llm, du )
74c      CALL initial0( ijmllm , dv )
75c      CALL initial0( ijp1llm, dh )
76     
77      ijb=ij_begin
78      ije=ij_end
79
80c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
81      DO l=1,llm
82        du(ijb:ije,l)=0
83        dh(ijb:ije,l)=0
84      ENDDO
85c$OMP END DO NOWAIT
86     
87      if (pole_sud) ije=ij_end-iip1
88
89c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
90      DO l=1,llm
91        dv(ijb:ije,l)=0
92      ENDDO
93c$OMP END DO NOWAIT
94     
95c-----------------------------------------------------------------------
96c   Calcul de la dissipation:
97c   -------------------------
98
99c   Calcul de la partie   grad  ( div ) :
100c   -------------------------------------
101     
102     
103     
104      IF(lstardis) THEN
105c      IF (.FALSE.) THEN
106         CALL gradiv2_loc( llm,ucov,vcov,nitergdiv,gdx,gdy )
107      ELSE
108!         CALL gradiv_p ( llm,ucov,vcov,nitergdiv,gdx,gdy )
109      ENDIF
110
111#ifdef DEBUG_IO   
112      call WriteField_u('gdx',gdx)
113      call WriteField_v('gdy',gdy)
114#endif
115
116      ijb=ij_begin
117      ije=ij_end
118      if (pole_sud) ije=ij_end-iip1
119
120c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
121      DO l=1,llm
122         if (pole_nord) then
123           DO ij = 1, iip1
124              gdx(     ij ,l) = 0.
125           ENDDO
126         endif
127         
128         if (pole_sud) then
129           DO ij = 1, iip1
130              gdx(ij+ip1jm,l) = 0.
131           ENDDO
132         endif
133         
134         if (pole_nord) ijb=ij_begin+iip1
135         DO ij = ijb,ije
136            du(ij,l) = du(ij,l) - te1dt(l) *gdx(ij,l)
137         ENDDO
138
139         if (pole_nord) ijb=ij_begin
140         DO ij = ijb,ije
141            dv(ij,l) = dv(ij,l) - te1dt(l) *gdy(ij,l)
142         ENDDO
143
144       ENDDO
145c$OMP END DO NOWAIT
146c   calcul de la partie   n X grad ( rot ):
147c   ---------------------------------------
148
149      IF(lstardis) THEN
150c      IF (.FALSE.) THEN
151         CALL nxgraro2_loc( llm,ucov, vcov, nitergrot,grx,gry )
152      ELSE
153!         CALL nxgrarot_p( llm,ucov, vcov, nitergrot,grx,gry )
154      ENDIF
155
156#ifdef DEBUG_IO   
157      call WriteField_u('grx',grx)
158      call WriteField_v('gry',gry)
159#endif
160
161
162      ijb=ij_begin
163      ije=ij_end
164      if (pole_sud) ije=ij_end-iip1
165
166c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
167      DO l=1,llm
168         
169         if (pole_nord) then
170           DO ij = 1, iip1
171              grx(ij,l) = 0.
172           ENDDO
173         endif
174         
175         if (pole_nord) ijb=ij_begin+iip1
176         DO ij = ijb,ije
177            du(ij,l) = du(ij,l) - te2dt(l) * grx(ij,l)
178         ENDDO
179         
180         if (pole_nord) ijb=ij_begin
181         DO ij =  ijb, ije
182            dv(ij,l) = dv(ij,l) - te2dt(l) * gry(ij,l)
183         ENDDO
184     
185      ENDDO
186c$OMP END DO NOWAIT
187
188c   calcul de la partie   div ( grad ):
189c   -----------------------------------
190
191       
192      IF(lstardis) THEN
193c      IF (.FALSE.) THEN
194   
195      ijb=ij_begin
196      ije=ij_end
197
198c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)     
199       DO l = 1, llm
200          DO ij = ijb, ije
201            deltapres(ij,l) = AMAX1( 0.,  p(ij,l) - p(ij,l+1) )
202          ENDDO
203       ENDDO
204c$OMP END DO NOWAIT
205         CALL divgrad2_loc( llm,teta, deltapres  ,niterh, gdx )
206      ELSE
207!         CALL divgrad_p ( llm,teta, niterh, gdx        )
208      ENDIF
209
210#ifdef DEBUG_IO   
211      call WriteField_u('gdx',gdx)
212#endif
213
214
215      ijb=ij_begin
216      ije=ij_end
217     
218c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)     
219      DO l = 1,llm
220         DO ij = ijb,ije
221            dh( ij,l ) = dh( ij,l ) - te3dt(l) * gdx( ij,l )
222         ENDDO
223      ENDDO
224c$OMP END DO NOWAIT
225
226      RETURN
227      END
Note: See TracBrowser for help on using the repository browser.