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

Last change on this file since 212 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.1 KB
Line 
1 SUBROUTINE user_spectra( mode, m, pr )
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_spectra.f90 211 2008-11-11 04:46:24Z raasch $
11!
12! Description:
13! ------------
14! Calculation of user-defined spectra.
15! See section 3.5.4 on how to define, calculate, and output user defined
16! quantities.
17!------------------------------------------------------------------------------!
18
19    USE arrays_3d
20    USE indices
21    USE spectrum
22    USE statistics
23    USE user
24
25    IMPLICIT NONE
26
27    CHARACTER (LEN=*) ::  mode
28
29    INTEGER ::  i, j, k, m, pr
30
31
32!
33!-- Sample on how to calculate spectra of user-defined quantities.
34!-- Each quantity is identified by the corresponding user profile index
35!-- "pr_palm+#" where "#" is an integer starting from 1. These
36!-- user-profile-numbers must also be assigned to the respective strings
37!-- given by data_output_pr_user in routine user_check_data_output_pr.
38    IF ( mode == 'preprocess' )  THEN
39
40       SELECT CASE ( TRIM( data_output_sp(m) ) )
41         
42          CASE ( 'u', 'v', 'w', 'pt', 'q' )
43!--          Not allowed here since these are the standard quantities used in
44!--          preprocess_spectra.
45       
46!          CASE ( 'u*v*' )
47!             pr = pr_palm+1
48!             d(nzb+1:nzt,nys:nyn,nxl:nxr) = ustvst(nzb+1:nzt,nys:nyn,nxl:nxr)
49       
50          CASE DEFAULT
51             PRINT*, '+++ user_spectra/preprocess: Spectra of ', &
52                  TRIM( data_output_sp(m) ), ' can not be calculated'
53         
54       END SELECT
55
56    ELSEIF ( mode == 'data_output' )  THEN
57
58       SELECT CASE ( TRIM( data_output_sp(m) ) )
59
60          CASE ( 'u', 'v', 'w', 'pt', 'q' )
61!--          Not allowed here since these are the standard quantities used in
62!--          data_output_spectra.
63
64!          CASE ( 'u*v*' )
65!             pr = 6
66
67          CASE DEFAULT
68             PRINT*, '+++ user_spectra/data_output: Spectra of ', &
69                          TRIM( data_output_sp(m) ), ' are not defined'
70
71          END SELECT
72
73    ENDIF
74
75 END SUBROUTINE user_spectra
76
Note: See TracBrowser for help on using the repository browser.