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

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

flight module added

  • 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 1957 2016-07-07 10:43:48Z suehring $
26!
27!
28! Description:
29! ------------
30!> Execution of user-defined initialization for flight measurements.
31!------------------------------------------------------------------------------!
32 SUBROUTINE user_init_flight( init, k, id, label_leg )
33 
34
35    USE control_parameters
36   
37    USE indices
38   
39    USE kinds
40   
41    USE netcdf_interface,                                                      &
42        ONLY: dofl_label, dofl_unit
43   
44    USE user
45
46    IMPLICIT NONE
47   
48    CHARACTER(LEN=10), OPTIONAL ::  label_leg     !< label of the respective leg
49   
50    INTEGER(iwp), OPTIONAL                ::  id  !< variable index
51    INTEGER(iwp), OPTIONAL, INTENT(INOUT) ::  k   !< index for respective variable and leg
52   
53    LOGICAL ::  init  !< variable to recognize initial call
54!
55!-- Sample for user-defined flight-time series.
56!-- For each quantity you have to give a label and a unit, which will be used
57!-- for the output into NetCDF file. They must not contain more than
58!-- twenty characters.
59
60
61    IF ( init )  THEN
62!
63!--    The number of user-defined quantity has to be increased appropriately.
64!--    In the following example, 2 user-defined quantities are added.
65!        num_var_fl_user = num_var_fl_user + 2
66
67       init = .FALSE.
68   
69    ELSE
70   
71!
72!--    Please add the respective number of new variables as following:
73     
74!        SELECT CASE ( id )
75!       
76!           CASE ( 1 )
77!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_u'
78!              dofl_unit(k)    = 'm/s'
79!              k               = k + 1
80!             
81!           CASE ( 2 )
82!     
83!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_v'
84!              dofl_unit(k)    = 'm/s'
85!              k               = k + 1
86!             
87!        END SELECT
88
89    ENDIF
90       
91 END SUBROUTINE user_init_flight
92
Note: See TracBrowser for help on using the repository browser.