source: palm/trunk/SOURCE/user_check_data_output_pr.f90 @ 557

Last change on this file since 557 was 557, checked in by weinreis, 14 years ago

bugfix message string in set_mask_locations

  • Property svn:keywords set to Id
File size: 2.7 KB
Line 
1 SUBROUTINE user_check_data_output_pr( variable, var_count, unit )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: user_check_data_output_pr.f90 557 2010-09-07 14:50:07Z weinreis $
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! Set the unit of user defined profile output quantities. For those variables
18! not recognized by the user, the parameter unit is set to "illegal", which
19! tells the calling routine that the output variable is not defined and leads
20! to a program abort.
21!------------------------------------------------------------------------------!
22
23    USE arrays_3d
24    USE indices
25    USE netcdf_control
26    USE profil_parameter
27    USE statistics
28    USE user
29
30    IMPLICIT NONE
31
32    CHARACTER (LEN=*) ::  unit, variable
33
34    INTEGER ::  index, var_count
35
36
37    SELECT CASE ( TRIM( variable ) )
38
39!
40!--    Uncomment and extend the following lines, if necessary.
41!--    Add additional CASE statements depending on the number of quantities
42!--    for which profiles are to be calculated. The respective calculations
43!--    to be performed have to be added in routine user_statistics.
44!--    The quantities are (internally) identified by a user-profile-number
45!--    (see variable "index" below). The first user-profile must be assigned
46!--    the number "pr_palm+1", the second one "pr_palm+2", etc. The respective
47!--    user-profile-numbers have also to be used in routine user_statistics!
48!       CASE ( 'u*v*' )                      ! quantity string as given in
49!                                            ! data_output_pr_user
50!          index = pr_palm + 1
51!          dopr_index(var_count)  = index    ! quantities' user-profile-number
52!          dopr_unit(var_count)   = 'm2/s2'  ! quantity unit
53!          hom(:,2,index,:)       = SPREAD( zu, 2, statistic_regions+1 )
54!                                            ! grid on which the quantity is
55!                                            ! defined (use zu or zw)
56
57       CASE ( 'u*v*' )                      ! quantity string as given in
58                                            ! data_output_pr_user
59          index = pr_palm + 1
60          dopr_index(var_count)  = index    ! quantities' user-profile-number
61          dopr_unit(var_count)   = 'm2/s2'  ! quantity unit
62          hom(:,2,index,:)       = SPREAD( zu, 2, statistic_regions+1 )
63                                            ! grid on which the quantity is
64                                            ! defined (use zu or zw)
65                                           
66       CASE DEFAULT
67          unit = 'illegal'
68
69    END SELECT
70
71
72 END SUBROUTINE user_check_data_output_pr
73
Note: See TracBrowser for help on using the repository browser.