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

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 5.2 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-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! kind-parameters added to all INTEGER and REAL declaration statements,
23! kinds are defined in new module kinds,
24! old module precision_kind is removed,
25! revision history before 2012 removed,
26! comment fields (!:) to be used for variable explanations added to
27! all variable declaration statements
28!
29!
30! Former revisions:
31! -----------------
32! $Id: user_statistics.f90 1320 2014-03-20 08:40:49Z raasch $
33!
34! 1046 2012-11-09 14:38:45Z maronga
35! added preprocessor directive for parameter file check
36!
37! 1036 2012-10-22 13:43:42Z raasch
38! code put under GPL (PALM 3.9)
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   
55    USE indices
56   
57    USE kinds
58   
59    USE netcdf_control
60   
61    USE pegrid
62   
63    USE statistics
64   
65    USE user
66
67    IMPLICIT NONE
68
69    CHARACTER (LEN=*) ::  mode   !:
70
71    INTEGER(iwp) ::  i    !:
72    INTEGER(iwp) ::  j    !:
73    INTEGER(iwp) ::  k    !:
74    INTEGER(iwp) ::  sr   !:
75    INTEGER(iwp) ::  tn   !:
76
77    REAL(wp),                                                                  &
78       DIMENSION(dots_num_palm+1:dots_max) ::                                  &
79          ts_value_l   !:
80
81
82    IF ( mode == 'profiles' )  THEN
83
84!
85!--    Sample on how to calculate horizontally averaged profiles of user-
86!--    defined quantities. Each quantity is identified by the index
87!--    "pr_palm+#" where "#" is an integer starting from 1. These
88!--    user-profile-numbers must also be assigned to the respective strings
89!--    given by data_output_pr_user in routine user_check_data_output_pr.
90!       !$OMP DO
91!       DO  i = nxl, nxr
92!          DO  j = nys, nyn
93!             DO  k = nzb_s_inner(j,i)+1, nzt
94!!
95!!--             Sample on how to calculate the profile of the resolved-scale
96!!--             horizontal momentum flux u*v*
97!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +               &
98!                      ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *     &
99!                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )       &
100!                                                 * rmask(j,i,sr)
101!!
102!!--             Further profiles can be defined and calculated by increasing
103!!--             the second index of array sums_l (replace ... appropriately)
104!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...           &
105!                                         * rmask(j,i,sr)
106!             ENDDO
107!          ENDDO
108!       ENDDO
109
110    ELSEIF ( mode == 'time_series' )  THEN
111
112!
113!--    Sample on how to add values for the user-defined time series quantities.
114!--    These have to be defined before in routine user_init. This sample
115!--    creates two time series for the absolut values of the horizontal
116!--    velocities u and v.
117!       ts_value_l = 0.0
118!       ts_value_l(dots_num_palm+1) = ABS( u_max )
119!       ts_value_l(dots_num_palm+2) = ABS( v_max )
120!
121!--     Collect / send values to PE0, because only PE0 outputs the time series.
122!--     CAUTION: Collection is done by taking the sum over all processors.
123!--              You may have to normalize this sum, depending on the quantity
124!--              that you like to calculate. For serial runs, nothing has to be
125!--              done.
126!--     HINT: If the time series value that you are calculating has the same
127!--           value on all PEs, you can omit the MPI_ALLREDUCE call and
128!--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
129!#if defined( __parallel ) && ! defined ( __check )
130!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
131!       CALL MPI_ALLREDUCE( ts_value_l(dots_num_palm+1),                         &
132!                           ts_value(dots_num_palm+1,sr),                        &
133!                           dots_max-dots_num_palm, MPI_REAL, MPI_SUM, comm2d,   &
134!                           ierr )
135!#else
136!       ts_value(dots_num_palm+1:,sr) = ts_value_l
137!#endif
138
139    ENDIF
140
141 END SUBROUTINE user_statistics
142
Note: See TracBrowser for help on using the repository browser.