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

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

New:
---

further adjustments on Tsubame and concerning openMP usage
(mrun, mbuild, subjob)

Changed:


Errors:


Bugfix in calculation of divergence of vertical flux of resolved scale
energy, pressure fluctuations, and flux of pressure fluctuation itself
(flow statistics)

Bugfix: module pegrid was missing. (user_statistics)

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