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

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

New:
---
Output in NetCDF4-format. New d3par-parameter netcdf_data_format.

(check_open, check_parameters, close_file, data_output_2d, data_output_3d, header, modules, netcdf, parin)

Modules to be loaded for compilation (mbuild) or job execution (mrun)
can be given in the configuration file using variable modules. Example:

%modules ifort/11.0.069:netcdf lcsgih parallel

This method replaces the (undocumented) mpilib-variable.

WARNING: All fixed settings of modules in the scripts mbuild, mrun, and subjob
have been removed! Please set the modules variable appropriately in your
configuration file. (mbuild, mrun, subjob)

Changed:


Parameters netcdf_64bit and netcdf_64bit_3d have been removed. Use
netcdf_data_format = 2 for choosing the classic 64bit-offset format (this is
the default). The offset-format can not be set independently for the
3d-output-data any more.

Parameters netcdf_format_mask, netcdf_format_mask_av, and variables
nc_format_mask, format_parallel_io removed. They are replaced by the new
parameter netcdf_data_format. (check_open, close_file,
data_output_mask, header, init_masks, modules, parin)

Errors:


bugfix in trunk/UTIL/Makefile: forgot to compile for interpret_config

Bugfix: timeseries data have to be collected by PE0 (user_statistics)

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