source: palm/tags/release-3.10/SOURCE/user_statistics.f90 @ 4417

Last change on this file since 4417 was 1047, checked in by maronga, 11 years ago

last commit documented / added nc2vdf

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