source: palm/trunk/SOURCE/user_init_flight_mod.f90 @ 4598

Last change on this file since 4598 was 4522, checked in by suehring, 4 years ago

user_init_flight modularized and renamed to user_init_flight_mod

  • Property svn:keywords set to Id
File size: 4.1 KB
RevLine 
[4522]1!> @file user_init_flight_mod.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_mod.f90 4522 2020-05-06 14:17:05Z suehring $
[4522]27! * Modularize user_init_flight in order to provide an explicit interface.
28! * routine renamed to user_init_flight_mod
29!
30! 4498 2020-04-15 14:26:31Z raasch
[4498]31! file re-formatted to follow the PALM coding standard
32!
33!
34! 4360 2020-01-07 11:25:50Z suehring
[4182]35! Corrected "Former revisions" section
[4498]36!
[4182]37! 3768 2019-02-27 14:35:58Z raasch
[3768]38! statements commented or added to avoid compiler warnings about unused variables
[4498]39!
[3768]40! 3655 2019-01-07 16:51:22Z knoop
[2716]41! Corrected "Former revisions" section
[4498]42!
[4182]43! 1957 2016-07-07 10:43:48Z suehring
44! Initial revision
[1957]45!
[4522]46!
[1957]47! Description:
48! ------------
[4522]49!> Initialization of user-defined flight measurements.
50!>
51!> @todo Integrate into user_module when circular dependencies has been vanished.
[4498]52!--------------------------------------------------------------------------------------------------!
[4522]53 MODULE user_init_flight_mod
[1957]54
55    USE control_parameters
[4498]56
[1957]57    USE indices
[4498]58
[1957]59    USE kinds
[4498]60
61!    USE netcdf_interface,                                                                          &
62!        ONLY: dofl_label,                                                                          &
63!              dofl_unit
64
[1957]65    USE user
66
67    IMPLICIT NONE
[4498]68
[4522]69    PUBLIC user_init_flight
70
71    INTERFACE user_init_flight
72       MODULE PROCEDURE user_init_flight
73    END INTERFACE user_init_flight
74
75    CONTAINS
76
77! Description:
78! ------------
79!> Execution of user-defined initialization for flight measurements.
80!--------------------------------------------------------------------------------------------------!
81 SUBROUTINE user_init_flight( init, k, id, label_leg )
82
[1957]83    CHARACTER(LEN=10), OPTIONAL ::  label_leg     !< label of the respective leg
[4498]84
[1957]85    INTEGER(iwp), OPTIONAL                ::  id  !< variable index
86    INTEGER(iwp), OPTIONAL, INTENT(INOUT) ::  k   !< index for respective variable and leg
[3768]87
[4498]88    LOGICAL ::  init  !< variable to recognize initial call
89
[1957]90!
[3768]91!-- Following statements are added to avoid compiler warnings about unused variables. Please remove.
92    IF ( PRESENT( id )        )  CONTINUE
93    IF ( PRESENT( k )         )  CONTINUE
94    IF ( PRESENT( label_leg ) )  CONTINUE
95
96!
[1957]97!-- Sample for user-defined flight-time series.
[4498]98!-- For each quantity you have to give a label and a unit, which will be used for the output into
99!-- NetCDF file. They must not contain more than twenty characters.
[1957]100
101
102    IF ( init )  THEN
103!
104!--    The number of user-defined quantity has to be increased appropriately.
105!--    In the following example, 2 user-defined quantities are added.
[4498]106!        num_var_fl_user = num_var_fl_user + 2
[1957]107
108       init = .FALSE.
[4498]109
[1957]110    ELSE
[4498]111
[1957]112!
113!--    Please add the respective number of new variables as following:
[4498]114
[1957]115!        SELECT CASE ( id )
[4498]116!
[1957]117!           CASE ( 1 )
118!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_u'
119!              dofl_unit(k)    = 'm/s'
120!              k               = k + 1
[4498]121!
[1957]122!           CASE ( 2 )
[4498]123!
[1957]124!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_v'
125!              dofl_unit(k)    = 'm/s'
126!              k               = k + 1
[4498]127!
[1957]128!        END SELECT
129
130    ENDIF
[4498]131
[1957]132 END SUBROUTINE user_init_flight
[4522]133 
134 END MODULE user_init_flight_mod
[1957]135
Note: See TracBrowser for help on using the repository browser.