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

Last change on this file since 646 was 623, checked in by raasch, 13 years ago

last commit documented

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