LMDZ
dissip_p.F
Go to the documentation of this file.
1 !
2 ! $Id: dissip_p.F 1987 2014-02-24 15:05:47Z emillour $
3 !
4  SUBROUTINE dissip_p( vcov,ucov,teta,p, dv,du,dh )
5 c
6  USE parallel_lmdz
7  USE write_field_p
8  IMPLICIT NONE
9 
10 
11 c .. Avec nouveaux operateurs star : gradiv2 , divgrad2, nxgraro2 ...
12 c ( 10/01/98 )
13 
14 c=======================================================================
15 c
16 c Auteur: P. Le Van
17 c -------
18 c
19 c Objet:
20 c ------
21 c
22 c Dissipation horizontale
23 c
24 c=======================================================================
25 c-----------------------------------------------------------------------
26 c Declarations:
27 c -------------
28 
29 #include "dimensions.h"
30 #include "paramet.h"
31 #include "comconst.h"
32 #include "comgeom.h"
33 #include "comdissnew.h"
34 #include "comdissipn.h"
35 
36 c Arguments:
37 c ----------
38 
39  REAL,INTENT(IN) :: vcov(ip1jm,llm) ! covariant meridional wind
40  REAL,INTENT(IN) :: ucov(ip1jmp1,llm) ! covariant zonal wind
41  REAL,INTENT(IN) :: teta(ip1jmp1,llm) ! potentail temperature
42  REAL,INTENT(IN) :: p(ip1jmp1,llmp1) ! pressure
43  ! tendencies (.../s) on covariant winds and potential temperature
44  REAL,INTENT(OUT) :: dv(ip1jm,llm)
45  REAL,INTENT(OUT) :: du(ip1jmp1,llm)
46  REAL,INTENT(OUT) :: dh(ip1jmp1,llm)
47 
48 c Local:
49 c ------
50 
51  REAL gdx(ip1jmp1,llm),gdy(ip1jm,llm)
52  REAL grx(ip1jmp1,llm),gry(ip1jm,llm)
53  REAL te1dt(llm),te2dt(llm),te3dt(llm)
54  REAL deltapres(ip1jmp1,llm)
55 
56  INTEGER l,ij
57 
58  REAL SSUM
59  integer :: ijb,ije
60 c-----------------------------------------------------------------------
61 c initialisations:
62 c ----------------
63 
64 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
65  DO l=1,llm
66  te1dt(l) = tetaudiv(l) * dtdiss
67  te2dt(l) = tetaurot(l) * dtdiss
68  te3dt(l) = tetah(l) * dtdiss
69  ENDDO
70 c$OMP END DO NOWAIT
71 c CALL initial0( ijp1llm, du )
72 c CALL initial0( ijmllm , dv )
73 c CALL initial0( ijp1llm, dh )
74 
75  ijb=ij_begin
76  ije=ij_end
77 
78 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
79  DO l=1,llm
80  du(ijb:ije,l)=0
81  dh(ijb:ije,l)=0
82  ENDDO
83 c$OMP END DO NOWAIT
84 
85  if (pole_sud) ije=ij_end-iip1
86 
87 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
88  DO l=1,llm
89  dv(ijb:ije,l)=0
90  ENDDO
91 c$OMP END DO NOWAIT
92 
93 c-----------------------------------------------------------------------
94 c Calcul de la dissipation:
95 c -------------------------
96 
97 c Calcul de la partie grad ( div ) :
98 c -------------------------------------
99 
100 
101 
102  IF(lstardis) THEN
103 c IF (.FALSE.) THEN
104  CALL gradiv2_p( llm,ucov,vcov,nitergdiv,gdx,gdy )
105  ELSE
106  CALL gradiv_p ( llm,ucov,vcov,nitergdiv,gdx,gdy )
107  ENDIF
108 
109 
110  ijb=ij_begin
111  ije=ij_end
112  if (pole_sud) ije=ij_end-iip1
113 
114 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
115  DO l=1,llm
116  if (pole_nord) then
117  DO ij = 1, iip1
118  gdx( ij ,l) = 0.
119  ENDDO
120  endif
121 
122  if (pole_sud) then
123  DO ij = 1, iip1
124  gdx(ij+ip1jm,l) = 0.
125  ENDDO
126  endif
127 
128  if (pole_nord) ijb=ij_begin+iip1
129  DO ij = ijb,ije
130  du(ij,l) = du(ij,l) - te1dt(l) *gdx(ij,l)
131  ENDDO
132 
133  if (pole_nord) ijb=ij_begin
134  DO ij = ijb,ije
135  dv(ij,l) = dv(ij,l) - te1dt(l) *gdy(ij,l)
136  ENDDO
137 
138  ENDDO
139 c$OMP END DO NOWAIT
140 c calcul de la partie n X grad ( rot ):
141 c ---------------------------------------
142 
143  IF(lstardis) THEN
144 c IF (.FALSE.) THEN
145  CALL nxgraro2_p( llm,ucov, vcov, nitergrot,grx,gry )
146  ELSE
147  CALL nxgrarot_p( llm,ucov, vcov, nitergrot,grx,gry )
148  ENDIF
149 
150 
151 
152  ijb=ij_begin
153  ije=ij_end
154  if (pole_sud) ije=ij_end-iip1
155 
156 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
157  DO l=1,llm
158 
159  if (pole_nord) then
160  DO ij = 1, iip1
161  grx(ij,l) = 0.
162  ENDDO
163  endif
164 
165  if (pole_nord) ijb=ij_begin+iip1
166  DO ij = ijb,ije
167  du(ij,l) = du(ij,l) - te2dt(l) * grx(ij,l)
168  ENDDO
169 
170  if (pole_nord) ijb=ij_begin
171  DO ij = ijb, ije
172  dv(ij,l) = dv(ij,l) - te2dt(l) * gry(ij,l)
173  ENDDO
174 
175  ENDDO
176 c$OMP END DO NOWAIT
177 
178 c calcul de la partie div ( grad ):
179 c -----------------------------------
180 
181 
182  IF(lstardis) THEN
183 c IF (.FALSE.) THEN
184 
185  ijb=ij_begin
186  ije=ij_end
187 
188 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
189  DO l = 1, llm
190  DO ij = ijb, ije
191  deltapres(ij,l) = amax1( 0., p(ij,l) - p(ij,l+1) )
192  ENDDO
193  ENDDO
194 c$OMP END DO NOWAIT
195  CALL divgrad2_p( llm,teta, deltapres ,niterh, gdx )
196  ELSE
197  CALL divgrad_p ( llm,teta, niterh, gdx )
198  ENDIF
199 
200 c call write_field3d_p('gdx2',reshape(gdx,(/iip1,jmp1,llm/)))
201 c stop
202 
203  ijb=ij_begin
204  ije=ij_end
205 
206 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
207  DO l = 1,llm
208  DO ij = ijb,ije
209  dh( ij,l ) = dh( ij,l ) - te3dt(l) * gdx( ij,l )
210  ENDDO
211  ENDDO
212 c$OMP END DO NOWAIT
213 
214  RETURN
215  END
!$Id mode_top_bound COMMON comconstr dtdiss
Definition: comconst.h:7
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
!$Header cdivh!COMMON comdissipn tetaudiv(llm)
!$Header llmp1
Definition: paramet.h:14
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
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
subroutine nxgraro2_p(klevel, xcov, ycov, lr, grx_out, gry_out)
Definition: nxgraro2_p.F:2
logical, save pole_nord
subroutine nxgrarot_p(klevel, xcov, ycov, lr, grx_out, gry_out)
Definition: nxgrarot_p.F:2
subroutine gradiv2_p(klevel, xcov, ycov, ld, gdx_out, gdy_out)
Definition: gradiv2_p.F:2
integer, save ij_begin
subroutine divgrad2_p(klevel, h, deltapres, lh, divgra_out)
Definition: divgrad2_p.F:2
subroutine gradiv_p(klevel, xcov, ycov, ld, gdx_out, gdy_out)
Definition: gradiv_p.F:2
subroutine dissip_p(vcov, ucov, teta, p, dv, du, dh)
Definition: dissip_p.F:5
!$Header tetaurot
Definition: comdissipn.h:11
subroutine divgrad_p(klevel, h, lh, divgra_out)
Definition: divgrad_p.F:2
!$Id niterh
Definition: comdissnew.h:13
!$Header tetah
Definition: comdissipn.h:11