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

Last change on this file since 557 was 556, checked in by raasch, 14 years ago

last commit documented

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