LMDZ
dissip_loc.F
Go to the documentation of this file.
1 !
2 ! $Id: $
3 !
4  SUBROUTINE dissip_loc( vcov,ucov,teta,p, dv,du,dh )
5 c
6  USE parallel_lmdz
8  USE dissip_mod, ONLY: dissip_allocate
9  IMPLICIT NONE
10 
11 
12 c .. Avec nouveaux operateurs star : gradiv2 , divgrad2, nxgraro2 ...
13 c ( 10/01/98 )
14 
15 c=======================================================================
16 c
17 c Auteur: P. Le Van
18 c -------
19 c
20 c Objet:
21 c ------
22 c
23 c Dissipation horizontale
24 c
25 c=======================================================================
26 c-----------------------------------------------------------------------
27 c Declarations:
28 c -------------
29 
30 #include "dimensions.h"
31 #include "paramet.h"
32 #include "comconst.h"
33 #include "comgeom.h"
34 #include "comdissnew.h"
35 #include "comdissipn.h"
36 
37 c Arguments:
38 c ----------
39 
40  REAL,INTENT(IN) :: vcov(ijb_v:ije_v,llm) ! covariant meridional wind
41  REAL,INTENT(IN) :: ucov(ijb_u:ije_u,llm) ! covariant zonal wind
42  REAL,INTENT(IN) :: teta(ijb_u:ije_u,llm) ! potential temperature
43  REAL,INTENT(IN) :: p(ijb_u:ije_u,llmp1) ! interlayer pressure
44  ! tendencies (.../s) on covariant winds and potential temperature
45  REAL,INTENT(OUT) :: dv(ijb_v:ije_v,llm)
46  REAL,INTENT(OUT) :: du(ijb_u:ije_u,llm)
47  REAL,INTENT(OUT) :: dh(ijb_u:ije_u,llm)
48 
49 c Local:
50 c ------
51 
52  REAL gdx(ijb_u:ije_u,llm),gdy(ijb_v:ije_v,llm)
53  REAL grx(ijb_u:ije_u,llm),gry(ijb_v:ije_v,llm)
54  REAL te1dt(llm),te2dt(llm),te3dt(llm)
55  REAL deltapres(ijb_u:ije_u,llm)
56 
57  INTEGER l,ij
58 
59  REAL SSUM
60  integer :: ijb,ije
61 
62  LOGICAl,SAVE :: first=.true.
63 !$OMP THREADPRIVATE(first)
64 
65  IF (first) THEN
66  CALL dissip_allocate
67  first=.false.
68  ENDIF
69 c-----------------------------------------------------------------------
70 c initialisations:
71 c ----------------
72 
73 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
74  DO l=1,llm
75  te1dt(l) = tetaudiv(l) * dtdiss
76  te2dt(l) = tetaurot(l) * dtdiss
77  te3dt(l) = tetah(l) * dtdiss
78  ENDDO
79 c$OMP END DO NOWAIT
80 c CALL initial0( ijp1llm, du )
81 c CALL initial0( ijmllm , dv )
82 c CALL initial0( ijp1llm, dh )
83 
84  ijb=ij_begin
85  ije=ij_end
86 
87 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
88  DO l=1,llm
89  du(ijb:ije,l)=0
90  dh(ijb:ije,l)=0
91  ENDDO
92 c$OMP END DO NOWAIT
93 
94  if (pole_sud) ije=ij_end-iip1
95 
96 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
97  DO l=1,llm
98  dv(ijb:ije,l)=0
99  ENDDO
100 c$OMP END DO NOWAIT
101 
102 c-----------------------------------------------------------------------
103 c Calcul de la dissipation:
104 c -------------------------
105 
106 c Calcul de la partie grad ( div ) :
107 c -------------------------------------
108 
109 
110 
111  IF(lstardis) THEN
112 c IF (.FALSE.) THEN
113  CALL gradiv2_loc( llm,ucov,vcov,nitergdiv,gdx,gdy )
114  ELSE
115 ! CALL gradiv_p ( llm,ucov,vcov,nitergdiv,gdx,gdy )
116  ENDIF
117 
118 #ifdef DEBUG_IO
119  call writefield_u('gdx',gdx)
120  call writefield_v('gdy',gdy)
121 #endif
122 
123  ijb=ij_begin
124  ije=ij_end
125  if (pole_sud) ije=ij_end-iip1
126 
127 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
128  DO l=1,llm
129  if (pole_nord) then
130  DO ij = 1, iip1
131  gdx( ij ,l) = 0.
132  ENDDO
133  endif
134 
135  if (pole_sud) then
136  DO ij = 1, iip1
137  gdx(ij+ip1jm,l) = 0.
138  ENDDO
139  endif
140 
141  if (pole_nord) ijb=ij_begin+iip1
142  DO ij = ijb,ije
143  du(ij,l) = du(ij,l) - te1dt(l) *gdx(ij,l)
144  ENDDO
145 
146  if (pole_nord) ijb=ij_begin
147  DO ij = ijb,ije
148  dv(ij,l) = dv(ij,l) - te1dt(l) *gdy(ij,l)
149  ENDDO
150 
151  ENDDO
152 c$OMP END DO NOWAIT
153 c calcul de la partie n X grad ( rot ):
154 c ---------------------------------------
155 
156  IF(lstardis) THEN
157 c IF (.FALSE.) THEN
158  CALL nxgraro2_loc( llm,ucov, vcov, nitergrot,grx,gry )
159  ELSE
160 ! CALL nxgrarot_p( llm,ucov, vcov, nitergrot,grx,gry )
161  ENDIF
162 
163 #ifdef DEBUG_IO
164  call writefield_u('grx',grx)
165  call writefield_v('gry',gry)
166 #endif
167 
168 
169  ijb=ij_begin
170  ije=ij_end
171  if (pole_sud) ije=ij_end-iip1
172 
173 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
174  DO l=1,llm
175 
176  if (pole_nord) then
177  DO ij = 1, iip1
178  grx(ij,l) = 0.
179  ENDDO
180  endif
181 
182  if (pole_nord) ijb=ij_begin+iip1
183  DO ij = ijb,ije
184  du(ij,l) = du(ij,l) - te2dt(l) * grx(ij,l)
185  ENDDO
186 
187  if (pole_nord) ijb=ij_begin
188  DO ij = ijb, ije
189  dv(ij,l) = dv(ij,l) - te2dt(l) * gry(ij,l)
190  ENDDO
191 
192  ENDDO
193 c$OMP END DO NOWAIT
194 
195 c calcul de la partie div ( grad ):
196 c -----------------------------------
197 
198 
199  IF(lstardis) THEN
200 c IF (.FALSE.) THEN
201 
202  ijb=ij_begin
203  ije=ij_end
204 
205 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
206  DO l = 1, llm
207  DO ij = ijb, ije
208  deltapres(ij,l) = amax1( 0., p(ij,l) - p(ij,l+1) )
209  ENDDO
210  ENDDO
211 c$OMP END DO NOWAIT
212  CALL divgrad2_loc( llm,teta, deltapres ,niterh, gdx )
213  ELSE
214 ! CALL divgrad_p ( llm,teta, niterh, gdx )
215  ENDIF
216 
217 #ifdef DEBUG_IO
218  call writefield_u('gdx',gdx)
219 #endif
220 
221 
222  ijb=ij_begin
223  ije=ij_end
224 
225 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
226  DO l = 1,llm
227  DO ij = ijb,ije
228  dh( ij,l ) = dh( ij,l ) - te3dt(l) * gdx( ij,l )
229  ENDDO
230  ENDDO
231 c$OMP END DO NOWAIT
232 
233  RETURN
234  END
!$Id mode_top_bound COMMON comconstr dtdiss
Definition: comconst.h:7
subroutine gradiv2_loc(klevel, xcov, ycov, ld, gdx_out, gdy_out)
Definition: gradiv2_loc.F:2
!$Header cdivh!COMMON comdissipn tetaudiv(llm)
!$Header llmp1
Definition: paramet.h:14
subroutine dissip_loc(vcov, ucov, teta, p, dv, du, dh)
Definition: dissip_loc.F:5
integer, save ij_end
logical, save pole_sud
!$Id nitergdiv
Definition: comdissnew.h:13
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
!$Id nitergrot
Definition: comdissnew.h:13
integer, save ijb_v
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
logical, save pole_nord
subroutine nxgraro2_loc(klevel, xcov, ycov, lr, grx_out, gry_out)
Definition: nxgraro2_loc.F:2
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer, save ij_begin
integer, save ije_v
subroutine dissip_allocate
Definition: dissip_mod.F90:8
!$Header tetaurot
Definition: comdissipn.h:11
integer, save ije_u
subroutine divgrad2_loc(klevel, h, deltapres, lh, divgra_out)
Definition: divgrad2_loc.F:2
!$Id niterh
Definition: comdissnew.h:13
integer, save ijb_u
!$Header tetah
Definition: comdissipn.h:11