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

Last change on this file since 213 was 211, checked in by raasch, 15 years ago

user interface was split into one single file per subroutine

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