source: palm/trunk/SOURCE/user_statistics.f90 @ 1036

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

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 4.8 KB
Line 
1 SUBROUTINE user_statistics( mode, sr, tn )
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: user_statistics.f90 1036 2012-10-22 13:43:42Z raasch $
27!
28! 678 2011-02-02 14:31:56Z raasch
29! Bugfix: module pegrid was missing
30!
31! 622 2010-12-10 08:08:13Z raasch
32! optional barriers included in order to speed up collective operations
33!
34! 555 2010-09-07 07:32:53Z raasch
35! Bugfix: wrong dimension used for ts_value_l
36!
37! 493 2010-03-01 08:30:24Z raasch
38! Bugfix: timeseries data have to be collected by PE0
39!
40! 211 2008-11-11 04:46:24Z raasch
41! Former file user_interface.f90 split into one file per subroutine
42!
43! Description:
44! ------------
45! Calculation of user-defined statistics, i.e. horizontally averaged profiles
46! and time series.
47! This routine is called for every statistic region sr defined by the user,
48! but at least for the region "total domain" (sr=0).
49! See section 3.5.4 on how to define, calculate, and output user defined
50! quantities.
51!------------------------------------------------------------------------------!
52
53    USE arrays_3d
54    USE indices
55    USE netcdf_control
56    USE pegrid
57    USE statistics
58    USE user
59
60    IMPLICIT NONE
61
62    CHARACTER (LEN=*) ::  mode
63
64    INTEGER ::  i, j, k, sr, tn
65
66    REAL, DIMENSION(dots_num_palm+1:dots_max) ::  ts_value_l
67
68
69    IF ( mode == 'profiles' )  THEN
70
71!
72!--    Sample on how to calculate horizontally averaged profiles of user-
73!--    defined quantities. Each quantity is identified by the index
74!--    "pr_palm+#" where "#" is an integer starting from 1. These
75!--    user-profile-numbers must also be assigned to the respective strings
76!--    given by data_output_pr_user in routine user_check_data_output_pr.
77!       !$OMP DO
78!       DO  i = nxl, nxr
79!          DO  j = nys, nyn
80!             DO  k = nzb_s_inner(j,i)+1, nzt
81!!
82!!--             Sample on how to calculate the profile of the resolved-scale
83!!--             horizontal momentum flux u*v*
84!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +           &
85!                      ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) * &
86!                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )   &
87!                                                 * rmask(j,i,sr)
88!!
89!!--             Further profiles can be defined and calculated by increasing
90!!--             the second index of array sums_l (replace ... appropriately)
91!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ... &
92!                                         * rmask(j,i,sr)
93!             ENDDO
94!          ENDDO
95!       ENDDO
96
97    ELSEIF ( mode == 'time_series' )  THEN
98
99!
100!--    Sample on how to add values for the user-defined time series quantities.
101!--    These have to be defined before in routine user_init. This sample
102!--    creates two time series for the absolut values of the horizontal
103!--    velocities u and v.
104!       ts_value_l = 0.0
105!       ts_value_l(dots_num_palm+1) = ABS( u_max )
106!       ts_value_l(dots_num_palm+2) = ABS( v_max )
107!
108!--     Collect / send values to PE0, because only PE0 outputs the time series.
109!--     CAUTION: Collection is done by taking the sum over all processors.
110!--              You may have to normalize this sum, depending on the quantity
111!--              that you like to calculate. For serial runs, nothing has to be
112!--              done.
113!--     HINT: If the time series value that you are calculating has the same
114!--           value on all PEs, you can omit the MPI_ALLREDUCE call and
115!--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
116!#if defined( __parallel )
117!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
118!       CALL MPI_ALLREDUCE( ts_value_l(dots_num_palm+1),                       &
119!                           ts_value(dots_num_palm+1,sr),                      &
120!                           dots_max-dots_num_palm, MPI_REAL, MPI_SUM, comm2d, &
121!                           ierr )
122!#else
123!       ts_value(dots_num_palm+1:,sr) = ts_value_l
124!#endif
125
126    ENDIF
127
128 END SUBROUTINE user_statistics
129
Note: See TracBrowser for help on using the repository browser.