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

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

pointer free version can be generated with cpp switch nopointer

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