source: palm/trunk/SOURCE/buoyancy.f90 @ 1015

Last change on this file since 1015 was 1015, checked in by raasch, 12 years ago

Starting with changes required for GPU optimization. OpenACC statements for using NVIDIA GPUs added.
Adjustment of mixing length to the Prandtl mixing length at first grid point above ground removed.
mask array is set zero for ghost boundaries

  • Property svn:keywords set to Id
File size: 14.6 KB
Line 
1 MODULE buoyancy_mod
2
3!------------------------------------------------------------------------------!
4! Currrent revisions:
5! -----------------
6! accelerator version (*_acc) added
7!
8! Former revisions:
9! -----------------
10! $Id: buoyancy.f90 1015 2012-09-27 09:23:24Z raasch $
11!
12! 1010 2012-09-20 07:59:54Z raasch
13! cpp switch __nopointer added for pointer free version
14!
15! 622 2010-12-10 08:08:13Z raasch
16! optional barriers included in order to speed up collective operations
17!
18! 515 2010-03-18 02:30:38Z raasch
19! PGI-compiler creates SIGFPE in routine buoyancy, if opt>1 is used! Therefore,
20! opt=1 is forced by compiler-directive.
21!
22! 247 2009-02-27 14:01:30Z heinze
23! Output of messages replaced by message handling routine
24!
25! 132 2007-11-20 09:46:11Z letzel
26! Vertical scalar profiles now based on nzb_s_inner and ngp_2dh_s_inner.
27!
28! 106 2007-08-16 14:30:26Z raasch
29! i loop for u-component (sloping surface) is starting from nxlu (needed for
30! non-cyclic boundary conditions)
31!
32! 97 2007-06-21 08:23:15Z raasch
33! Routine reneralized to be used with temperature AND density:
34! argument theta renamed var, new argument var_reference,
35! use_pt_reference renamed use_reference,
36! calc_mean_pt_profile renamed calc_mean_profile
37!
38! 57 2007-03-09 12:05:41Z raasch
39! Reference temperature pt_reference can be used.
40!
41! RCS Log replace by Id keyword, revision history cleaned up
42!
43! Revision 1.19  2006/04/26 12:09:56  raasch
44! OpenMP optimization (one dimension added to sums_l)
45!
46! Revision 1.1  1997/08/29 08:56:48  raasch
47! Initial revision
48!
49!
50! Description:
51! ------------
52! Buoyancy term of the third component of the equation of motion.
53! WARNING: humidity is not regarded when using a sloping surface!
54!------------------------------------------------------------------------------!
55
56    PRIVATE
57    PUBLIC buoyancy, buoyancy_acc, calc_mean_profile
58
59    INTERFACE buoyancy
60       MODULE PROCEDURE buoyancy
61       MODULE PROCEDURE buoyancy_ij
62    END INTERFACE buoyancy
63
64    INTERFACE buoyancy_acc
65       MODULE PROCEDURE buoyancy_acc
66    END INTERFACE buoyancy_acc
67
68    INTERFACE calc_mean_profile
69       MODULE PROCEDURE calc_mean_profile
70    END INTERFACE calc_mean_profile
71
72 CONTAINS
73
74
75!------------------------------------------------------------------------------!
76! Call for all grid points
77!------------------------------------------------------------------------------!
78    SUBROUTINE buoyancy( var, var_reference, wind_component, pr )
79
80       USE arrays_3d
81       USE control_parameters
82       USE indices
83       USE pegrid
84       USE statistics
85
86       IMPLICIT NONE
87
88       INTEGER ::  i, j, k, pr, wind_component
89       REAL    ::  var_reference
90#if defined( __nopointer )
91       REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var
92#else
93       REAL, DIMENSION(:,:,:), POINTER ::  var
94#endif
95
96
97       IF ( .NOT. sloping_surface )  THEN
98!
99!--       Normal case: horizontal surface
100          IF ( use_reference )  THEN
101             DO  i = nxl, nxr
102                DO  j = nys, nyn
103                   DO  k = nzb_s_inner(j,i)+1, nzt-1
104                      tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5 * &
105                                                            (                  &
106                          ( var(k,j,i)   - hom(k,1,pr,0)   ) / var_reference + &
107                          ( var(k+1,j,i) - hom(k+1,1,pr,0) ) / var_reference   &
108                                                            )
109                   ENDDO
110                ENDDO
111             ENDDO
112          ELSE
113             DO  i = nxl, nxr
114                DO  j = nys, nyn
115                   DO  k = nzb_s_inner(j,i)+1, nzt-1
116                      tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5 * &
117                                                            (                  &
118                          ( var(k,j,i)   - hom(k,1,pr,0)   ) / hom(k,1,pr,0) + &
119                          ( var(k+1,j,i) - hom(k+1,1,pr,0) ) / hom(k+1,1,pr,0) &
120                                                            )
121                   ENDDO
122                ENDDO
123             ENDDO
124          ENDIF
125
126       ELSE
127!
128!--       Buoyancy term for a surface with a slope in x-direction. The equations
129!--       for both the u and w velocity-component contain proportionate terms.
130!--       Temperature field at time t=0 serves as environmental temperature.
131!--       Reference temperature (pt_surface) is the one at the lower left corner
132!--       of the total domain.
133          IF ( wind_component == 1 )  THEN
134
135             DO  i = nxlu, nxr
136                DO  j = nys, nyn
137                   DO  k = nzb_s_inner(j,i)+1, nzt-1
138                      tend(k,j,i) = tend(k,j,i) + g * sin_alpha_surface *      &
139                           0.5 * ( ( pt(k,j,i-1)         + pt(k,j,i)         ) &
140                                 - ( pt_slope_ref(k,i-1) + pt_slope_ref(k,i) ) &
141                                 ) / pt_surface
142                   ENDDO
143                ENDDO
144             ENDDO
145
146          ELSEIF ( wind_component == 3 )  THEN
147
148             DO  i = nxl, nxr
149                DO  j = nys, nyn
150                   DO  k = nzb_s_inner(j,i)+1, nzt-1
151                      tend(k,j,i) = tend(k,j,i) + g * cos_alpha_surface *      &
152                           0.5 * ( ( pt(k,j,i)         + pt(k+1,j,i)         ) &
153                                 - ( pt_slope_ref(k,i) + pt_slope_ref(k+1,i) ) &
154                                 ) / pt_surface
155                   ENDDO
156                ENDDO
157            ENDDO
158
159          ELSE
160             
161             WRITE( message_string, * ) 'no term for component "',&
162                                       wind_component,'"'
163             CALL message( 'buoyancy', 'PA0159', 1, 2, 0, 6, 0 )
164
165          ENDIF
166
167       ENDIF
168
169    END SUBROUTINE buoyancy
170
171
172!------------------------------------------------------------------------------!
173! Call for all grid points - accelerator version
174!------------------------------------------------------------------------------!
175    SUBROUTINE buoyancy_acc( var, var_reference, wind_component, pr )
176
177       USE arrays_3d
178       USE control_parameters
179       USE indices
180       USE pegrid
181       USE statistics
182
183       IMPLICIT NONE
184
185       INTEGER ::  i, j, k, pr, wind_component
186       REAL    ::  var_reference
187#if defined( __nopointer )
188       REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var
189#else
190       REAL, DIMENSION(:,:,:), POINTER ::  var
191#endif
192
193
194       IF ( .NOT. sloping_surface )  THEN
195!
196!--       Normal case: horizontal surface
197          IF ( use_reference )  THEN
198             DO  i = nxl, nxr
199                DO  j = nys, nyn
200                   DO  k = nzb_s_inner(j,i)+1, nzt-1
201                      tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5 * &
202                                                            (                  &
203                          ( var(k,j,i)   - hom(k,1,pr,0)   ) / var_reference + &
204                          ( var(k+1,j,i) - hom(k+1,1,pr,0) ) / var_reference   &
205                                                            )
206                   ENDDO
207                ENDDO
208             ENDDO
209          ELSE
210             !$acc kernels present( nzb_s_inner, hom, tend, var )
211             !$acc loop
212             DO  i = nxl, nxr
213                DO  j = nys, nyn
214                   !$acc loop vector(32)
215                   DO  k = 1, nzt-1
216                      IF ( k > nzb_s_inner(j,i) )  THEN
217                         tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5 * &
218                                                               (                  &
219                             ( var(k,j,i)   - hom(k,1,pr,0)   ) / hom(k,1,pr,0) + &
220                             ( var(k+1,j,i) - hom(k+1,1,pr,0) ) / hom(k+1,1,pr,0) &
221                                                               )
222                      ENDIF
223                   ENDDO
224                ENDDO
225             ENDDO
226             !$acc end kernels
227          ENDIF
228
229       ELSE
230!
231!--       Buoyancy term for a surface with a slope in x-direction. The equations
232!--       for both the u and w velocity-component contain proportionate terms.
233!--       Temperature field at time t=0 serves as environmental temperature.
234!--       Reference temperature (pt_surface) is the one at the lower left corner
235!--       of the total domain.
236          IF ( wind_component == 1 )  THEN
237
238             DO  i = nxlu, nxr
239                DO  j = nys, nyn
240                   DO  k = nzb_s_inner(j,i)+1, nzt-1
241                      tend(k,j,i) = tend(k,j,i) + g * sin_alpha_surface *      &
242                           0.5 * ( ( pt(k,j,i-1)         + pt(k,j,i)         ) &
243                                 - ( pt_slope_ref(k,i-1) + pt_slope_ref(k,i) ) &
244                                 ) / pt_surface
245                   ENDDO
246                ENDDO
247             ENDDO
248
249          ELSEIF ( wind_component == 3 )  THEN
250
251             DO  i = nxl, nxr
252                DO  j = nys, nyn
253                   DO  k = nzb_s_inner(j,i)+1, nzt-1
254                      tend(k,j,i) = tend(k,j,i) + g * cos_alpha_surface *      &
255                           0.5 * ( ( pt(k,j,i)         + pt(k+1,j,i)         ) &
256                                 - ( pt_slope_ref(k,i) + pt_slope_ref(k+1,i) ) &
257                                 ) / pt_surface
258                   ENDDO
259                ENDDO
260            ENDDO
261
262          ELSE
263
264             WRITE( message_string, * ) 'no term for component "',&
265                                       wind_component,'"'
266             CALL message( 'buoyancy', 'PA0159', 1, 2, 0, 6, 0 )
267
268          ENDIF
269
270       ENDIF
271
272    END SUBROUTINE buoyancy_acc
273
274
275!------------------------------------------------------------------------------!
276! Call for grid point i,j
277! ATTENTION: PGI-compiler creates SIGFPE if opt>1 is used! Therefore, opt=1 is
278!            forced by compiler-directive.
279!------------------------------------------------------------------------------!
280!pgi$r opt=1
281    SUBROUTINE buoyancy_ij( i, j, var, var_reference, wind_component, pr )
282
283       USE arrays_3d
284       USE control_parameters
285       USE indices
286       USE pegrid
287       USE statistics
288
289       IMPLICIT NONE
290
291       INTEGER ::  i, j, k, pr, wind_component
292       REAL    ::  var_reference
293#if defined( __nopointer )
294       REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var
295#else
296       REAL, DIMENSION(:,:,:), POINTER ::  var
297#endif
298
299
300       IF ( .NOT. sloping_surface )  THEN
301!
302!--       Normal case: horizontal surface
303          IF ( use_reference )  THEN
304             DO  k = nzb_s_inner(j,i)+1, nzt-1
305                 tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5 * (   &
306                         ( var(k,j,i)   - hom(k,1,pr,0)   ) / var_reference + &
307                         ( var(k+1,j,i) - hom(k+1,1,pr,0) ) / var_reference   &
308                                                                          )
309             ENDDO
310          ELSE
311             DO  k = nzb_s_inner(j,i)+1, nzt-1
312                 tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5 * (    &
313                          ( var(k,j,i)   - hom(k,1,pr,0)   ) / hom(k,1,pr,0) + &
314                          ( var(k+1,j,i) - hom(k+1,1,pr,0) ) / hom(k+1,1,pr,0) &
315                                                                          )
316             ENDDO
317          ENDIF
318
319       ELSE
320!
321!--       Buoyancy term for a surface with a slope in x-direction. The equations
322!--       for both the u and w velocity-component contain proportionate terms.
323!--       Temperature field at time t=0 serves as environmental temperature.
324!--       Reference temperature (pt_surface) is the one at the lower left corner
325!--       of the total domain.
326          IF ( wind_component == 1 )  THEN
327
328             DO  k = nzb_s_inner(j,i)+1, nzt-1
329                tend(k,j,i) = tend(k,j,i) + g * sin_alpha_surface *            &
330                           0.5 * ( ( pt(k,j,i-1)         + pt(k,j,i)         ) &
331                                 - ( pt_slope_ref(k,i-1) + pt_slope_ref(k,i) ) &
332                                 ) / pt_surface
333             ENDDO
334
335          ELSEIF ( wind_component == 3 )  THEN
336
337             DO  k = nzb_s_inner(j,i)+1, nzt-1
338                tend(k,j,i) = tend(k,j,i) + g * cos_alpha_surface *            &
339                           0.5 * ( ( pt(k,j,i)         + pt(k+1,j,i)         ) &
340                                 - ( pt_slope_ref(k,i) + pt_slope_ref(k+1,i) ) &
341                                 ) / pt_surface
342             ENDDO
343
344          ELSE
345
346             WRITE( message_string, * ) 'no term for component "',&
347                                       wind_component,'"'
348             CALL message( 'buoyancy', 'PA0159', 1, 2, 0, 6, 0 )
349
350          ENDIF
351
352       ENDIF
353
354    END SUBROUTINE buoyancy_ij
355
356
357    SUBROUTINE calc_mean_profile( var, pr )
358
359!------------------------------------------------------------------------------!
360! Description:
361! ------------
362! Calculate the horizontally averaged vertical temperature profile (pr=4 in case
363! of potential temperature and 44 in case of virtual potential temperature).
364!------------------------------------------------------------------------------!
365
366       USE control_parameters
367       USE indices
368       USE pegrid
369       USE statistics
370
371       IMPLICIT NONE
372
373       INTEGER ::  i, j, k, omp_get_thread_num, pr, tn
374#if defined( __nopointer )
375       REAL, DIMENSION(:,:,:) ::  var
376#else
377       REAL, DIMENSION(:,:,:), POINTER ::  var
378#endif
379
380!
381!--    Computation of the horizontally averaged profile of variable var, unless
382!--    already done by the relevant call from flow_statistics. The calculation
383!--    is done only for the first respective intermediate timestep in order to
384!--    spare communication time and to produce identical model results with jobs
385!--    which are calling flow_statistics at different time intervals.
386       IF ( .NOT. flow_statistics_called  .AND. &
387            intermediate_timestep_count == 1 )  THEN
388
389!
390!--       Horizontal average of variable var
391          tn           =   0  ! Default thread number in case of one thread
392          !$OMP PARALLEL PRIVATE( i, j, k, tn )
393!$        tn = omp_get_thread_num()
394          sums_l(:,pr,tn) = 0.0
395          !$OMP DO
396          DO  i = nxl, nxr
397             DO  j =  nys, nyn
398                DO  k = nzb_s_inner(j,i), nzt+1
399                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)
400                ENDDO
401             ENDDO
402          ENDDO
403          !$OMP END PARALLEL
404
405          DO  i = 1, threads_per_task-1
406             sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
407          ENDDO
408
409#if defined( __parallel )
410
411          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
412          CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb, &
413                              MPI_REAL, MPI_SUM, comm2d, ierr )
414
415#else
416
417          sums(:,pr) = sums_l(:,pr,0)
418
419#endif
420
421          hom(:,1,pr,0) = sums(:,pr) / ngp_2dh_s_inner(:,0)
422
423       ENDIF
424
425    END SUBROUTINE calc_mean_profile
426
427 END MODULE buoyancy_mod
Note: See TracBrowser for help on using the repository browser.