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

Last change on this file since 392 was 226, checked in by raasch, 15 years ago

preparations for the next release

  • Property svn:keywords set to Id
File size: 2.6 KB
Line 
1 SUBROUTINE user_statistics( mode, sr, tn )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: user_statistics.f90 226 2009-02-02 07:39:34Z raasch $
11!
12! 211 2008-11-11 04:46:24Z raasch
13! Former file user_interface.f90 split into one file per subroutine
14!
15! Description:
16! ------------
17! Calculation of user-defined statistics, i.e. horizontally averaged profiles
18! and time series.
19! This routine is called for every statistic region sr defined by the user,
20! but at least for the region "total domain" (sr=0).
21! See section 3.5.4 on how to define, calculate, and output user defined
22! quantities.
23!------------------------------------------------------------------------------!
24
25    USE arrays_3d
26    USE indices
27    USE statistics
28    USE user
29
30    IMPLICIT NONE
31
32    CHARACTER (LEN=*) ::  mode
33
34    INTEGER ::  i, j, k, sr, tn
35
36
37    IF ( mode == 'profiles' )  THEN
38
39!
40!--    Sample on how to calculate horizontally averaged profiles of user-
41!--    defined quantities. Each quantity is identified by the index
42!--    "pr_palm+#" where "#" is an integer starting from 1. These
43!--    user-profile-numbers must also be assigned to the respective strings
44!--    given by data_output_pr_user in routine user_check_data_output_pr.
45!       !$OMP DO
46!       DO  i = nxl, nxr
47!          DO  j = nys, nyn
48!             DO  k = nzb_s_inner(j,i)+1, nzt
49!!
50!!--             Sample on how to calculate the profile of the resolved-scale
51!!--             horizontal momentum flux u*v*
52!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +           &
53!                      ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) * &
54!                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )   &
55!                                                 * rmask(j,i,sr)
56!!
57!!--             Further profiles can be defined and calculated by increasing
58!!--             the second index of array sums_l (replace ... appropriately)
59!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ... &
60!                                         * rmask(j,i,sr)
61!             ENDDO
62!          ENDDO
63!       ENDDO
64
65    ELSEIF ( mode == 'time_series' )  THEN
66
67!
68!--    Sample on how to add values for the user-defined time series quantities.
69!--    These have to be defined before in routine user_init. This sample
70!--    creates two time series for the absolut values of the horizontal
71!--    velocities u and v.
72!       ts_value(dots_num_palm+1,sr) = ABS( u_max )
73!       ts_value(dots_num_palm+2,sr) = ABS( v_max )
74
75    ENDIF
76
77 END SUBROUTINE user_statistics
78
Note: See TracBrowser for help on using the repository browser.