source: palm/trunk/SOURCE/user_init_flight.f90 @ 1969

Last change on this file since 1969 was 1958, checked in by suehring, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 2.8 KB
Line 
1!> @file user_init_flight.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2016 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: user_init_flight.f90 1958 2016-07-07 10:51:40Z suehring $
26!
27! 1957 2016-07-07 10:43:48Z suehring
28! Initial revision
29!
30! Description:
31! ------------
32!> Execution of user-defined initialization for flight measurements.
33!------------------------------------------------------------------------------!
34 SUBROUTINE user_init_flight( init, k, id, label_leg )
35 
36
37    USE control_parameters
38   
39    USE indices
40   
41    USE kinds
42   
43    USE netcdf_interface,                                                      &
44        ONLY: dofl_label, dofl_unit
45   
46    USE user
47
48    IMPLICIT NONE
49   
50    CHARACTER(LEN=10), OPTIONAL ::  label_leg     !< label of the respective leg
51   
52    INTEGER(iwp), OPTIONAL                ::  id  !< variable index
53    INTEGER(iwp), OPTIONAL, INTENT(INOUT) ::  k   !< index for respective variable and leg
54   
55    LOGICAL ::  init  !< variable to recognize initial call
56!
57!-- Sample for user-defined flight-time series.
58!-- For each quantity you have to give a label and a unit, which will be used
59!-- for the output into NetCDF file. They must not contain more than
60!-- twenty characters.
61
62
63    IF ( init )  THEN
64!
65!--    The number of user-defined quantity has to be increased appropriately.
66!--    In the following example, 2 user-defined quantities are added.
67!        num_var_fl_user = num_var_fl_user + 2
68
69       init = .FALSE.
70   
71    ELSE
72   
73!
74!--    Please add the respective number of new variables as following:
75     
76!        SELECT CASE ( id )
77!       
78!           CASE ( 1 )
79!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_u'
80!              dofl_unit(k)    = 'm/s'
81!              k               = k + 1
82!             
83!           CASE ( 2 )
84!     
85!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_v'
86!              dofl_unit(k)    = 'm/s'
87!              k               = k + 1
88!             
89!        END SELECT
90
91    ENDIF
92       
93 END SUBROUTINE user_init_flight
94
Note: See TracBrowser for help on using the repository browser.