source: palm/tags/release-3.9/SOURCE/user_statistics.f90 @ 3968

Last change on this file since 3968 was 1037, checked in by raasch, 11 years ago

last commit documented

  • 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 1037 2012-10-22 14:10:22Z suehring $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 678 2011-02-02 14:31:56Z raasch
32! Bugfix: module pegrid was missing
33!
34! 622 2010-12-10 08:08:13Z raasch
35! optional barriers included in order to speed up collective operations
36!
37! 555 2010-09-07 07:32:53Z raasch
38! Bugfix: wrong dimension used for ts_value_l
39!
40! 493 2010-03-01 08:30:24Z raasch
41! Bugfix: timeseries data have to be collected by PE0
42!
43! 211 2008-11-11 04:46:24Z raasch
44! Former file user_interface.f90 split into one file per subroutine
45!
46! Description:
47! ------------
48! Calculation of user-defined statistics, i.e. horizontally averaged profiles
49! and time series.
50! This routine is called for every statistic region sr defined by the user,
51! but at least for the region "total domain" (sr=0).
52! See section 3.5.4 on how to define, calculate, and output user defined
53! quantities.
54!------------------------------------------------------------------------------!
55
56    USE arrays_3d
57    USE indices
58    USE netcdf_control
59    USE pegrid
60    USE statistics
61    USE user
62
63    IMPLICIT NONE
64
65    CHARACTER (LEN=*) ::  mode
66
67    INTEGER ::  i, j, k, sr, tn
68
69    REAL, DIMENSION(dots_num_palm+1:dots_max) ::  ts_value_l
70
71
72    IF ( mode == 'profiles' )  THEN
73
74!
75!--    Sample on how to calculate horizontally averaged profiles of user-
76!--    defined quantities. Each quantity is identified by the index
77!--    "pr_palm+#" where "#" is an integer starting from 1. These
78!--    user-profile-numbers must also be assigned to the respective strings
79!--    given by data_output_pr_user in routine user_check_data_output_pr.
80!       !$OMP DO
81!       DO  i = nxl, nxr
82!          DO  j = nys, nyn
83!             DO  k = nzb_s_inner(j,i)+1, nzt
84!!
85!!--             Sample on how to calculate the profile of the resolved-scale
86!!--             horizontal momentum flux u*v*
87!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +           &
88!                      ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) * &
89!                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )   &
90!                                                 * rmask(j,i,sr)
91!!
92!!--             Further profiles can be defined and calculated by increasing
93!!--             the second index of array sums_l (replace ... appropriately)
94!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ... &
95!                                         * rmask(j,i,sr)
96!             ENDDO
97!          ENDDO
98!       ENDDO
99
100    ELSEIF ( mode == 'time_series' )  THEN
101
102!
103!--    Sample on how to add values for the user-defined time series quantities.
104!--    These have to be defined before in routine user_init. This sample
105!--    creates two time series for the absolut values of the horizontal
106!--    velocities u and v.
107!       ts_value_l = 0.0
108!       ts_value_l(dots_num_palm+1) = ABS( u_max )
109!       ts_value_l(dots_num_palm+2) = ABS( v_max )
110!
111!--     Collect / send values to PE0, because only PE0 outputs the time series.
112!--     CAUTION: Collection is done by taking the sum over all processors.
113!--              You may have to normalize this sum, depending on the quantity
114!--              that you like to calculate. For serial runs, nothing has to be
115!--              done.
116!--     HINT: If the time series value that you are calculating has the same
117!--           value on all PEs, you can omit the MPI_ALLREDUCE call and
118!--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
119!#if defined( __parallel )
120!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
121!       CALL MPI_ALLREDUCE( ts_value_l(dots_num_palm+1),                       &
122!                           ts_value(dots_num_palm+1,sr),                      &
123!                           dots_max-dots_num_palm, MPI_REAL, MPI_SUM, comm2d, &
124!                           ierr )
125!#else
126!       ts_value(dots_num_palm+1:,sr) = ts_value_l
127!#endif
128
129    ENDIF
130
131 END SUBROUTINE user_statistics
132
Note: See TracBrowser for help on using the repository browser.