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

Last change on this file since 4521 was 4498, checked in by raasch, 4 years ago

bugfix for creation of filetypes, argument removed from rd_mpi_io_open, files re-formatted to follow the PALM coding standard

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