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

Last change on this file since 550 was 494, checked in by raasch, 14 years ago

last commit documented; configuration example file for netcdf4 added

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