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

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

last commit documented

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