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

Last change on this file since 697 was 679, checked in by raasch, 13 years ago

last commit documented

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