source: palm/trunk/SOURCE/user_spectra.f90 @ 287

Last change on this file since 287 was 274, checked in by heinze, 15 years ago

Indentation of the message calls corrected

  • Property svn:keywords set to Id
File size: 2.4 KB
Line 
1 SUBROUTINE user_spectra( mode, m, pr )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! Output of messages replaced by message handling routine.
7!
8! Former revisions:
9! -----------------
10! $Id: user_spectra.f90 274 2009-03-26 15:11:21Z 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 spectra.
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 control_parameters
24    USE indices
25    USE spectrum
26    USE statistics
27    USE user
28
29    IMPLICIT NONE
30
31    CHARACTER (LEN=*) ::  mode
32
33    INTEGER ::  i, j, k, m, pr
34
35
36!
37!-- Sample on how to calculate spectra of user-defined quantities.
38!-- Each quantity is identified by the corresponding user profile 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    IF ( mode == 'preprocess' )  THEN
43
44       SELECT CASE ( TRIM( data_output_sp(m) ) )
45         
46          CASE ( 'u', 'v', 'w', 'pt', 'q' )
47!--          Not allowed here since these are the standard quantities used in
48!--          preprocess_spectra.
49       
50!          CASE ( 'u*v*' )
51!             pr = pr_palm+1
52!             d(nzb+1:nzt,nys:nyn,nxl:nxr) = ustvst(nzb+1:nzt,nys:nyn,nxl:nxr)
53       
54          CASE DEFAULT
55             message_string = 'Spectra of ' // &
56                         TRIM( data_output_sp(m) ) // ' can not be calculated'
57             CALL message( 'user_spectra', 'UI0010', 0, 0, 0, 6, 0 )
58           
59       END SELECT
60
61    ELSEIF ( mode == 'data_output' )  THEN
62
63       SELECT CASE ( TRIM( data_output_sp(m) ) )
64
65          CASE ( 'u', 'v', 'w', 'pt', 'q' )
66!--          Not allowed here since these are the standard quantities used in
67!--          data_output_spectra.
68
69!          CASE ( 'u*v*' )
70!             pr = 6
71
72          CASE DEFAULT
73             message_string = 'Spectra of ' //  &
74                              TRIM( data_output_sp(m) ) // ' are not defined'
75             CALL message( 'user_spectra', 'UI0011', 0, 0, 0, 6, 0 )
76             
77          END SELECT
78
79    ENDIF
80
81 END SUBROUTINE user_spectra
82
Note: See TracBrowser for help on using the repository browser.